EFTCAMB  Reference documentation for version 3.0
03_abstract_EFTCAMB_cache.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 
21 
22 
23 !----------------------------------------------------------------------------------------
28 
30 
32 
33  use precision
34  use inifile
35  use amlutils
36 
37  implicit none
38 
39  private
40 
41  public eftcamb_parameter_cache, eftcamb_timestep_cache
42 
43  ! some settings:
44  character(*), parameter :: cache_output_format = 'e18.10'
45 
46  !----------------------------------------------------------------------------------------
51  type :: eftcamb_parameter_cache
52 
53  ! 1) relative densities:
54  real(dl) :: omegac
55  real(dl) :: omegab
56  real(dl) :: omegav
57  real(dl) :: omegak
58  real(dl) :: omegan
59  real(dl) :: omegag
60  real(dl) :: omegar
61  ! 2) Hubble constant:
62  real(dl) :: h0
63  real(dl) :: h0_mpc
64  ! 3) densities:
65  real(dl) :: grhog
66  real(dl) :: grhornomass
67  real(dl) :: grhoc
68  real(dl) :: grhob
69  real(dl) :: grhov
70  real(dl) :: grhok
71  ! 4) massive neutrinos:
72  integer :: num_nu_massive
73  integer :: nu_mass_eigenstates
74  real(dl), allocatable, dimension(:) :: grhormass
75  real(dl), allocatable, dimension(:) :: nu_masses
76  ! 5) massive neutrinos wrapper:
77  procedure( nu_background_wrapper ), pointer, nopass :: nu_background => null()
78  procedure( nu_rho_wrapper ), pointer, nopass :: nu_rho => null()
79  procedure( nu_drho_wrapper ), pointer, nopass :: nu_drho => null()
80  procedure( nu_pidot_wrapper ), pointer, nopass :: nu_pidot => null()
81  procedure( nu_pidotdot_wrapper ), pointer, nopass :: nu_pidotdot => null()
82 
83  contains
84 
85  procedure :: initialize => eftcambparametercacheinit
86  procedure :: is_nan => eftcambparametercacheisnan
87  procedure :: print => eftcambparametercacheprint
88 
89  end type eftcamb_parameter_cache
90 
91  !----------------------------------------------------------------------------------------
92  ! Interface containing the wrapper to massive neutrinos stuff.
93  interface
94  !----------------------------------------------------------------------------------------
97  subroutine nu_background_wrapper( am, rhonu, pnu )
98  use precision
99  implicit none
100  real(dl), intent(in) :: am
101  real(dl), intent(out) :: rhonu
102  real(dl), intent(out) :: pnu
103  end subroutine nu_background_wrapper
104  !----------------------------------------------------------------------------------------
106  subroutine nu_rho_wrapper( am, rhonu )
107  use precision
108  implicit none
109  real(dl), intent(in) :: am
110  real(dl), intent(out) :: rhonu
111  end subroutine nu_rho_wrapper
112  !----------------------------------------------------------------------------------------
115  function nu_drho_wrapper( am, adotoa, rhonu )
116  use precision
117  implicit none
118  real(dl), intent(in) :: am
119  real(dl) :: adotoa
120  real(dl) :: rhonu
121  real(dl) :: nu_drho_wrapper
122  end function nu_drho_wrapper
123  !----------------------------------------------------------------------------------------
126  function nu_pidot_wrapper( am, adotoa, presnu )
127  use precision
128  implicit none
129  real(dl), intent(in) :: am
130  real(dl) :: adotoa
131  real(dl) :: presnu
132  real(dl) :: nu_pidot_wrapper
133  end function nu_pidot_wrapper
134  !----------------------------------------------------------------------------------------
137  function nu_pidotdot_wrapper( am, adotoa, Hdot, presnu, presnudot )
138  use precision
139  implicit none
140  real(dl), intent(in) :: am
141  real(dl) :: adotoa
142  real(dl) :: hdot
143  real(dl) :: presnu
144  real(dl) :: presnudot
145  real(dl) :: nu_pidotdot_wrapper
146  end function nu_pidotdot_wrapper
147  !----------------------------------------------------------------------------------------
148  end interface
149 
150 
151  !----------------------------------------------------------------------------------------
153  type :: eftcamb_timestep_cache
154 
155  ! 1) time and k:
156  real(dl) :: a
157  real(dl) :: tau
158  real(dl) :: k
159  ! 2) total matter densities:
160  real(dl) :: grhoa2
161  real(dl) :: grhom_t
162  real(dl) :: gpresm_t
163  real(dl) :: gpresdotm_t
164  ! 3) densities and pressure of the various species:
165  real(dl) :: grhob_t
166  real(dl) :: grhoc_t
167  real(dl) :: grhor_t
168  real(dl) :: grhog_t
169  real(dl) :: grhov_t
170  real(dl) :: gpiv_t
171  real(dl) :: grhonu_tot
172  real(dl) :: gpinu_tot
173  real(dl) :: grhonudot_tot
174  real(dl) :: gpinudot_tot
175  ! 4) expansion history:
176  real(dl) :: adotoa
177  real(dl) :: hdot
178  real(dl) :: hdotdot
179  ! 5) EFT functions:
180  real(dl) :: eftomegav
181  real(dl) :: eftomegap
182  real(dl) :: eftomegapp
183  real(dl) :: eftomegappp
184  real(dl) :: eftc
185  real(dl) :: eftcdot
186  real(dl) :: eftlambda
187  real(dl) :: eftlambdadot
188  real(dl) :: eftgamma1v
189  real(dl) :: eftgamma1p
190  real(dl) :: eftgamma2v
191  real(dl) :: eftgamma2p
192  real(dl) :: eftgamma3v
193  real(dl) :: eftgamma3p
194  real(dl) :: eftgamma4v
195  real(dl) :: eftgamma4p
196  real(dl) :: eftgamma4pp
197  real(dl) :: eftgamma5v
198  real(dl) :: eftgamma5p
199  real(dl) :: eftgamma6v
200  real(dl) :: eftgamma6p
201  ! 6) other background quantities:
202  real(dl) :: grhoq
203  real(dl) :: gpresq
204  real(dl) :: grhodotq
205  real(dl) :: gpresdotq
206  ! 7) the Einstein equations coefficients:
207  real(dl) :: efteomf
208  real(dl) :: efteomn
209  real(dl) :: efteomndot
210  real(dl) :: efteomx
211  real(dl) :: efteomxdot
212  real(dl) :: efteomy
213  real(dl) :: efteomg
214  real(dl) :: efteomu
215  real(dl) :: efteoml
216  real(dl) :: efteomm
217  real(dl) :: efteomv
218  real(dl) :: efteomvdot
219  ! 8) pi field factors:
220  real(dl) :: eftpia1
221  real(dl) :: eftpia2
222  real(dl) :: eftpib1
223  real(dl) :: eftpib2
224  real(dl) :: eftpic
225  real(dl) :: eftpid1
226  real(dl) :: eftpid2
227  real(dl) :: eftpie
228  ! 9) pi field quantities:
229  real(dl) :: pi
230  real(dl) :: pidot
231  real(dl) :: pidotdot
232  ! 10) scalar perturbations quantities:
233  real(dl) :: z
234  real(dl) :: dz
235  real(dl) :: sigma
236  real(dl) :: sigmadot
237  real(dl) :: clxg
238  real(dl) :: clxr
239  real(dl) :: dgpnu
240  real(dl) :: dgrho
241  real(dl) :: dgq
242  ! 11) tensor perturbations quantities:
243  real(dl) :: eftat
244  real(dl) :: eftbt
245  real(dl) :: eftdt
246  ! 12) Kinetic and Gradient quantities for the stability check:
247  real(dl) :: eft_kinetic
248  real(dl) :: eft_gradient
249 
250  contains
251 
252  procedure :: initialize => eftcambtimestepcacheinit
253  procedure :: is_nan => eftcambtimestepcacheisnan
254  procedure :: open_cache_files => eftcambtimestepcacheopenfile
255  procedure :: dump_cache_files => eftcambtimestepcachedumpfile
256  procedure :: close_cache_files => eftcambtimestepcacheclosefile
257 
258  end type eftcamb_timestep_cache
259 
260 contains
261 
262  ! ---------------------------------------------------------------------------------------------
264  subroutine eftcambtimestepcacheinit( self )
265 
266  implicit none
267 
268  class(eftcamb_timestep_cache) :: self
269 
270  ! initialize all class members to zero:
271  ! 1) time and k:
272  self%a = 0._dl
273  self%tau = 0._dl
274  self%k = 0._dl
275  ! 2) expansion history:
276  self%adotoa = 0._dl
277  self%Hdot = 0._dl
278  self%Hdotdot = 0._dl
279  ! 3) total matter densities:
280  self%grhoa2 = 0._dl
281  self%grhom_t = 0._dl
282  self%gpresm_t = 0._dl
283  self%gpresdotm_t = 0._dl
284  ! 4) densities and pressure of the various species:
285  self%grhob_t = 0._dl
286  self%grhoc_t = 0._dl
287  self%grhor_t = 0._dl
288  self%grhog_t = 0._dl
289  self%grhov_t = 0._dl
290  self%gpiv_t = 0._dl
291  self%grhonu_tot = 0._dl
292  self%gpinu_tot = 0._dl
293  self%grhonudot_tot = 0._dl
294  self%gpinudot_tot = 0._dl
295  ! 5) EFT functions:
296  self%EFTOmegaV = 0._dl
297  self%EFTOmegaP = 0._dl
298  self%EFTOmegaPP = 0._dl
299  self%EFTOmegaPPP = 0._dl
300  self%EFTc = 0._dl
301  self%EFTcdot = 0._dl
302  self%EFTLambda = 0._dl
303  self%EFTLambdadot = 0._dl
304  self%EFTGamma1V = 0._dl
305  self%EFTGamma1P = 0._dl
306  self%EFTGamma2V = 0._dl
307  self%EFTGamma2P = 0._dl
308  self%EFTGamma3V = 0._dl
309  self%EFTGamma3P = 0._dl
310  self%EFTGamma4V = 0._dl
311  self%EFTGamma4P = 0._dl
312  self%EFTGamma4PP = 0._dl
313  self%EFTGamma5V = 0._dl
314  self%EFTGamma5P = 0._dl
315  self%EFTGamma6V = 0._dl
316  self%EFTGamma6P = 0._dl
317  ! 6) other background quantities:
318  self%grhoq = 0._dl
319  self%gpresq = 0._dl
320  self%grhodotq = 0._dl
321  self%gpresdotq = 0._dl
322  ! 7) the Einstein equations coefficients:
323  self%EFTeomF = 0._dl
324  self%EFTeomN = 0._dl
325  self%EFTeomNdot = 0._dl
326  self%EFTeomX = 0._dl
327  self%EFTeomXdot = 0._dl
328  self%EFTeomY = 0._dl
329  self%EFTeomG = 0._dl
330  self%EFTeomU = 0._dl
331  self%EFTeomL = 0._dl
332  self%EFTeomM = 0._dl
333  self%EFTeomV = 0._dl
334  self%EFTeomVdot = 0._dl
335  ! 8) pi field factors:
336  self%EFTpiA1 = 0._dl
337  self%EFTpiA2 = 0._dl
338  self%EFTpiB1 = 0._dl
339  self%EFTpiB2 = 0._dl
340  self%EFTpiC = 0._dl
341  self%EFTpiD1 = 0._dl
342  self%EFTpiD2 = 0._dl
343  self%EFTpiE = 0._dl
344  ! 9) pi field quantities:
345  self%pi = 0._dl
346  self%pidot = 0._dl
347  self%pidotdot = 0._dl
348  ! 10) perturbations quantities:
349  self%z = 0._dl
350  self%clxg = 0._dl
351  self%clxr = 0._dl
352  self%dgpnu = 0._dl
353  self%dgrho = 0._dl
354  self%dgq = 0._dl
355  ! 11) tensor perturbations quantities:
356  self%EFTAT = 0._dl
357  self%EFTBT = 0._dl
358  self%EFTDT = 0._dl
359  ! 12) Kinetic and Gradient quantities for the stability check:
360  self%EFT_kinetic = 0._dl
361  self%EFT_gradient = 0._dl
362 
363  end subroutine eftcambtimestepcacheinit
364 
365  ! ---------------------------------------------------------------------------------------------
367  subroutine eftcambtimestepcacheisnan( self, HaveNan )
368 
369  implicit none
370 
371  class(eftcamb_timestep_cache), intent(in) :: self
372  logical, intent(out) :: havenan
374 
375  havenan = .false.
376  havenan = havenan.or.isnan(self%a)
377  havenan = havenan.or.isnan(self%tau)
378  havenan = havenan.or.isnan(self%k)
379  havenan = havenan.or.isnan(self%adotoa)
380  havenan = havenan.or.isnan(self%Hdot)
381  havenan = havenan.or.isnan(self%Hdotdot)
382  havenan = havenan.or.isnan(self%grhoa2)
383  havenan = havenan.or.isnan(self%grhom_t)
384  havenan = havenan.or.isnan(self%gpresm_t)
385  havenan = havenan.or.isnan(self%gpresdotm_t)
386  havenan = havenan.or.isnan(self%grhob_t)
387  havenan = havenan.or.isnan(self%grhoc_t)
388  havenan = havenan.or.isnan(self%grhor_t)
389  havenan = havenan.or.isnan(self%grhog_t)
390  havenan = havenan.or.isnan(self%grhov_t)
391  havenan = havenan.or.isnan(self%gpiv_t)
392  havenan = havenan.or.isnan(self%grhonu_tot)
393  havenan = havenan.or.isnan(self%gpinu_tot)
394  havenan = havenan.or.isnan(self%grhonudot_tot)
395  havenan = havenan.or.isnan(self%gpinudot_tot)
396  havenan = havenan.or.isnan(self%EFTOmegaV)
397  havenan = havenan.or.isnan(self%EFTOmegaP)
398  havenan = havenan.or.isnan(self%EFTOmegaPP)
399  havenan = havenan.or.isnan(self%EFTOmegaPPP)
400  havenan = havenan.or.isnan(self%EFTc)
401  havenan = havenan.or.isnan(self%EFTcdot)
402  havenan = havenan.or.isnan(self%EFTLambda)
403  havenan = havenan.or.isnan(self%EFTLambdadot)
404  havenan = havenan.or.isnan(self%EFTGamma1V)
405  havenan = havenan.or.isnan(self%EFTGamma1P)
406  havenan = havenan.or.isnan(self%EFTGamma2V)
407  havenan = havenan.or.isnan(self%EFTGamma2P)
408  havenan = havenan.or.isnan(self%EFTGamma3V)
409  havenan = havenan.or.isnan(self%EFTGamma3P)
410  havenan = havenan.or.isnan(self%EFTGamma4V)
411  havenan = havenan.or.isnan(self%EFTGamma4P)
412  havenan = havenan.or.isnan(self%EFTGamma4PP)
413  havenan = havenan.or.isnan(self%EFTGamma5V)
414  havenan = havenan.or.isnan(self%EFTGamma5P)
415  havenan = havenan.or.isnan(self%EFTGamma6V)
416  havenan = havenan.or.isnan(self%EFTGamma6P)
417  havenan = havenan.or.isnan(self%grhoq)
418  havenan = havenan.or.isnan(self%gpresq)
419  havenan = havenan.or.isnan(self%grhodotq)
420  havenan = havenan.or.isnan(self%gpresdotq)
421  havenan = havenan.or.isnan(self%EFTeomF)
422  havenan = havenan.or.isnan(self%EFTeomN)
423  havenan = havenan.or.isnan(self%EFTeomNdot)
424  havenan = havenan.or.isnan(self%EFTeomX)
425  havenan = havenan.or.isnan(self%EFTeomXdot)
426  havenan = havenan.or.isnan(self%EFTeomY)
427  havenan = havenan.or.isnan(self%EFTeomG)
428  havenan = havenan.or.isnan(self%EFTeomU)
429  havenan = havenan.or.isnan(self%EFTeomL)
430  havenan = havenan.or.isnan(self%EFTeomM)
431  havenan = havenan.or.isnan(self%EFTeomV)
432  havenan = havenan.or.isnan(self%EFTeomVdot)
433  havenan = havenan.or.isnan(self%EFTpiA1)
434  havenan = havenan.or.isnan(self%EFTpiA2)
435  havenan = havenan.or.isnan(self%EFTpiB1)
436  havenan = havenan.or.isnan(self%EFTpiB2)
437  havenan = havenan.or.isnan(self%EFTpiC)
438  havenan = havenan.or.isnan(self%EFTpiD1)
439  havenan = havenan.or.isnan(self%EFTpiD2)
440  havenan = havenan.or.isnan(self%EFTpiE)
441  havenan = havenan.or.isnan(self%pi)
442  havenan = havenan.or.isnan(self%pidot)
443  havenan = havenan.or.isnan(self%pidotdot)
444  havenan = havenan.or.isnan(self%z)
445  havenan = havenan.or.isnan(self%clxg)
446  havenan = havenan.or.isnan(self%clxr)
447  havenan = havenan.or.isnan(self%dgpnu)
448  havenan = havenan.or.isnan(self%dgrho)
449  havenan = havenan.or.isnan(self%dgq)
450  havenan = havenan.or.isnan(self%EFTAT)
451  havenan = havenan.or.isnan(self%EFTBT)
452  havenan = havenan.or.isnan(self%EFTDT)
453  havenan = havenan.or.isnan(self%EFT_kinetic)
454  havenan = havenan.or.isnan(self%EFT_gradient)
455 
456  end subroutine eftcambtimestepcacheisnan
457 
458  ! ---------------------------------------------------------------------------------------------
460  subroutine eftcambtimestepcacheopenfile( self, outroot )
461 
462  implicit none
463 
464  class(eftcamb_timestep_cache) :: self
465  character(len=*), intent(in) :: outroot
466 
467  logical :: is_open
468 
469  ! print some feedback:
470  write(*,'(a)') "***************************************************************"
471  write(*,'(a)') 'EFTCAMB cache opening print files:'
472  write(*,'(a)') "***************************************************************"
473 
474  ! test whether the files are already open:
475  call test_open( 111 )
476  call test_open( 222 )
477  call test_open( 333 )
478  call test_open( 444 )
479  call test_open( 555 )
480  call test_open( 666 )
481  call test_open( 777 )
482  call test_open( 888 )
483  call test_open( 999 )
484  call test_open( 1111 )
485  call test_open( 2222 )
486 
487  ! open the files:
488  call createtxtfile( trim(outroot)//'cache_FRW.dat' ,111 )
489  call createtxtfile( trim(outroot)//'cache_BDens.dat' ,222 )
490  call createtxtfile( trim(outroot)//'cache_BPres.dat' ,333 )
491  call createtxtfile( trim(outroot)//'cache_BackgroundEFT.dat' ,444 )
492  call createtxtfile( trim(outroot)//'cache_SecondOrdEFT.dat' ,555 )
493  call createtxtfile( trim(outroot)//'cache_BackgroundQ.dat' ,666 )
494  call createtxtfile( trim(outroot)//'cache_EinsteinCoeff.dat' ,777 )
495  call createtxtfile( trim(outroot)//'cache_PiCoeff.dat' ,888 )
496  call createtxtfile( trim(outroot)//'cache_PiSolution.dat' ,999 )
497  call createtxtfile( trim(outroot)//'cache_EinsteinSol.dat' ,1111)
498  call createtxtfile( trim(outroot)//'cache_TensorCoeff.dat' ,2222)
499 
500  ! write the headers:
501  write (111 ,'(12a)') '# ', 'a ', 'tau ', 'k ', 'adotoa ', 'Hdot ', 'Hdotdot '
502  write (222 ,'(12a)') '# ', 'a ', 'tau ', 'k ', 'grhom_t ', 'grhob_t ', 'grhoc_t ', 'grhor_t ', 'grhog_t ', 'grhov_t ', 'grhonu_tot ', 'grhonudot_tot '
503  write (333 ,'(12a)') '# ', 'a ', 'tau ', 'k ', 'gpresm_t ', 'gpresdotm_t ', 'gpiv_t ', 'gpinu_tot ', 'gpinudot_tot '
504  write (444 ,'(20a)') '# ', 'a ', 'tau ', 'k ', 'EFTOmegaV ', 'EFTOmegaP ', 'EFTOmegaPP ', 'EFTOmegaPPP ', 'EFTc ', 'EFTcdot ', 'EFTLambda ', 'EFTLambdadot '
505  write (555 ,'(16a)') '# ', 'a ', 'tau ', 'k ', 'EFTGamma1V ', 'EFTGamma1P ', 'EFTGamma2V ', 'EFTGamma2P ', 'EFTGamma3V ', 'EFTGamma3P ', 'EFTGamma4V ', 'EFTGamma4P ', 'EFTGamma4PP ', 'EFTGamma5V ', 'EFTGamma5P ', 'EFTGamma6V ', 'EFTGamma6P '
506  write (666 ,'(12a)') '# ', 'a ', 'tau ', 'k ', 'grhoq ', 'gpresq ', 'grhodotq ', 'gpresdotq '
507  write (777 ,'(18a)') '# ', 'a ', 'tau ', 'k ', 'EFTeomF ', 'EFTeomN ', 'EFTeomNdot ', 'EFTeomX ', 'EFTeomXdot ', 'EFTeomY ', 'EFTeomG ', 'EFTeomU ', 'EFTeomL ', 'EFTeomM ', 'EFTeomV ', 'EFTeomVdot '
508  write (888 ,'(14a)') '# ', 'a ', 'tau ', 'k ', 'EFTpiA1 ', 'EFTpiA2 ', 'EFTpiB1 ', 'EFTpiB2 ', 'EFTpiC ', 'EFTpiD1 ', 'EFTpiD2 ', 'EFTpiE '
509  write (999 ,'(12a)') '# ', 'a ', 'tau ', 'k ', 'pi ', 'pidot ', 'pidotdot '
510  write (1111,'(12a)') '# ', 'a ', 'tau ', 'k ', 'z ', 'clxg ', 'clxr ', 'dgpnu ', 'dgrho ', 'dgq '
511  write (2222,'(12a)') '# ', 'a ', 'tau ', 'k ', 'EFTAT ', 'EFTBT ', 'EFTDT '
512 
513  contains
514 
515  ! Temporary subroutine that tests wether a cache file is open.
516  subroutine test_open( number )
517 
518  implicit none
519 
520  integer, intent(in) :: number
521  logical :: is_open
522 
523  inquire( unit=number, opened=is_open )
524  if ( is_open ) then
525  write(*,*) 'EFTCAMB ERROR: Oputput unit', number, 'is already open.'
526  write(*,*) 'EFTCAMB cannot use it and cannot proceed.'
527  call mpistop('EFTCAMB error')
528  end if
529 
530  end subroutine test_open
531 
532  end subroutine eftcambtimestepcacheopenfile
533 
534  ! ---------------------------------------------------------------------------------------------
536  subroutine eftcambtimestepcacheclosefile( self )
537 
538  implicit none
539 
540  class(eftcamb_timestep_cache) :: self
541 
542  ! test wether the files can be closed:
543  call test_close( 111 )
544  call test_close( 222 )
545  call test_close( 333 )
546  call test_close( 444 )
547  call test_close( 555 )
548  call test_close( 666 )
549  call test_close( 777 )
550  call test_close( 888 )
551  call test_close( 999 )
552  call test_close( 1111 )
553  call test_close( 2222 )
554  ! close the files:
555  close( 111 )
556  close( 222 )
557  close( 333 )
558  close( 444 )
559  close( 555 )
560  close( 666 )
561  close( 777 )
562  close( 888 )
563  close( 999 )
564  close( 1111 )
565  close( 2222 )
566  ! print some feedback:
567  write(*,'(a)') "***************************************************************"
568  write(*,'(a)') 'EFTCAMB cache printing done.'
569  write(*,'(a)') "***************************************************************"
570 
571  contains
572 
573  ! Temporary subroutine that tests wether a cahce file is open.
574  subroutine test_close( number )
575 
576  implicit none
577 
578  integer, intent(in) :: number
579  logical :: is_open
580 
581  inquire( unit=number, opened=is_open )
582  if ( .not. is_open ) then
583  write(*,*) 'EFTCAMB ERROR: Oputput unit', number, 'is not open.'
584  write(*,*) 'EFTCAMB is trying to close it and cannot proceed.'
585  call mpistop('EFTCAMB error')
586  end if
587 
588  end subroutine test_close
589 
590  end subroutine eftcambtimestepcacheclosefile
591 
592  ! ---------------------------------------------------------------------------------------------
594  subroutine eftcambtimestepcachedumpfile( self )
595 
596  implicit none
597 
598  class(eftcamb_timestep_cache) :: self
599 
600  ! write the background expansion history:
601  write (111 ,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%adotoa, self%Hdot, self%Hdotdot
602  ! write the background densities:
603  write (222 ,'(14'//cache_output_format//')') self%a, self%tau, self%k, self%grhom_t, self%grhob_t, self%grhoc_t, self%grhor_t, self%grhog_t, self%grhov_t, self%grhonu_tot, self%grhonudot_tot
604  ! write the background pressure:
605  write (333 ,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%gpresm_t, self%gpresdotm_t, self%gpiv_t, self%gpinu_tot, self%gpinudot_tot
606  ! write background EFT functions:
607  write (444 ,'(14'//cache_output_format//')') self%a, self%tau, self%k, self%EFTOmegaV, self%EFTOmegaP, self%EFTOmegaPP, self%EFTOmegaPPP, self%EFTc, self%EFTcdot, self%EFTLambda, self%EFTLambdadot
608  ! write second order EFT functions:
609  write (555 ,'(18'//cache_output_format//')') self%a, self%tau, self%k, self%EFTGamma1V, self%EFTGamma1P, self%EFTGamma2V, self%EFTGamma2P, self%EFTGamma3V, self%EFTGamma3P, self%EFTGamma4V, self%EFTGamma4P, self%EFTGamma4PP, self%EFTGamma5V, self%EFTGamma5P, self%EFTGamma6V, self%EFTGamma6P
610  ! write background EFT auxiliary quantities:
611  write (666 ,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%grhoq, self%gpresq, self%grhodotq, self%gpresdotq
612  ! write Einstein equations coefficients:
613  write (777 ,'(18'//cache_output_format//')') self%a, self%tau, self%k, self%EFTeomF, self%EFTeomN, self%EFTeomNdot, self%EFTeomX, self%EFTeomXdot, self%EFTeomY, self%EFTeomG, self%EFTeomU, self%EFTeomL, self%EFTeomM, self%EFTeomV, self%EFTeomVdot
614  ! write pi field coefficients:
615  write (888 ,'(14'//cache_output_format//')') self%a, self%tau, self%k, self%EFTpiA1, self%EFTpiA2, self%EFTpiB1, self%EFTpiB2, self%EFTpiC, self%EFTpiD1, self%EFTpiD2, self%EFTpiE
616  ! write pi field solution:
617  write (999 ,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%pi, self%pidot, self%pidotdot
618  ! write some perturbations:
619  write (1111,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%z, self%clxg, self%clxr, self%dgpnu, self%dgrho, self%dgq
620  ! write tensor coefficients:
621  write (2222,'(12'//cache_output_format//')') self%a, self%tau, self%k, self%EFTAT, self%EFTBT, self%EFTDT
622 
623  end subroutine eftcambtimestepcachedumpfile
624 
625  ! ---------------------------------------------------------------------------------------------
627  subroutine eftcambparametercacheinit( self )
628 
629  implicit none
630 
631  class(eftcamb_parameter_cache) :: self
632 
633  ! initialize all class members to zero:
634  self%omegac = 0._dl
635  self%omegab = 0._dl
636  self%omegav = 0._dl
637  self%omegak = 0._dl
638  self%omegan = 0._dl
639  self%omegag = 0._dl
640  self%omegar = 0._dl
641  self%h0 = 0._dl
642  self%h0_Mpc = 0._dl
643  self%grhog = 0._dl
644  self%grhornomass = 0._dl
645  self%grhoc = 0._dl
646  self%grhob = 0._dl
647  self%grhov = 0._dl
648  self%grhok = 0._dl
649  self%Num_Nu_Massive = 0
650  self%Nu_mass_eigenstates = 0
651  if ( allocated(self%grhormass) ) deallocate(self%grhormass)
652  if ( allocated(self%nu_masses) ) deallocate(self%nu_masses)
653  if ( associated(self%Nu_background) ) nullify(self%Nu_background)
654  if ( associated(self%Nu_rho) ) nullify(self%Nu_rho)
655  if ( associated(self%Nu_pidot) ) nullify(self%Nu_pidot)
656  if ( associated(self%Nu_pidotdot) ) nullify(self%Nu_pidotdot)
657 
658  end subroutine eftcambparametercacheinit
659 
660  ! ---------------------------------------------------------------------------------------------
662  subroutine eftcambparametercacheprint( self )
663 
664  implicit none
665 
666  class(eftcamb_parameter_cache) :: self
667 
668  integer :: i
669 
670  ! print to screen the parameter cache:
671  write(*,'(a)') "***************************************************************"
672  write(*,'(a)') 'EFTCAMB parameters cache content:'
673  write(*,'(a)') "***************************************************************"
674  write(*,'(a14,E13.6)') ' Omega_CDM : ', self%omegac
675  write(*,'(a14,E13.6)') ' Omega_b : ', self%omegab
676  write(*,'(a14,E13.6)') ' Omega_v : ', self%omegav
677  write(*,'(a14,E13.6)') ' Omega_k : ', self%omegak
678  write(*,'(a14,E13.6)') ' Omega_n : ', self%omegan
679  write(*,'(a14,E13.6)') ' Omega_g : ', self%omegag
680  write(*,'(a14,E13.6)') ' Omega_r : ', self%omegar
681  write(*,'(a14,F12.6)') ' h : ', self%h0
682  write(*,'(a14,E13.6)') ' h_Mpc : ', self%h0_Mpc
683  write(*,'(a14,E13.6)') ' grhog : ', self%grhog
684  write(*,'(a14,E13.6)') ' grnonomass : ', self%grhornomass
685  write(*,'(a14,E13.6)') ' grhoc : ', self%grhoc
686  write(*,'(a14,E13.6)') ' grhob : ', self%grhob
687  write(*,'(a14,E13.6)') ' grhov : ', self%grhov
688  write(*,'(a14,E13.6)') ' grhok : ', self%grhok
689  write(*,'(a22,I10)') ' Num_Nu_Massive : ', self%Num_Nu_Massive
690  write(*,'(a22,I10)') ' Nu_mass_eigenstates : ', self%Nu_mass_eigenstates
691  do i=1, self%Nu_mass_eigenstates
692  write(*,'(a11,I3,a9,E13.6)') ' grhormass(',i,') : ', self%grhormass(i)
693  write(*,'(a11,I3,a9,E13.6)') ' nu_masses(',i,') : ', self%nu_masses(i)
694  end do
695  write(*,'(a)') "***************************************************************"
696 
697  end subroutine eftcambparametercacheprint
698 
699  ! ---------------------------------------------------------------------------------------------
701  subroutine eftcambparametercacheisnan( self, HaveNan )
702 
703  implicit none
704 
705  class(eftcamb_parameter_cache), intent(in) :: self
706  logical, intent(out) :: havenan
708 
709  integer :: i
710 
711  havenan = .false.
712  havenan = havenan.or.isnan(self%omegac)
713  havenan = havenan.or.isnan(self%omegab)
714  havenan = havenan.or.isnan(self%omegav)
715  havenan = havenan.or.isnan(self%omegak)
716  havenan = havenan.or.isnan(self%omegan)
717  havenan = havenan.or.isnan(self%omegag)
718  havenan = havenan.or.isnan(self%omegar)
719  havenan = havenan.or.isnan(self%h0)
720  havenan = havenan.or.isnan(self%h0_Mpc)
721  havenan = havenan.or.isnan(self%grhog)
722  havenan = havenan.or.isnan(self%grhornomass)
723  havenan = havenan.or.isnan(self%grhoc)
724  havenan = havenan.or.isnan(self%grhob)
725  havenan = havenan.or.isnan(self%grhov)
726  havenan = havenan.or.isnan(self%grhok)
727  havenan = havenan.or.isnan(self%Num_Nu_Massive*1.0_dl)
728  havenan = havenan.or.isnan(self%Nu_mass_eigenstates*1.0)
729 
730  do i=1, self%Nu_mass_eigenstates
731  havenan = havenan.or.isnan(self%grhormass(i)).or.isnan(self%nu_masses(i))
732  end do
733 
734  end subroutine eftcambparametercacheisnan
735 
736  ! ---------------------------------------------------------------------------------------------
737 
738 end module eftcamb_cache
739 
740 !----------------------------------------------------------------------------------------
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...