-
Notifications
You must be signed in to change notification settings - Fork 159
/
Copy pathcosmorec.f90
195 lines (156 loc) · 5.96 KB
/
cosmorec.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
!---------------------------------------------------------------------------------------------------
! Recombination module for CAMB, using CosmoRec
! Author: Richard Shaw (CITA)
!
! To use with the python wrapper add -fPIC to CCFLAGS in the CosmoRec Makefile (for gcc)
!---------------------------------------------------------------------------------------------------
! 08.06.2012: added possibility to communicate Hubble (Jens Chluba)
! 12.06.2012: AL, changed interface to pass nnu directly; fixed spline extrapolation
! 09.01.2019: AL, updated for new class structure
module CosmoRec
use precision
use constants
use classes
use MathUtils
use results
use config
use Interpolation
use MpiUtils, only : MpiStop
implicit none
private
integer, parameter :: Nz = 10000
real(dl), parameter :: zmax = 1d4
real(dl), parameter :: zmin = 0._dl
type, extends(TRecombinationModel) :: TCosmoRec
integer :: runmode = 0
real(dl) :: fdm = 0._dl ! Dark matter annihilation efficiency
! Internal accuracy of CosmoRec (0 - normal, 3 - most accurate
! other values defined in CosmoRec.cpp source file)
real(dl) :: accuracy = 0._dl
!Internal data
class(TRegularCubicSpline), allocatable :: xrec, tmrec
contains
procedure :: ReadParams => TCosmoRec_ReadParams
procedure :: Validate => TCosmoRec_Validate
procedure :: Init => TCosmoRec_init
procedure :: x_e => TCosmoRec_xe
procedure :: T_m => TCosmoRec_tm !baryon temperature
procedure, nopass :: SelfPointer => TCosmoRec_SelfPointer
end type TCosmoRec
public TCosmoRec
contains
subroutine TCosmoRec_ReadParams(this, Ini)
class(TCosmoRec) :: this
class(TIniFile), intent(in) :: Ini
call Ini%Read('cosmorec_runmode', this%runmode)
call Ini%Read('cosmorec_accuracy', this%accuracy)
call Ini%Read('cosmorec_fdm', this%fdm)
end subroutine TCosmoRec_ReadParams
subroutine TCosmoRec_Validate(this, OK)
class(TCosmoRec),intent(in) :: this
logical, intent(inout) :: OK
if(this%runmode < 0 .or. this%runmode > 3) then
write(*,*) "Invalid runmode for CosmoRec,"
OK = .false.
end if
if(this%runmode < 2 .and. this%fdm > 1d-23) then
write(*,*) "Dark matter annihilation rate too high. Will crash CosmoRec."
OK = .false.
end if
if(this%accuracy < 0.0 .or. this%accuracy > 3.0) then
write(*,*) "CosmoRec accuracy mode undefined."
OK = .false.
end if
end subroutine TCosmoRec_Validate
function TCosmoRec_tm(this,a)
class(TCosmoRec) :: this
real(dl), intent(in) :: a
real(dl) TCosmoRec_tm
real(dl) z
z =1/a-1
if (z >= this%tmrec%xmax) then
TCosmoRec_tm = this%tmrec%F(Nz)*(1+z)/(1+this%tmrec%xmax)
else if (z <= this%tmrec%xmin) then
TCosmoRec_tm = this%tmrec%F(1)
else
TCosmoRec_tm = this%tmrec%Value(z)
end if
end function TCosmoRec_tm
function TCosmoRec_xe(this,a)
class(TCosmoRec) :: this
real(dl), intent(in) :: a
real(dl) TCosmoRec_xe
real(dl) z
z =1/a-1
if (z >= this%xrec%xmax) then
TCosmoRec_xe = this%xrec%F(Nz)
else if (z <= this%xrec%xmin) then
TCosmoRec_xe = this%xrec%F(1)
else
TCosmoRec_xe = this%xrec%Value(z)
end if
end function TCosmoRec_xe
subroutine TCosmoRec_init(this, State, WantTSpin)
use MiscUtils
class(TCosmoRec), target :: this
class(TCAMBdata), target :: State
logical, intent(in), optional :: WantTSpin
integer :: i, label
real(dl), dimension(5) :: runpars
procedure(obj_function) :: dtauda
real(dl) OmegaB, OmegaC, OmegaK, h2
real(dl), allocatable :: Hz(:), zrec(:), tmrec(:), xrec(:), tmp(:)
external CosmoRec_calc_h_cpp
#ifdef MPI
label = GetMpiRank()
#else
label = 0
#endif
! Some feedback
if (DefaultFalse(WantTSpin)) call MpiStop('CosmoRec does not support 21cm')
select type(State)
class is (CAMBdata)
if (State%CP%Evolve_delta_xe) &
call MpiStop('CosmoRec currently does not support evolving Delta x_e')
h2 = (State%CP%H0/100)**2
OmegaB = State%CP%ombh2/h2
!These parameters are now redundant since using Hz array, just set to something
Omegak = State%CP%omk
OmegaC = State%CP%omch2/h2
if (.not. allocated(this%xrec)) allocate(TRegularCubicSpline::this%xrec)
if (.not. allocated(this%tmrec)) allocate(TRegularCubicSpline::this%tmrec)
allocate(Hz(Nz), zrec(Nz), xrec(Nz), tmrec(Nz), tmp(Nz))
! Set runtime parameters
runpars = 0._dl
runpars(1) = this%fdm ! Set dark matter annihilation efficiency
runpars(2) = this%accuracy
! Set redshifts to calculate at.
do i=1,Nz
zrec(i) = zmax - (i-1)*((zmax - zmin) / (Nz-1))
Hz(i) = 1/dtauda(State,1/(1._dl+zrec(i))) &
*(1._dl+zrec(i))**2/MPC_in_sec
end do
! internal Hubble function of CosmoRec is used
!call CosmoRec_calc_cpp(Recomb%runmode, runpars, &
! OmegaC, OmegaB, OmegaK, num_nu, h0inp, tcmb, yp, &
! zrec, xrec, tmrec, Nz, label)
! version which uses camb Hubble function
call CosmoRec_calc_h_cpp(this%runmode, runpars, &
OmegaC, OmegaB, OmegaK, State%CP%N_eff(), State%CP%H0, State%CP%tcmb, State%CP%yhe, &
zrec, Hz, Nz, zrec, xrec, tmrec, Nz, label)
!Init interpolation
tmp =xrec(Nz:1:-1)
call this%xrec%Init(zrec(Nz), zrec(1), Nz, tmp)
tmp =tmrec(Nz:1:-1)
call this%tmrec%Init(zrec(Nz), zrec(1), Nz, tmp)
end select
end subroutine TCosmoRec_init
subroutine TCosmoRec_SelfPointer(cptr,P)
use iso_c_binding
Type(c_ptr) :: cptr
Type (TCosmoRec), pointer :: PType
class (TPythonInterfacedClass), pointer :: P
call c_f_pointer(cptr, PType)
P => PType
end subroutine TCosmoRec_SelfPointer
end module CosmoRec