-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathxr_ref.f90
executable file
·167 lines (150 loc) · 5.03 KB
/
xr_ref.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
subroutine parratt_born(q,lambda,d,rho,beta,sigma,Rgen,Rgenr, M,N)
!***************************************************************************
!Subroutine to calculate Specular Reflectivity using Parratt Algorithm with
!Born Approximation for roughness
!M = No. of data points
!N = No. of slabs
!lambda = wavelength
!d = list of thicknesses of each slab
!rho=list of Electron densities of each slab
!beta=list of Absorption coefficient in each slab
!Rgen = generated reflectivtiy data
!Rgenr = generated reflectance data
!q = change in wave vector
!***************************************************************************
integer :: M,N
double precision :: q(0:M), Rgen(0:M)
double precision :: d(0:N+1), rho(0:N+1), beta(0:N+1), sigma(0:N+1), qc2(0:N+1)
double precision :: lambda
double complex :: X, fact1, fact2, r(0:N+1), k1, k2, fact, Rgenr(0:M)
double precision, parameter :: re=2.817938e-5, pi=3.14159
Cf2py intent(in) q
Cf2py intent(in) lambda
Cf2py intent(in) d
Cf2py intent(in) rho
Cf2py intent(in) beta
Cf2py intent(in) sigma
Cf2py intent(out) Rgen
Cf2py intent(out) rgenr
Cf2py depend(M) Rgen
CF2py depend(M) Rgenr
do j=0,N+1
qc2(j)=16.0d0*pi*re*(rho(j)-rho(0))
enddo
do i = 0,M
r(N+1)=dcmplx(0.0d0,0.0d0)
do j=N,0,-1
k1=cdsqrt(dcmplx(q(i)**2-qc2(j),-32.0d0*beta(j)*pi**2/lambda**2))
k2=cdsqrt(dcmplx(q(i)**2-qc2(j+1),-32.0d0*beta(j+1)*pi**2/lambda**2))
X=(k1-k2)*cdexp(-k1*k2*sigma(j+1)**2/2)/(k1+k2)
fact1=dcmplx(dcos(dble(k2)*d(j+1)),dsin(dble(k2)*d(j+1)))
fact2=dexp(-aimag(k2)*d(j+1))
fact=fact1*fact2
r(j)=(X+r(j+1)*fact)/(1.0+X*r(j+1)*fact)
enddo
Rgenr(i)=r(0)
Rgen(i)=cdabs(r(0))**2
enddo
end subroutine parratt_born
subroutine parratt(q,lambda,d,rho,beta,Rgen,Rgenr,M,N)
!***************************************************************************
!Calculation of reflectivity by Parratt Recursion Formula without any roughness
!
!M = No. of data points
!N = No. of slabs
!lambda = wavelength
!d = list of thicknesses of each slab
!rho=list of Electron densities of each slab
!beta=list of Absorption coefficient in each slab
!Rgen = generated reflectivtiy data
!Rgenr= generated reflectance data
!q = change in wave vector
!***************************************************************************
integer :: M,N
double precision :: q(0:M), Rgen(0:M)
double precision :: d(0:N+1), rho(0:N+1), beta(0:N+1), qc2(0:N+1)
double precision :: lambda
double complex :: X, fact1, fact2, r(0:N+1), k1, k2, fact,Rgenr(0:M)
double precision, parameter :: re=2.817938e-5, pi=3.14159
Cf2py intent(in) q
Cf2py intent(in) lambda
Cf2py intent(in) d
Cf2py intent(in) rho
Cf2py intent(in) beta
Cf2py intent(out) Rgen
Cf2py intent(out) rgenr
do j=0,N+1
qc2(j)=16.0d0*pi*re*(rho(j)-rho(0))
enddo
do i = 0,M
r(N+1)=dcmplx(0.0d0,0.0d0)
do j=N,0,-1
k1=cdsqrt(dcmplx(q(i)**2-qc2(j),-32.0d0*beta(j)*pi**2/lambda**2))
k2=cdsqrt(dcmplx(q(i)**2-qc2(j+1),-32.0d0*beta(j+1)*pi**2/lambda**2))
X=(k1-k2)/(k1+k2)
fact1=dcmplx(dcos(dble(k2)*d(j+1)),dsin(dble(k2)*d(j+1)))
fact2=dexp(-aimag(k2)*d(j+1))
fact=fact1*fact2
r(j)=(X+r(j+1)*fact)/(1.0+X*r(j+1)*fact)
enddo
Rgenr(i)=r(0)
Rgen(i)=cdabs(r(0))**2
enddo
end subroutine parratt
subroutine conv_parratt(q,delq,lambda,d,rho,beta,Rgen,M,N)
!***************************************************************************
!Calculation of convoluted reflectivity by Parratt Recursion Formula without
!any roughness
!M = No. of data points
!N = No. of slabs
!lambda = wavelength
!d = list of thicknesses of each slab
!rho=list of Electron densities of each slab
!beta=list of Absorption coefficient in each slab
!Rgen = generated reflectivtiy data
!q = change in wave vector
!delq=width of the resolution funciton
!***************************************************************************
integer :: M,N
double precision :: q(0:M), Rgen(0:M)
double precision :: d(0:N+1), rho(0:N+1), beta(0:N+1), qc2(0:N+1)
double precision :: lambda,delq
double complex :: X, fact1, fact2, r(0:N+1), k1, k2, fact
double precision, parameter :: re=2.817938e-5, pi=3.14159
double precision :: refsum,q0
integer :: Nres
Cf2py intent(in) q
Cf2py intent(in) delq
Cf2py intent(in) lambda
Cf2py intent(in) d
Cf2py intent(in) rho
Cf2py intent(in) beta
Cf2py intent(out) Rgen
Cf2py depend(M) Rgen
Nres=21
do j=0,N+1
qc2(j)=16.0d0*pi*re*(rho(j)-rho(0))
enddo
do i = 0,M
r(N+1)=dcmplx(0.0d0,0.0d0)
refsum=0.0d0
ressum=0.0d0
do k = -(Nres-1)/2,(Nres-1)/2
qo=q(i)+4*k*delq/(Nres-1)
if (qo>=0.0d0) then
do j=N,0,-1
k1=cdsqrt(dcmplx(qo**2-qc2(j),-32.0d0*beta(j)*pi**2/lambda**2))
k2=cdsqrt(dcmplx(qo**2-qc2(j+1),-32.0d0*beta(j+1)*pi**2/lambda**2))
X=(k1-k2)/(k1+k2)
fact1=dcmplx(dcos(dble(k2)*d(j+1)),dsin(dble(k2)*d(j+1)))
fact2=dexp(-aimag(k2)*d(j+1))
fact=fact1*fact2
r(j)=(X+r(j+1)*fact)/(1.0+X*r(j+1)*fact)
enddo
refsum=refsum+cdabs(r(0))**2*dexp(-k**2/2.0d0/(Nres-1)**2)
ressum=ressum+dexp(-dfloat(k)**2/2.0d0/(dfloat(Nres)-1)**2)
endif
enddo
rgen(i)=refsum/ressum
enddo
end subroutine conv_parratt