44 type,
extends ( eftcamb_designer_model ) :: eftcamb_horava
47 logical :: horavasolarsystem
51 real(dl) :: horava_eta
53 real(dl) :: horava_lambda
58 procedure :: read_model_selection => eftcambhoravareadmodelselectionfromfile
59 procedure :: allocate_model_selection => eftcambhoravaallocatemodelselection
60 procedure :: init_model_parameters => eftcambhoravainitmodelparameters
61 procedure :: init_model_parameters_from_file => eftcambhoravainitmodelparametersfromfile
63 procedure :: compute_param_number => eftcambhoravacomputeparametersnumber
64 procedure :: feedback => eftcambhoravafeedback
65 procedure :: parameter_names => eftcambhoravaparameternames
66 procedure :: parameter_names_latex => eftcambhoravaparameternameslatex
67 procedure :: parameter_values => eftcambhoravaparametervalues
69 procedure :: compute_background_eft_functions => eftcambhoravabackgroundeftfunctions
70 procedure :: compute_secondorder_eft_functions => eftcambhoravasecondordereftfunctions
71 procedure :: compute_dtauda => eftcambhoravacomputedtauda
72 procedure :: compute_adotoa => eftcambhoravacomputeadotoa
73 procedure :: compute_h_derivs => eftcambhoravacomputehubbleder
74 procedure :: compute_pi_factors => eftcambhoravacomputepifactors
76 procedure :: additional_model_stability => eftcambhoravaadditionalmodelstability
78 end type eftcamb_horava
86 subroutine eftcambhoravareadmodelselectionfromfile( self, Ini )
90 class(eftcamb_horava) :: self
94 self%HoravaSolarSystem = ini_read_logical_file( ini,
'HoravaSolarSystem', .false. )
96 end subroutine eftcambhoravareadmodelselectionfromfile
100 subroutine eftcambhoravaallocatemodelselection( self )
104 class(eftcamb_horava) :: self
106 end subroutine eftcambhoravaallocatemodelselection
110 subroutine eftcambhoravainitmodelparameters( self, array )
114 class(eftcamb_horava) :: self
115 real(dl),
dimension(self%parameter_number),
intent(in) :: array
117 real(dl),
allocatable,
dimension(:) :: temp
118 integer :: num_params_function, num_params_temp, i
120 if ( self%HoravaSolarSystem )
then 121 self%Horava_eta = array(1)
122 self%Horava_lambda = array(2)
123 self%Horava_xi = 0.5_dl*self%Horava_eta
125 self%Horava_eta = array(1)
126 self%Horava_lambda = array(2)
127 self%Horava_xi = array(3)
130 end subroutine eftcambhoravainitmodelparameters
134 subroutine eftcambhoravainitmodelparametersfromfile( self, Ini )
138 class(eftcamb_horava) :: self
139 type(tinifile) :: ini
141 self%Horava_eta = ini_read_double_file( ini,
'Horava_eta' , 0._dl )
142 self%Horava_lambda = ini_read_double_file( ini,
'Horava_lambda', 0._dl )
143 if ( self%HoravaSolarSystem )
then 144 self%Horava_xi = 0.5_dl*self%Horava_eta
146 self%Horava_xi = ini_read_double_file( ini,
'Horava_xi' , 0._dl )
149 end subroutine eftcambhoravainitmodelparametersfromfile
153 subroutine eftcambhoravacomputeparametersnumber( self )
157 class(eftcamb_horava) :: self
159 if ( self%HoravaSolarSystem )
then 160 self%parameter_number = 2
162 self%parameter_number = 3
165 end subroutine eftcambhoravacomputeparametersnumber
169 subroutine eftcambhoravafeedback( self, print_params )
173 class(eftcamb_horava) :: self
174 logical,
optional :: print_params
177 logical :: print_params_temp
181 write(*,
'(a,a)')
' Model = ', self%name
182 write(*,
'(a,I3)')
' Number of params =' , self%parameter_number
184 if ( self%HoravaSolarSystem )
then 185 write(*,
'(a)')
' Horava with solar system constraints' 189 if (
present(print_params) )
then 190 print_params_temp = print_params
192 print_params_temp = .true.
195 if ( print_params_temp )
then 197 write(*,
'(a23,a,F12.6)')
' Horava_eta ',
'=', self%Horava_eta
198 write(*,
'(a23,a,F12.6)')
' Horava_lambda ',
'=', self%Horava_lambda
199 if ( .not. self%HoravaSolarSystem )
then 200 write(*,
'(a23,a,F12.6)')
' Horava_xi ',
'=', self%Horava_xi
204 end subroutine eftcambhoravafeedback
208 subroutine eftcambhoravaparameternames( self, i, name )
212 class(eftcamb_horava) :: self
213 integer ,
intent(in) :: i
214 character(*),
intent(out) :: name
217 if ( i>self%parameter_number )
then 218 write(*,*)
'Illegal index for parameter_names.' 219 write(*,*)
'Maximum value is:', self%parameter_number
220 call mpistop(
'EFTCAMB error')
228 name =
'Horava_lambda' 231 if ( i==3 .and. self%HoravaSolarSystem )
then 236 end subroutine eftcambhoravaparameternames
240 subroutine eftcambhoravaparameternameslatex( self, i, latexname )
244 class(eftcamb_horava) :: self
245 integer ,
intent(in) :: i
246 character(*),
intent(out) :: latexname
249 if ( i>self%parameter_number )
then 250 write(*,*)
'Illegal index for parameter_names_latex.' 251 write(*,*)
'Maximum value is:', self%parameter_number
252 call mpistop(
'EFTCAMB error')
256 latexname =
'\eta_{\rm Ho\v rava}' 260 latexname =
'\lambda_{\rm Ho\v rava}' 263 if ( i==3 .and. self%HoravaSolarSystem )
then 264 latexname =
'\xi_{\rm Ho\v rava}' 268 end subroutine eftcambhoravaparameternameslatex
272 subroutine eftcambhoravaparametervalues( self, i, value )
276 class(eftcamb_horava) :: self
277 integer ,
intent(in) :: i
278 real(dl),
intent(out) ::
value 281 if ( i>self%parameter_number )
then 282 write(*,*)
'Illegal index for parameter_value.' 283 write(*,*)
'Maximum value is:', self%parameter_number
284 call mpistop(
'EFTCAMB error')
288 value = self%Horava_eta
292 value = self%Horava_lambda
295 if ( i==3 .and. self%HoravaSolarSystem )
then 296 value = self%Horava_xi
300 end subroutine eftcambhoravaparametervalues
304 subroutine eftcambhoravabackgroundeftfunctions( self, a, eft_par_cache, eft_cache )
308 class(eftcamb_horava) :: self
309 real(dl),
intent(in) :: a
310 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
311 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
314 eft_cache%EFTOmegaV = self%Horava_eta/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
315 eft_cache%EFTOmegaP = 0._dl
316 eft_cache%EFTOmegaPP = 0._dl
317 eft_cache%EFTOmegaPPP = 0._dl
318 eft_cache%EFTc = -( 2._dl*self%Horava_xi -3._dl*self%Horava_lambda )*( eft_cache%Hdot -eft_cache%adotoa**2 )/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
319 eft_cache%EFTLambda = -eft_cache%grhov_t + 2._dl*( 3._dl*self%Horava_lambda - 2._dl*self%Horava_xi)*&
320 &( 0.5_dl*eft_cache%adotoa**2 + eft_cache%Hdot)/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
321 eft_cache%EFTcdot = ( 3._dl*self%Horava_lambda - 2._dl*self%Horava_xi )*&
322 &( eft_cache%Hdotdot -4._dl*eft_cache%adotoa*eft_cache%Hdot + 2._dl*eft_cache%adotoa**3 )/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
323 eft_cache%EFTLambdadot = +2._dl*( 3._dl*self%Horava_lambda -2._dl*self%Horava_xi)*&
324 &( eft_cache%Hdotdot -eft_cache%adotoa*eft_cache%Hdot -eft_cache%adotoa**3 )/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
326 end subroutine eftcambhoravabackgroundeftfunctions
330 subroutine eftcambhoravasecondordereftfunctions( self, a, eft_par_cache, eft_cache )
334 class(eftcamb_horava) :: self
335 real(dl),
intent(in) :: a
336 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
337 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
340 eft_cache%EFTGamma1V = 0._dl
341 eft_cache%EFTGamma1P = 0._dl
342 eft_cache%EFTGamma2V = 0._dl
343 eft_cache%EFTGamma2P = 0._dl
344 eft_cache%EFTGamma3V = 2._dl*(self%Horava_lambda -self%Horava_xi)/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
345 eft_cache%EFTGamma3P = 0._dl
346 eft_cache%EFTGamma4V = 2._dl*self%Horava_xi/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
347 eft_cache%EFTGamma4P = 0._dl
348 eft_cache%EFTGamma4PP = 0._dl
349 eft_cache%EFTGamma5V = 0._dl
350 eft_cache%EFTGamma5P = 0._dl
351 eft_cache%EFTGamma6V = self%Horava_eta/4._dl/( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )
352 eft_cache%EFTGamma6P = 0._dl
354 end subroutine eftcambhoravasecondordereftfunctions
359 function eftcambhoravacomputedtauda( self, a, eft_par_cache, eft_cache )
363 class(eftcamb_horava) :: self
364 real(dl),
intent(in) :: a
365 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
366 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
368 real(dl) :: eftcambhoravacomputedtauda
372 temp = eft_cache%grhoa2 +a**4*( eft_par_cache%grhov &
373 & +3._dl*eft_par_cache%h0_Mpc**2*( (self%Horava_eta +3._dl*self%Horava_lambda-2._dl*self%Horava_xi)/(2._dl*self%Horava_xi+2._dl-self%Horava_eta)))
374 eftcambhoravacomputedtauda = sqrt(3/temp)/sqrt(( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )/(3._dl*self%Horava_lambda +2._dl))
376 end function eftcambhoravacomputedtauda
380 subroutine eftcambhoravacomputeadotoa( self, a, eft_par_cache, eft_cache )
384 class(eftcamb_horava) :: self
385 real(dl),
intent(in) :: a
386 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
387 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
389 eft_cache%grhov_t = ( eft_par_cache%grhov &
390 & +3._dl*eft_par_cache%h0_Mpc**2*((self%Horava_eta +3._dl*self%Horava_lambda -2._dl*self%Horava_xi)/(2._dl*self%Horava_xi +2._dl -self%Horava_eta)))*a**2
391 eft_cache%adotoa = sqrt( ( eft_cache%grhom_t +eft_cache%grhov_t )/3._dl )
392 eft_cache%adotoa = eft_cache%adotoa*sqrt(( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )/(3._dl*self%Horava_lambda +2._dl))
394 end subroutine eftcambhoravacomputeadotoa
398 subroutine eftcambhoravacomputehubbleder( self, a, eft_par_cache, eft_cache )
402 class(eftcamb_horava) :: self
403 real(dl),
intent(in) :: a
404 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
405 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
407 eft_cache%gpiv_t = -eft_cache%grhov_t
408 eft_cache%Hdot = -0.5_dl*( eft_cache%adotoa**2 +eft_cache%gpresm_t +eft_cache%gpiv_t )
409 eft_cache%Hdotdot = eft_cache%adotoa*( ( eft_cache%grhob_t +eft_cache%grhoc_t)/6._dl +2._dl*( eft_cache%grhor_t +eft_cache%grhog_t)/3._dl ) &
410 & +2._dl*eft_cache%adotoa*eft_cache%grhov_t/3._dl &
411 & +eft_cache%adotoa*eft_cache%grhonu_tot/6._dl -0.5_dl*eft_cache%adotoa*eft_cache%gpinu_tot -0.5_dl*eft_cache%gpinudot_tot
413 eft_cache%Hdot = eft_cache%Hdot*sqrt(( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )/(3._dl*self%Horava_lambda +2._dl))
414 eft_cache%Hdotdot = eft_cache%Hdotdot*sqrt(( 2._dl +2._dl*self%Horava_xi -self%Horava_eta )/(3._dl*self%Horava_lambda +2._dl))
416 end subroutine eftcambhoravacomputehubbleder
420 subroutine eftcambhoravacomputepifactors( self, a, eft_par_cache, eft_cache )
424 class(eftcamb_horava) :: self
425 real(dl),
intent(in) :: a
426 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
427 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
429 eft_cache%EFTpiA1 = 0._dl
430 eft_cache%EFTpiA2 = 0.5_dl*self%Horava_eta
431 eft_cache%EFTpiB1 = 0._dl
432 eft_cache%EFTpiB2 = eft_cache%adotoa*self%Horava_eta
433 eft_cache%EFTpiC = 0._dl
434 eft_cache%EFTpiD1 = 0.5_dl*( 3._dl*self%Horava_lambda -2._dl*self%Horava_xi)*( eft_cache%adotoa**2 -eft_cache%Hdot ) + 0.5_dl*self%Horava_eta*( eft_cache%adotoa**2 +eft_cache%Hdot )
435 eft_cache%EFTpiD2 = 0.5_dl*self%Horava_lambda*(1._dl+self%Horava_xi)
436 eft_cache%EFTpiE = 0.5_dl*eft_cache%k**2*self%Horava_lambda*( 1._dl +self%Horava_xi )*eft_cache%k*eft_cache%z + 0.5_dl*eft_cache%k*self%Horava_xi*eft_cache%dgq
438 end subroutine eftcambhoravacomputepifactors
442 function eftcambhoravaadditionalmodelstability( self, a, eft_par_cache, eft_cache )
446 class(eftcamb_horava) :: self
447 real(dl),
intent(in) :: a
448 type(eftcamb_parameter_cache),
intent(inout) :: eft_par_cache
449 type(eftcamb_timestep_cache ),
intent(inout) :: eft_cache
451 logical :: eftcambhoravaadditionalmodelstability
453 eftcambhoravaadditionalmodelstability = .true.
455 if ( self%Horava_lambda > -2._dl/3._dl .and. self%Horava_lambda < 0._dl )
then 456 eftcambhoravaadditionalmodelstability = .false.
458 if ( self%Horava_eta < 0._dl .or. self%Horava_eta > 2._dl*self%Horava_xi +2._dl )
then 459 eftcambhoravaadditionalmodelstability = .false.
462 end function eftcambhoravaadditionalmodelstability
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...
This module contains the definition of low energy (LE) Horava gravity. Please refer to the numerical ...
This module contains the abstract definition of all the places where EFTCAMB interacts with CAMB in c...
This module contains the definitions of all the EFTCAMB compile time flags.