EFTCAMB  Reference documentation for version 3.0
08p1_RPH.f90
Go to the documentation of this file.
1 !----------------------------------------------------------------------------------------
2 !
3 ! This file is part of EFTCAMB.
4 !
5 ! Copyright (C) 2013-2016 by the EFTCAMB authors
6 !
7 ! The EFTCAMB code is free software;
8 ! You can use it, redistribute it, and/or modify it under the terms
9 ! of the GNU General Public License as published by the Free Software Foundation;
10 ! either version 3 of the License, or (at your option) any later version.
11 ! The full text of the license can be found in the file eftcamb/LICENSE at
12 ! the top level of the EFTCAMB distribution.
13 !
14 !----------------------------------------------------------------------------------------
15 
20 
21 !----------------------------------------------------------------------------------------
25 
27 
29 
30  use precision
31  use inifile
32  use amlutils
33  use eftcamb_cache
34  use eft_def
46 
47  implicit none
48 
49  private
50 
51  public eftcamb_rph
52 
53  !----------------------------------------------------------------------------------------
55  type, extends ( eftcamb_designer_model ) :: eftcamb_rph
56 
57  ! the RPH functions model selection flags:
58  integer :: rphwde
59  integer :: rphmasspmodel
60  integer :: rphkineticitymodel
61  integer :: rphbraidingmodel
62  integer :: rphtensormodel
63 
64  ! the RPH functions:
65  class( parametrized_function_1d ), allocatable :: rph_wde
66  class( parametrized_function_1d ), allocatable :: rph_planckmass
67  class( parametrized_function_1d ), allocatable :: rph_kineticity
68  class( parametrized_function_1d ), allocatable :: rph_braiding
69  class( parametrized_function_1d ), allocatable :: rph_tensor
70 
71  contains
72 
73  ! initialization of the model:
74  procedure :: read_model_selection => eftcambrphreadmodelselectionfromfile
75  procedure :: allocate_model_selection => eftcambrphallocatemodelselection
76  procedure :: init_model_parameters => eftcambrphinitmodelparameters
77  procedure :: init_model_parameters_from_file => eftcambrphinitmodelparametersfromfile
78  ! utility functions:
79  procedure :: compute_param_number => eftcambrphcomputeparametersnumber
80  procedure :: feedback => eftcambrphfeedback
81  procedure :: parameter_names => eftcambrphparameternames
82  procedure :: parameter_names_latex => eftcambrphparameternameslatex
83  procedure :: parameter_values => eftcambrphparametervalues
84  ! CAMB related procedures:
85  procedure :: compute_background_eft_functions => eftcambrphbackgroundeftfunctions
86  procedure :: compute_secondorder_eft_functions => eftcambrphsecondordereftfunctions
87  procedure :: compute_dtauda => eftcambrphcomputedtauda
88  procedure :: compute_adotoa => eftcambrphcomputeadotoa
89  procedure :: compute_h_derivs => eftcambrphcomputehubbleder
90  ! stability procedures:
91  procedure :: additional_model_stability => eftcambrphadditionalmodelstability
92 
93  end type eftcamb_rph
94 
95  ! ---------------------------------------------------------------------------------------------
96 
97 contains
98 
99  ! ---------------------------------------------------------------------------------------------
101  subroutine eftcambrphreadmodelselectionfromfile( self, Ini )
102 
103  implicit none
104 
105  class(eftcamb_rph) :: self
106  type(tinifile) :: ini
107 
108  ! read model selection flags:
109  self%RPHwDE = ini_read_int_file( ini, 'RPHwDE' , 0 )
110  self%RPHmassPmodel = ini_read_int_file( ini, 'RPHmassPmodel' , 0 )
111  self%RPHkineticitymodel = ini_read_int_file( ini, 'RPHkineticitymodel', 0 )
112  self%RPHbraidingmodel = ini_read_int_file( ini, 'RPHbraidingmodel' , 0 )
113  self%RPHtensormodel = ini_read_int_file( ini, 'RPHtensormodel' , 0 )
114 
115  end subroutine eftcambrphreadmodelselectionfromfile
116 
117  ! ---------------------------------------------------------------------------------------------
119  subroutine eftcambrphallocatemodelselection( self )
120 
121  implicit none
122 
123  class(eftcamb_rph) :: self
124 
125  ! allocate wDE:
126  if ( allocated(self%RPH_wDE) ) deallocate(self%RPH_wDE)
127  select case ( self%RPHwDE )
128  case(0)
129  allocate( wde_lcdm_parametrization_1d::self%RPH_wDE )
130  case(1)
131  allocate( constant_parametrization_1d::self%RPH_wDE )
132  case(2)
133  allocate( cpl_parametrization_1d::self%RPH_wDE )
134  call self%RPH_wDE%set_param_names( ['EFTw0', 'EFTwa'], ['w_0', 'w_a'] )
135  case(3)
136  allocate( jbp_parametrization_1d::self%RPH_wDE )
137  call self%RPH_wDE%set_param_names( ['EFTw0', 'EFTwa', 'EFTwn'], [ 'w_0', 'w_a', 'n ' ] )
138  case(4)
139  allocate( turning_point_parametrization_1d::self%RPH_wDE )
140  call self%RPH_wDE%set_param_names( ['EFTw0 ', 'EFTwa ', 'EFTwat'], ['w_0', 'w_a', 'a_t'] )
141  case(5)
142  allocate( taylor_parametrization_1d::self%RPH_wDE )
143  call self%RPH_wDE%set_param_names( ['EFTw0', 'EFTwa', 'EFTw2', 'EFTw3'], ['w_0', 'w_a', 'w_2', 'w_3'] )
144  case default
145  write(*,'(a,I3)') 'No model corresponding to RPH_wDE =', self%RPHwDE
146  write(*,'(a)') 'Please select an appropriate model.'
147  end select
148  ! allocate RPH_PlanckMass:
149  if ( allocated(self%RPH_PlanckMass) ) deallocate(self%RPH_PlanckMass)
150  select case ( self%RPHmassPmodel )
151  case(0)
152  allocate( zero_parametrization_1d::self%RPH_PlanckMass )
153  case(1)
154  allocate( constant_parametrization_1d::self%RPH_PlanckMass )
155  case(2)
156  allocate( linear_parametrization_1d::self%RPH_PlanckMass )
157  case(3)
158  allocate( power_law_parametrization_1d::self%RPH_PlanckMass )
159  call self%RPH_PlanckMass%set_param_names( ['RPHmassP0 ', 'RPHmassPExp'], ['\tilde{M}_0 ', '\tilde{M}_{\rm exp}^{\rm RPH}'] )
160  case(4)
161  allocate( exponential_parametrization_1d::self%RPH_PlanckMass )
162  call self%RPH_PlanckMass%set_param_names( ['RPHmassP0 ', 'RPHmassPExp'], ['\tilde{M}_0 ', '\tilde{M}_{\rm exp}^{\rm RPH}'] )
163  case default
164  write(*,'(a,I3)') 'No model corresponding to RPH_PlanckMass =', self%RPHmassPmodel
165  write(*,'(a)') 'Please select an appropriate model.'
166  end select
167  ! allocate RPH_Kineticity:
168  if ( allocated(self%RPH_Kineticity) ) deallocate(self%RPH_Kineticity)
169  select case ( self%RPHkineticitymodel )
170  case(0)
171  allocate( zero_parametrization_1d::self%RPH_Kineticity )
172  case(1)
173  allocate( constant_parametrization_1d::self%RPH_Kineticity )
174  case(2)
175  allocate( linear_parametrization_1d::self%RPH_Kineticity )
176  case(3)
177  allocate( power_law_parametrization_1d::self%RPH_Kineticity )
178  call self%RPH_Kineticity%set_param_names( ['RPHkineticity0 ', 'RPHkineticityExp'], ['\alpha_0^{\rm K} ', '\alpha_{\rm exp}^{\rm K}'] )
179  case(4)
180  allocate( exponential_parametrization_1d::self%RPH_Kineticity )
181  call self%RPH_Kineticity%set_param_names( ['RPHkineticity0 ', 'RPHkineticityExp'], ['\alpha_0^{\rm K} ', '\alpha_{\rm exp}^{\rm K}'] )
182  case default
183  write(*,'(a,I3)') 'No model corresponding to RPH_Kineticity =', self%RPHkineticitymodel
184  write(*,'(a)') 'Please select an appropriate model.'
185  end select
186  ! allocate RPH_Braiding:
187  if ( allocated(self%RPH_Braiding) ) deallocate(self%RPH_Braiding)
188  select case ( self%RPHbraidingmodel )
189  case(0)
190  allocate( zero_parametrization_1d::self%RPH_Braiding )
191  case(1)
192  allocate( constant_parametrization_1d::self%RPH_Braiding )
193  case(2)
194  allocate( linear_parametrization_1d::self%RPH_Braiding )
195  case(3)
196  allocate( power_law_parametrization_1d::self%RPH_Braiding )
197  call self%RPH_Braiding%set_param_names( ['RPHbraiding0 ', 'RPHbraidingExp'], ['\alpha_0^{\rm B} ', '\alpha_{\rm exp}^{\rm B}'] )
198  case(4)
199  allocate( exponential_parametrization_1d::self%RPH_Braiding )
200  call self%RPH_Braiding%set_param_names( ['RPHbraiding0 ', 'RPHbraidingExp'], ['\alpha_0^{\rm B} ', '\alpha_{\rm exp}^{\rm B}'] )
201  case default
202  write(*,'(a,I3)') 'No model corresponding to RPH_Braiding =', self%RPHbraidingmodel
203  write(*,'(a)') 'Please select an appropriate model.'
204  end select
205  ! allocate RPH_Braiding:
206  if ( allocated(self%RPH_Tensor) ) deallocate(self%RPH_Tensor)
207  select case ( self%RPHtensormodel )
208  case(0)
209  allocate( zero_parametrization_1d::self%RPH_Tensor )
210  case(1)
211  allocate( constant_parametrization_1d::self%RPH_Tensor )
212  case(2)
213  allocate( linear_parametrization_1d::self%RPH_Tensor )
214  case(3)
215  allocate( power_law_parametrization_1d::self%RPH_Tensor )
216  call self%RPH_Tensor%set_param_names( ['RPHtensor0 ', 'RPHtensorExp'], ['\alpha_0^{\rm T} ', '\alpha_{\rm exp}^{\rm T}'] )
217  case(4)
218  allocate( exponential_parametrization_1d::self%RPH_Tensor )
219  call self%RPH_Tensor%set_param_names( ['RPHtensor0 ', 'RPHtensorExp'], ['\alpha_0^{\rm T} ', '\alpha_{\rm exp}^{\rm T}'] )
220  case default
221  write(*,'(a,I3)') 'No model corresponding to RPH_Tensor =', self%RPHtensormodel
222  write(*,'(a)') 'Please select an appropriate model.'
223  end select
224 
225  ! initialize the names:
226  call self%RPH_wDE%set_name ( 'RPHw' , 'w' )
227  call self%RPH_PlanckMass%set_name ( 'RPHmassP' , '\tilde{M}' )
228  call self%RPH_Kineticity%set_name ( 'RPHkineticity', '\alpha^{\rm K}' )
229  call self%RPH_Braiding%set_name ( 'RPHbraiding' , '\alpha^{\rm B}' )
230  call self%RPH_Tensor%set_name ( 'RPHtensor' , '\alpha^{\rm T}' )
231 
232  end subroutine eftcambrphallocatemodelselection
233 
234  ! ---------------------------------------------------------------------------------------------
236  subroutine eftcambrphinitmodelparameters( self, array )
237 
238  implicit none
239 
240  class(eftcamb_rph) :: self
241  real(dl), dimension(self%parameter_number), intent(in) :: array
242 
243  real(dl), allocatable, dimension(:) :: temp
244  integer :: num_params_function, num_params_temp, i
245 
246  num_params_temp = 1
247 
248  ! first elements are w_DE parameters:
249  num_params_function = self%RPH_wDE%parameter_number
250  allocate( temp(num_params_function) )
251  do i = 1, num_params_function
252  temp(i) = array(num_params_temp)
253  num_params_temp = num_params_temp +1
254  end do
255  call self%RPH_wDE%init_parameters(temp)
256  deallocate( temp )
257  ! then RPH_PlanckMass parameters:
258  num_params_function = self%RPH_PlanckMass%parameter_number
259  allocate( temp(num_params_function) )
260  do i = 1, num_params_function
261  temp(i) = array(num_params_temp)
262  num_params_temp = num_params_temp +1
263  end do
264  call self%RPH_PlanckMass%init_parameters(temp)
265  deallocate(temp)
266  ! then RPH_Kineticity parameters:
267  num_params_function = self%RPH_Kineticity%parameter_number
268  allocate( temp(num_params_function) )
269  do i = 1, num_params_function
270  temp(i) = array(num_params_temp)
271  num_params_temp = num_params_temp +1
272  end do
273  call self%RPH_Kineticity%init_parameters(temp)
274  deallocate(temp)
275  ! then RPH_Braiding parameters:
276  num_params_function = self%RPH_Braiding%parameter_number
277  allocate( temp(num_params_function) )
278  do i = 1, num_params_function
279  temp(i) = array(num_params_temp)
280  num_params_temp = num_params_temp +1
281  end do
282  call self%RPH_Braiding%init_parameters(temp)
283  deallocate(temp)
284  ! then RPH_Tensor parameters:
285  num_params_function = self%RPH_Tensor%parameter_number
286  allocate( temp(num_params_function) )
287  do i = 1, num_params_function
288  temp(i) = array(num_params_temp)
289  num_params_temp = num_params_temp +1
290  end do
291  call self%RPH_Tensor%init_parameters(temp)
292  deallocate(temp)
293 
294  ! now check the length of the parameters:
295  if ( num_params_temp-1 /= self%parameter_number ) then
296  write(*,*) 'In EFTCAMBRPHInitModelParameters:'
297  write(*,*) 'Length of num_params_temp and self%parameter_number do not coincide.'
298  write(*,*) 'num_params_temp:', num_params_temp-1
299  write(*,*) 'self%parameter_number:', self%parameter_number
300  call mpistop('EFTCAMB error')
301  end if
302 
303  end subroutine eftcambrphinitmodelparameters
304 
305  ! ---------------------------------------------------------------------------------------------
307  subroutine eftcambrphinitmodelparametersfromfile( self, Ini )
308 
309  implicit none
310 
311  class(eftcamb_rph) :: self
312  type(tinifile) :: ini
313 
314  call self%RPH_wDE%init_from_file( ini )
315  call self%RPH_PlanckMass%init_from_file( ini )
316  call self%RPH_Kineticity%init_from_file( ini )
317  call self%RPH_Braiding%init_from_file( ini )
318  call self%RPH_Tensor%init_from_file( ini )
319 
320  end subroutine eftcambrphinitmodelparametersfromfile
321 
322  ! ---------------------------------------------------------------------------------------------
324  subroutine eftcambrphcomputeparametersnumber( self )
325 
326  implicit none
327 
328  class(eftcamb_rph) :: self
329 
330  self%parameter_number = 0
331  self%parameter_number = self%parameter_number +self%RPH_wDE%parameter_number
332  self%parameter_number = self%parameter_number +self%RPH_PlanckMass%parameter_number
333  self%parameter_number = self%parameter_number +self%RPH_Kineticity%parameter_number
334  self%parameter_number = self%parameter_number +self%RPH_Braiding%parameter_number
335  self%parameter_number = self%parameter_number +self%RPH_Tensor%parameter_number
336 
337  end subroutine eftcambrphcomputeparametersnumber
338 
339  ! ---------------------------------------------------------------------------------------------
341  subroutine eftcambrphfeedback( self, print_params )
342 
343  implicit none
344 
345  class(eftcamb_rph) :: self
346  logical, optional :: print_params
348 
349  ! print general model informations:
350  write(*,*)
351  write(*,'(a,a)') ' Model = ', self%name
352  write(*,'(a,I3)') ' Number of params =' , self%parameter_number
353 
354  ! print model functions informations:
355  write(*,*)
356  if ( self%RPHwDE /= 0 ) write(*,'(a,I3)') ' RPHwDE =', self%RPHwDE
357  if ( self%RPHmassPmodel /= 0 ) write(*,'(a,I3)') ' RPHmassPmodel =', self%RPHmassPmodel
358  if ( self%RPHkineticitymodel /= 0 ) write(*,'(a,I3)') ' RPHkineticitymodel =', self%RPHkineticitymodel
359  if ( self%RPHbraidingmodel /= 0 ) write(*,'(a,I3)') ' RPHbraidingmodel =', self%RPHbraidingmodel
360  if ( self%RPHtensormodel /= 0 ) write(*,'(a,I3)') ' RPHtensormodel =', self%RPHtensormodel
361 
362  write(*,*)
363  ! print functions informations:
364  call self%RPH_wDE%feedback ( print_params )
365  call self%RPH_PlanckMass%feedback ( print_params )
366  call self%RPH_Kineticity%feedback ( print_params )
367  call self%RPH_Braiding%feedback ( print_params )
368  call self%RPH_Tensor%feedback ( print_params )
369 
370  end subroutine eftcambrphfeedback
371 
372  ! ---------------------------------------------------------------------------------------------
374  subroutine eftcambrphparameternames( self, i, name )
375 
376  implicit none
377 
378  class(eftcamb_rph) :: self
379  integer , intent(in) :: i
380  character(*), intent(out) :: name
381 
382  integer :: nw, nm, nk, nb, nt
383  integer :: j
384 
385  ! compute the incremental number of parameters:
386  nw = self%RPH_wDE%parameter_number
387  nm = nw + self%RPH_PlanckMass%parameter_number
388  nk = nm + self%RPH_Kineticity%parameter_number
389  nb = nk + self%RPH_Braiding%parameter_number
390  nt = nb + self%RPH_Tensor%parameter_number
391 
392  ! check validity of input:
393  if ( i > self%parameter_number .or. i <= 0 ) then
394  write(*,'(a,I3)') 'No parameter corresponding to: ', i
395  write(*,'(a,I3)') 'Total number of parameters is: ', self%parameter_number
396  call mpistop('EFTCAMB error')
397 
398  ! parameter from wDE function
399  else if ( i <= nw ) then
400  do j = 1, self%RPH_wDE%parameter_number
401  if ( i == j ) call self%RPH_wDE%parameter_names( j, name )
402  end do
403  return
404 
405  ! parameter from RPH_PlanckMass function
406  else if ( i <= nm ) then
407  do j = 1, self%RPH_PlanckMass%parameter_number
408  if ( i-nw == j ) call self%RPH_PlanckMass%parameter_names( j, name )
409  end do
410  return
411 
412  ! parameter from RPH_Kineticity function
413  else if ( i <= nk) then
414  do j = 1, self%RPH_Kineticity%parameter_number
415  if ( i-nm == j ) call self%RPH_Kineticity%parameter_names( j, name )
416  end do
417  return
418 
419  !parameter from RPH_Braiding function
420  else if ( i <= nb ) then
421  do j = 1, self%RPH_Braiding%parameter_number
422  if ( i-nk == j ) call self%RPH_Braiding%parameter_names( j, name )
423  end do
424  return
425 
426  !parameter from RPH_Tensor function
427  else if ( i <= nt ) then
428 
429  do j = 1, self%RPH_Tensor%parameter_number
430  if ( i-nb == j ) call self%RPH_Tensor%parameter_names( j, name )
431  end do
432  return
433 
434  end if
435 
436  end subroutine eftcambrphparameternames
437 
438  ! ---------------------------------------------------------------------------------------------
440  subroutine eftcambrphparameternameslatex( self, i, latexname )
441 
442  implicit none
443 
444  class(eftcamb_rph) :: self
445  integer , intent(in) :: i
446  character(*), intent(out) :: latexname
447 
448  integer :: nw, nm, nk, nb, nt
449  integer :: j
450 
451  ! compute the incremental number of parameters:
452  nw = self%RPH_wDE%parameter_number
453  nm = nw + self%RPH_PlanckMass%parameter_number
454  nk = nm + self%RPH_Kineticity%parameter_number
455  nb = nk + self%RPH_Braiding%parameter_number
456  nt = nb + self%RPH_Tensor%parameter_number
457 
458  ! check validity of input:
459  if ( i > self%parameter_number .or. i <= 0 ) then
460  write(*,'(a,I3)') 'No parameter corresponding to: ', i
461  write(*,'(a,I3)') 'Total number of parameters is: ', self%parameter_number
462  call mpistop('EFTCAMB error')
463 
464  ! parameter from wDE function
465  else if ( i <= nw ) then
466  do j = 1, self%RPH_wDE%parameter_number
467  if ( i == j ) call self%RPH_wDE%parameter_names_latex( j, latexname )
468  end do
469  return
470 
471  ! parameter from RPH_PlanckMass function
472  else if ( i <= nm ) then
473  do j = 1, self%RPH_PlanckMass%parameter_number
474  if ( i-nw == j ) call self%RPH_PlanckMass%parameter_names_latex( j, latexname )
475  end do
476  return
477 
478  ! parameter from RPH_Kineticity function
479  else if ( i <= nk) then
480  do j = 1, self%RPH_Kineticity%parameter_number
481  if ( i-nm == j ) call self%RPH_Kineticity%parameter_names_latex( j, latexname )
482  end do
483  return
484 
485  !parameter from RPH_Braiding function
486  else if ( i <= nb ) then
487  do j = 1, self%RPH_Braiding%parameter_number
488  if ( i-nk == j ) call self%RPH_Braiding%parameter_names_latex( j, latexname )
489  end do
490  return
491 
492  !parameter from RPH_Tensor function
493  else if ( i <= nt ) then
494 
495  do j = 1, self%RPH_Tensor%parameter_number
496  if ( i-nb == j ) call self%RPH_Tensor%parameter_names_latex( j, latexname )
497  end do
498  return
499 
500  end if
501 
502  end subroutine eftcambrphparameternameslatex
503 
504  ! ---------------------------------------------------------------------------------------------
506  subroutine eftcambrphparametervalues( self, i, value )
507 
508  implicit none
509 
510  class(eftcamb_rph) :: self
511  integer , intent(in) :: i
512  real(dl), intent(out) :: value
513 
514  integer :: nw, nm, nk, nb, nt
515  integer :: j
516 
517  ! compute the incremental number of parameters:
518  nw = self%RPH_wDE%parameter_number
519  nm = nw + self%RPH_PlanckMass%parameter_number
520  nk = nm + self%RPH_Kineticity%parameter_number
521  nb = nk + self%RPH_Braiding%parameter_number
522  nt = nb + self%RPH_Tensor%parameter_number
523 
524  ! check validity of input:
525  if ( i > self%parameter_number .or. i <= 0 ) then
526  write(*,'(a,I3)') 'No parameter corresponding to: ', i
527  write(*,'(a,I3)') 'Total number of parameters is: ', self%parameter_number
528  call mpistop('EFTCAMB error')
529 
530  ! parameter from wDE function
531  else if ( i <= nw ) then
532  do j = 1, self%RPH_wDE%parameter_number
533  if ( i == j ) call self%RPH_wDE%parameter_value( j, value )
534  end do
535  return
536 
537  ! parameter from RPH_PlanckMass function
538  else if ( i <= nm ) then
539  do j = 1, self%RPH_PlanckMass%parameter_number
540  if ( i-nw == j ) call self%RPH_PlanckMass%parameter_value( j, value )
541  end do
542  return
543 
544  ! parameter from RPH_Kineticity function
545  else if ( i <= nk) then
546  do j = 1, self%RPH_Kineticity%parameter_number
547  if ( i-nm == j ) call self%RPH_Kineticity%parameter_value( j, value )
548  end do
549  return
550 
551  !parameter from RPH_Braiding function
552  else if ( i <= nb ) then
553  do j = 1, self%RPH_Braiding%parameter_number
554  if ( i-nk == j ) call self%RPH_Braiding%parameter_value( j, value )
555  end do
556  return
557 
558  !parameter from RPH_Tensor function
559  else if ( i <= nt ) then
560 
561  do j = 1, self%RPH_Tensor%parameter_number
562  if ( i-nb == j ) call self%RPH_Tensor%parameter_value( j, value )
563  end do
564  return
565 
566  end if
567 
568  end subroutine eftcambrphparametervalues
569 
570  ! ---------------------------------------------------------------------------------------------
572  subroutine eftcambrphbackgroundeftfunctions( self, a, eft_par_cache, eft_cache )
573 
574  implicit none
575 
576  class(eftcamb_rph) :: self
577  real(dl), intent(in) :: a
578  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
579  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
580 
581  real(dl) :: rph_pm_v, rph_at_v, rph_pm_p, rph_at_p, rph_pm_pp, rph_at_pp, rph_pm_ppp, rph_at_ppp
582 
583  ! precompute some functions:
584  rph_pm_v = self%RPH_PlanckMass%value(a)
585  rph_at_v = self%RPH_Tensor%value(a)
586  rph_pm_p = self%RPH_PlanckMass%first_derivative(a)
587  rph_at_p = self%RPH_Tensor%first_derivative(a)
588  rph_pm_pp = self%RPH_PlanckMass%second_derivative(a)
589  rph_at_pp = self%RPH_Tensor%second_derivative(a)
590  rph_pm_ppp = self%RPH_PlanckMass%third_derivative(a)
591  rph_at_ppp = self%RPH_Tensor%third_derivative(a)
592  ! compute the EFT functions:
593  eft_cache%EFTOmegaV = rph_pm_v +rph_at_v*(1._dl +rph_pm_v)
594  eft_cache%EFTOmegaP = rph_pm_v*rph_at_p +(1._dl +rph_at_v)*rph_pm_p
595  eft_cache%EFTOmegaPP = rph_pm_v*rph_at_pp +2._dl*rph_pm_p*rph_at_p +(1._dl +rph_at_v)*rph_pm_pp
596  eft_cache%EFTOmegaPPP = rph_pm_v*rph_at_ppp +3._dl*rph_pm_pp*rph_at_p +3._dl*rph_pm_p*rph_at_pp &
597  & +(1._dl +rph_at_v)*rph_pm_ppp
598  eft_cache%EFTc = ( eft_cache%adotoa**2 - eft_cache%Hdot )*( eft_cache%EFTOmegaV + 0.5_dl*a*eft_cache%EFTOmegaP ) &
599  & -0.5_dl*( a*eft_cache%adotoa )**2*eft_cache%EFTOmegaPP&
600  & +0.5_dl*eft_cache%grhov_t*( 1._dl+ self%RPH_wDE%value(a) )
601  eft_cache%EFTLambda = -eft_cache%EFTOmegaV*( 2._dl*eft_cache%Hdot +eft_cache%adotoa**2 ) &
602  & -a*eft_cache%EFTOmegaP*( 2._dl*eft_cache%adotoa**2 + eft_cache%Hdot ) &
603  & -( a*eft_cache%adotoa )**2*eft_cache%EFTOmegaPP &
604  & +self%RPH_wDE%value(a)*eft_cache%grhov_t
605  eft_cache%EFTcdot = +0.5_dl*eft_cache%adotoa*eft_cache%grhov_t*( -3._dl*(1._dl +self%RPH_wDE%value(a))**2 + a*self%RPH_wDE%first_derivative(a) ) &
606  & -eft_cache%EFTOmegaV*( eft_cache%Hdotdot -4._dl*eft_cache%adotoa*eft_cache%Hdot +2._dl*eft_cache%adotoa**3 ) &
607  & +0.5_dl*a*eft_cache%EFTOmegaP*( -eft_cache%Hdotdot +eft_cache%adotoa*eft_cache%Hdot +eft_cache%adotoa**3) &
608  & +0.5_dl*a**2*eft_cache%adotoa*eft_cache%EFTOmegaPP*( eft_cache%adotoa**2 -3._dl*eft_cache%Hdot ) &
609  & -0.5_dl*(a*eft_cache%adotoa)**3*eft_cache%EFTOmegaPPP
610  eft_cache%EFTLambdadot = -2._dl*eft_cache%EFTOmegaV*( eft_cache%Hdotdot -eft_cache%adotoa*eft_cache%Hdot -eft_cache%adotoa**3 ) &
611  & -a*eft_cache%EFTOmegaP*( +eft_cache%Hdotdot +5._dl*eft_cache%adotoa*eft_cache%Hdot -eft_cache%adotoa**3 ) &
612  & -a**2*eft_cache%EFTOmegaPP*eft_cache%adotoa*( +2._dl*eft_cache%adotoa**2 +3._dl*eft_cache%Hdot )&
613  & -(a*eft_cache%adotoa)**3*eft_cache%EFTOmegaPPP &
614  & +eft_cache%grhov_t*eft_cache%adotoa*( a*self%RPH_wDE%first_derivative(a) -3._dl*self%RPH_wDE%value(a)*(1._dl +self%RPH_wDE%value(a) ))
615 
616  end subroutine eftcambrphbackgroundeftfunctions
617 
618  ! ---------------------------------------------------------------------------------------------
620  subroutine eftcambrphsecondordereftfunctions( self, a, eft_par_cache, eft_cache )
621 
622  implicit none
623 
624  class(eftcamb_rph) :: self
625  real(dl), intent(in) :: a
626  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
627  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
628 
629  real(dl) :: rph_pm_v, rph_at_v, rph_ak_v, rph_ab_v, rph_pm_p, rph_at_p, rph_ak_p, rph_ab_p
630  real(dl) :: rph_pm_pp, rph_at_pp
631 
632  ! precompute some functions:
633  rph_pm_v = self%RPH_PlanckMass%value(a)
634  rph_at_v = self%RPH_Tensor%value(a)
635  rph_ak_v = self%RPH_Kineticity%value(a)
636  rph_ab_v = self%RPH_Braiding%value(a)
637  rph_pm_p = self%RPH_PlanckMass%first_derivative(a)
638  rph_at_p = self%RPH_Tensor%first_derivative(a)
639  rph_ak_p = self%RPH_Kineticity%first_derivative(a)
640  rph_ab_p = self%RPH_Braiding%first_derivative(a)
641  rph_pm_pp = self%RPH_PlanckMass%second_derivative(a)
642  rph_at_pp = self%RPH_Tensor%second_derivative(a)
643  ! compute the EFT functions:
644  eft_cache%EFTGamma1V = 0.25_dl*( rph_ak_v*(1._dl +rph_pm_v)*eft_cache%adotoa**2 &
645  & -2._dl*eft_cache%EFTc )/(eft_par_cache%h0_Mpc**2*a**2)
646  eft_cache%EFTGamma1P = - 0.5_dl*( rph_ak_v*(1._dl +rph_pm_v)*eft_cache%adotoa**2 &
647  & -2._dl*eft_cache%EFTc )/(eft_par_cache%h0_Mpc**2*a**3) &
648  & +0.25_dl*( rph_ak_p*(1._dl +rph_pm_v)*eft_cache%adotoa**2 &
649  & +rph_ak_v*rph_pm_p*eft_cache%adotoa**2 &
650  & +2._dl*rph_ak_v*(1._dl +rph_pm_v)*eft_cache%Hdot/a &
651  & -4._dl*eft_cache%EFTc -2._dl*eft_cache%EFTcdot/a/eft_cache%adotoa )/(eft_par_cache%h0_Mpc**2*a**2)
652  eft_cache%EFTGamma2V = ( +2._dl*rph_ab_v*(1._dl +rph_pm_v) &
653  & -a*eft_cache%EFTOmegaP )*eft_cache%adotoa/(eft_par_cache%h0_Mpc*a)
654  eft_cache%EFTGamma2P = -0.5_dl*( +2._dl*rph_ab_v*(1._dl +rph_pm_v) &
655  & -a*eft_cache%EFTOmegaP )*eft_cache%adotoa/(eft_par_cache%h0_Mpc*a) &
656  & -( -2._dl*(1._dl +rph_pm_v)*( rph_ab_p*eft_cache%adotoa**2 &
657  & + rph_ab_v*eft_cache%Hdot/a) &
658  & - 2._dl*rph_ab_v*eft_cache%adotoa**2*rph_pm_p &
659  & + eft_cache%EFTOmegaP*( eft_cache%adotoa**2 +eft_cache%Hdot ) &
660  & + a*eft_cache%adotoa**2*eft_cache%EFTOmegaPP )/(eft_par_cache%h0_Mpc*a*eft_cache%adotoa)
661  eft_cache%EFTGamma3V = -rph_at_v*(1._dl +rph_pm_v)
662  eft_cache%EFTGamma3P = -rph_pm_p*rph_at_v -(1._dl +rph_pm_v)*rph_at_p
663  eft_cache%EFTGamma4V = -eft_cache%EFTGamma3V
664  eft_cache%EFTGamma4P = -eft_cache%EFTGamma3P
665  eft_cache%EFTGamma4PP = +(1._dl +rph_pm_v)*rph_at_pp +rph_pm_pp*rph_at_v &
666  & +2._dl*rph_pm_p*rph_at_p
667  eft_cache%EFTGamma5V = +0.5_dl*eft_cache%EFTGamma3V
668  eft_cache%EFTGamma5P = +0.5_dl*eft_cache%EFTGamma3P
669  eft_cache%EFTGamma6V = 0._dl
670  eft_cache%EFTGamma6P = 0._dl
671 
672  end subroutine eftcambrphsecondordereftfunctions
673 
674  ! ---------------------------------------------------------------------------------------------
677  function eftcambrphcomputedtauda( self, a, eft_par_cache, eft_cache )
678 
679  implicit none
680 
681  class(eftcamb_rph) :: self
682  real(dl), intent(in) :: a
683  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
684  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
685 
686  real(dl) :: eftcambrphcomputedtauda
687 
688  real(dl) :: temp
689 
690  temp = eft_cache%grhoa2 +eft_par_cache%grhov*a*a*self%RPH_wDE%integral(a)
691  eftcambrphcomputedtauda = sqrt(3/temp)
692 
693  end function eftcambrphcomputedtauda
694 
695  ! ---------------------------------------------------------------------------------------------
697  subroutine eftcambrphcomputeadotoa( self, a, eft_par_cache, eft_cache )
698 
699  implicit none
700 
701  class(eftcamb_rph) :: self
702  real(dl), intent(in) :: a
703  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
704  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
705 
706  eft_cache%grhov_t = eft_par_cache%grhov*self%RPH_wDE%integral(a)
707  eft_cache%adotoa = sqrt( ( eft_cache%grhom_t +eft_cache%grhov_t )/3._dl )
708 
709  end subroutine eftcambrphcomputeadotoa
710 
711  ! ---------------------------------------------------------------------------------------------
713  subroutine eftcambrphcomputehubbleder( self, a, eft_par_cache, eft_cache )
714 
715  implicit none
716 
717  class(eftcamb_rph) :: self
718  real(dl), intent(in) :: a
719  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
720  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
721 
722  eft_cache%gpiv_t = self%RPH_wDE%value(a)*eft_cache%grhov_t
723  eft_cache%Hdot = -0.5_dl*( eft_cache%adotoa**2 +eft_cache%gpresm_t +eft_cache%gpiv_t )
724  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 ) &
725  & +eft_cache%adotoa*eft_cache%grhov_t*( 1._dl/6._dl +self%RPH_wDE%value(a) +1.5_dl*self%RPH_wDE%value(a)**2 -0.5_dl*a*self%RPH_wDE%first_derivative(a) ) &
726  & +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
727 
728  end subroutine eftcambrphcomputehubbleder
729 
730  ! ---------------------------------------------------------------------------------------------
732  function eftcambrphadditionalmodelstability( self, a, eft_par_cache, eft_cache )
733 
734  implicit none
735 
736  class(eftcamb_rph) :: self
737  real(dl), intent(in) :: a
738  type(eftcamb_parameter_cache), intent(inout) :: eft_par_cache
739  type(eftcamb_timestep_cache ), intent(inout) :: eft_cache
740 
741  logical :: eftcambrphadditionalmodelstability
742 
743  eftcambrphadditionalmodelstability = .true.
744  if ( self%RPH_wDE%value(a) > -1._dl/3._dl ) eftcambrphadditionalmodelstability = .false.
745 
746  end function eftcambrphadditionalmodelstability
747 
748  ! ---------------------------------------------------------------------------------------------
749 
This module contains the definition of the constant parametrization, inheriting from parametrized_fun...
This module contains the definition of the Taylor expansion parametrization, around a=0...
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...
This module contains the definition of the linear parametrization, inheriting from parametrized_funct...
This module contains the definition of the turning point parametrization, inheriting from parametrize...
This module contains the abstract definition of all the places where EFTCAMB interacts with CAMB in c...
This module contains the definition of the CPL parametrization, inheriting from parametrized_function...
This module contains the definition of the power law parametrization, inheriting from parametrized_fu...
This module contains the definition of neutral parametrizations that can be used when parametrized fu...
This module contains the definitions of all the EFTCAMB compile time flags.
Definition: 01_EFT_def.f90:25
This module contains the definition of the generalized Jassal-Bagla-Padmanabhan (JBP) parametrization...
This module contains the definition of the exponential parametrization, inheriting from parametrized_...
This module contains the definition of an EFT reparametrization of Horndeski models. This is described by four functions of time and w_DE. Please refer to the numerical notes for details.
Definition: 08p1_RPH.f90:28
This module contains the abstract class for generic parametrizations for 1D functions that are used b...