-
Notifications
You must be signed in to change notification settings - Fork 9
/
py_camb_wrap.f90.template
273 lines (228 loc) · 9.15 KB
/
py_camb_wrap.f90.template
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
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
module pycamb_mod
double precision, dimension(:,:,:), allocatable :: transfers
double precision, dimension(:), allocatable :: transfers_k,transfers_sigma8
real, dimension(:,:,:), allocatable :: matter_power
double precision, dimension(:,:), allocatable :: matter_power_kh
double precision, dimension(:), allocatable :: matter_power_sigma8
double precision :: output_cl_scale=7.4311e12
contains
subroutine getcls(paramVec,lmax,Max_eta_k,cls)
use camb
implicit none
real, intent(in) :: paramVec($number_parameters$)
integer, intent(in) :: lmax, Max_eta_k
real, intent(out) :: cls(2:lmax,4)
type(CAMBparams) :: P
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
P%max_l=lmax
P%Max_l_tensor=lmax
P%Max_eta_k=Max_eta_k
P%Max_eta_k_tensor=Max_eta_k
call CAMB_GetResults(P)
call CAMB_GetCls(cls, lmax, 1, .false.)
cls=cls*output_cl_scale
end subroutine getcls
subroutine getage(paramVec,age)
use camb
implicit none
real, intent(in) :: paramVec($number_parameters$)
double precision, intent(out) :: age
type(CAMBparams) :: P
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
age = CAMB_GetAge(P)
end subroutine getage
subroutine gentransfers(paramVec,lmax,nred,redshifts)
use camb
implicit none
real, intent(in) :: paramVec($number_parameters$)
integer, intent(in) :: nred, lmax
double precision, intent(in), dimension(nred) :: redshifts
type(CAMBparams) :: P
integer :: nr, i
nr = size(redshifts)
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
P%WantTransfer = .true.
P%max_l=lmax
P%Max_l_tensor=lmax
P%Max_eta_k=2*lmax
P%Max_eta_k_tensor=2*lmax
P%transfer%num_redshifts = nr
do i=1,nr
P%transfer%redshifts(i)=redshifts(i)
enddo
call Transfer_SortAndIndexRedshifts(P%Transfer)
call CAMB_GetResults(P)
call freetransfers()
allocate(transfers(Transfer_max,MT%num_q_trans,nred))
allocate(transfers_k(MT%num_q_trans))
allocate(transfers_sigma8(nred))
transfers = MT%TransferData
transfers_k = MT%q_trans
transfers_sigma8 = MT%sigma_8(:,1)
end subroutine gentransfers
subroutine freetransfers()
if (allocated(transfers)) deallocate(transfers)
if (allocated(transfers_k)) deallocate(transfers_k)
if (allocated(transfers_sigma8)) deallocate(transfers_sigma8)
end subroutine freetransfers
subroutine freematterpower()
if (allocated(matter_power)) deallocate(matter_power)
if (allocated(matter_power_kh)) deallocate(matter_power_kh)
if (allocated(matter_power_sigma8)) deallocate(matter_power_sigma8)
end subroutine freematterpower
subroutine genpowerandcls(paramVec,lmax,Max_eta_k,nk_input, kh_input, nred,redshifts,cls)
use camb
implicit none
real, intent(out) :: cls(2:lmax,4)
real, intent(in) :: paramVec($number_parameters$)
integer, intent(in) :: nred, lmax, Max_eta_k
real :: maxk, dlogk
real, parameter :: minkh = 1.0e-4
double precision, intent(in), dimension(nred) :: redshifts
type(CAMBparams) :: P
integer :: nr, i, nk
integer in,itf, points, points_check
integer, intent(in) :: nk_input
double precision, intent(in), dimension(nk_input) :: kh_input
type(MatterPowerData) :: PK_data
dlogk = 0.02
nr = size(redshifts)
nk = size(kh_input)
maxk = maxval(kh_input)*2.0
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
P%WantTransfer = .true.
P%max_l=lmax
P%Max_l_tensor=lmax
P%Max_eta_k=Max_eta_k
P%Max_eta_k_tensor=Max_eta_k
P%transfer%PK_num_redshifts = nr
do i=1,nr
P%transfer%pk_redshifts(i)=redshifts(i)
enddo
P%transfer%num_redshifts = nr
P%transfer%kmax = maxk * (P%h0/100._dl)
P%transfer%k_per_logint = dlogk
call Transfer_SortAndIndexRedshifts(P%Transfer)
call CAMB_GetResults(P)
call CAMB_GetCls(cls, lmax, 1, .false.)
cls=cls*output_cl_scale
call freematterpower()
allocate(matter_power(nk,CP%InitPower%nn,nr))
allocate(matter_power_kh(nk,nr))
allocate(matter_power_sigma8(nr))
call Transfer_GetMatterPowerData(MT, PK_data, 1)
if (P%nonlinear==nonlinear_pk .or. P%nonlinear==NonLinear_both) call MatterPowerdata_MakeNonlinear(PK_data)
do itf=1,nr
call Transfer_Get_sigma8(MT, matter_power_sigma8(i))
do i=1,nk
matter_power_kh(i,itf) = kh_input(i)
matter_power(i, 1, itf) = MatterPowerData_k(PK_data, kh_input(i), itf)
enddo
enddo
end subroutine genpowerandcls
subroutine getpower(paramVec,nk_input, kh_input,nred,redshifts)
use camb
implicit none
real, intent(in) :: paramVec($number_parameters$)
integer, intent(in) :: nred
integer :: lmax
double precision, intent(in), dimension(nred) :: redshifts
type(CAMBparams) :: P
type(MatterPowerData) :: PK_data
integer :: nr, i, nk
integer, intent(in) :: nk_input
double precision, intent(in), dimension(nk_input) :: kh_input
real :: maxk, dlogk
real, parameter :: minkh = 1.0e-4
integer in,itf, points, points_check
dlogk = 0.02
nr = size(redshifts)
nk = size(kh_input)
maxk = maxval(kh_input)*2.0
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
P%WantTransfer = .true.
P%PK_WantTransfer = .true.
lmax=2000
P%max_l=lmax
P%Max_l_tensor=lmax
P%Max_eta_k=2*lmax
P%Max_eta_k_tensor=2*lmax
P%transfer%pk_num_redshifts = nr
P%transfer%kmax = maxk * (P%h0/100._dl)
P%transfer%k_per_logint = dlogk
do i=1,nr
P%transfer%pk_redshifts(i)=redshifts(i)
enddo
call Transfer_SortAndIndexRedshifts(P%Transfer)
call CAMB_GetResults(P)
call freematterpower()
allocate(matter_power(nk,CP%InitPower%nn,nr))
allocate(matter_power_kh(nk,nr))
allocate(matter_power_sigma8(nr))
call Transfer_GetMatterPowerData(MT, PK_data, 1)
if (P%nonlinear==nonlinear_pk .or. P%nonlinear==NonLinear_both) call MatterPowerdata_MakeNonlinear(PK_data)
do itf=1,nr
call Transfer_Get_sigma8(MT, matter_power_sigma8(i))
do i=1,nk
matter_power_kh(i,itf) = kh_input(i)
matter_power(i, 1, itf) = MatterPowerData_k(PK_data, kh_input(i), itf)
enddo
enddo
end subroutine getpower
function angularDiameter(paramVec,z)
use ModelParams, only : CAMBparams, camb_angulardiameter => AngularDiameterDistance
use camb, only : CAMB_SetDefParams, CAMBParams_Set
implicit none
double precision, intent(in) :: z
double precision :: angularDiameter
real, intent(in) :: paramVec($number_parameters$)
integer error
type(CAMBparams) :: P
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
call CAMBParams_Set(P,error)
angularDiameter = camb_angulardiameter(z)
end function angularDiameter
subroutine angularDiameterVector(paramVec,n,z,ang)
!Should be in temporal order ie redshift decreasing
use ModelParams, only : CAMBparams, DeltaTime, rofchi
use camb, only : CAMB_SetDefParams, CAMBParams_Set, CP
implicit none
integer, intent(in) :: n
integer :: nz
double precision,dimension(n), intent(in) :: z
double precision,dimension(n), intent(out) :: ang
real, intent(in) :: paramVec($number_parameters$)
integer error
integer i,j
type(CAMBparams) :: P
nz=size(z)
call CAMB_SetDefParams(P)
call makeParameters(paramVec,P)
call CAMBParams_Set(P,error)
ang(nz) = rofchi(DeltaTime(1/(1+z(nz)),1.0_8)/CP%r)
do i=1,nz-1
j=nz-i
ang(j) = rofchi(DeltaTime(1.0/(1.0+z(j)),1./(1.+z(j+1)))/CP%r) + ang(j+1)
enddo
ang = ang * CP%r/(1+z)
end subroutine angularDiameterVector
subroutine makeParameters(paramVec,P)
use camb
implicit none
type(CAMBparams) P
real, intent(in) :: paramVec($number_parameters$)
$param_caller_function$
end subroutine makeParameters
subroutine setCLTemplatePath(path)
use camb
implicit none
character(LEN=1024), intent(in) :: path
highL_unlensed_cl_template = path
end subroutine setCLTemplatePath
end module pycamb_mod