screening_module.f90
Go to the documentation of this file.
1 !> @file screengva2008.f90
2 !!
3 !! @brief Subroutines \ref screen and \ref screening for electron
4 !! screening coefficients
5 !!
6 
7 !> Module to calculate electron screening.
8 !!
9 !! This module calculates the screening function h (=ln(f_screen))
10 !!
11 !! @author Urs Frischknecht
12 !!
13 !! \b Edited:
14 !! - 26.07.22, MR: Made it a module and made hv, htv, and hpv module variables.
15 !! .
16 #include "macros.h"
18 
19 
20  real(r_kind), dimension(:), allocatable, public :: hv !< Screening correction
21  real(r_kind), dimension(:), allocatable, public :: htv !< temp. derivative
22  real(r_kind), dimension(:), allocatable, public :: hpv !< density derivative
23 
24  logical, public :: iscreen !< Flag whether screening is enabled or not
25 
26  !
27  ! Public and private fields and methods of the module
28  !
29  public:: &
31  private:: &
33 contains
34 
35 
36  !> Initialize the screening module
37  !!
38  !! Allocates screening correction arrays.
39  !!
40  !! @author M. Reichert
41  !! @date 26.07.22
42  subroutine init_screening(nreac)
45  implicit none
46  integer,intent(in) :: nreac !< Number of reactions
47  integer :: istat !< Status variable
48 
49  if (screening_mode .gt. 0) then
50  iscreen = .true.
51  ! Allocate the screening corrections
52  allocate(hv(nreac),htv(nreac),hpv(nreac),stat=istat)
53 
54  if (istat .ne. 0) then
55  call raise_exception('Could not allocate screening correction arrays.',&
56  'init_screening',400001)
57  end if
58  else
59  iscreen = .false.
60  end if
61 
62  end subroutine init_screening
63 
64 
65  !> @brief This function calculates the screening coefficients hv.
66  !!
67  !! It serves as interface between the subroutine \ref screening and
68  !! the \ref jacobian_class.
69  !!
70  !! @author Urs Frischknecht
71  !!
72  !! \b Edited:
73  !! - 12.01.14
74  !! - 26.07.22, MR: Made hv, htv, and hpv module variables.
75  !! - 28.07.22, MR: Introduced new chapters
76  !! .
77  subroutine screen(t9,rho,n,ye,mode)
78  use global_class, only:rrate,isotope
79  implicit none
80  real(r_kind), intent(in) :: t9, rho, ye
81  integer, intent(in) :: mode,n
82  real(r_kind) :: h1,ht1,hp1,h2,ht2,hp2,h3,ht3,hp3
83  integer :: i,z1,z2,z3,z4,z5,z6,a1,a2,a3,a4,a5,a6
84 
85  do i=1,n
86  select case (rrate(i)%group)
87  case(1:3,11)
88  hv(i)=0.d0
89  htv(i)=0.d0
90  hpv(i)=0.d0
91  case(4:7)
92  z1=isotope(rrate(i)%parts(1))%p_nr
93  z2=isotope(rrate(i)%parts(2))%p_nr
94  a1=isotope(rrate(i)%parts(1))%mass
95  a2=isotope(rrate(i)%parts(2))%mass
96  call screening(t9,rho,z1,z2,a1,a2,ye,mode,h1,ht1,hp1)
97  hv(i)=h1
98  htv(i)=ht1
99  hpv(i)=hp1
100  case(8:9)
101  z1=isotope(rrate(i)%parts(1))%p_nr
102  z2=isotope(rrate(i)%parts(2))%p_nr
103  z3=isotope(rrate(i)%parts(3))%p_nr
104  z4=z1+z2
105  a1=isotope(rrate(i)%parts(1))%mass
106  a2=isotope(rrate(i)%parts(2))%mass
107  a3=isotope(rrate(i)%parts(3))%mass
108  a4=a1+a2
109  call screening(t9,rho,z1,z2,a1,a2,ye,mode,h1,ht1,hp1)
110  call screening(t9,rho,z3,z4,a3,a4,ye,mode,h2,ht2,hp2)
111  hv(i)=h1+h2
112  htv(i)=ht1+ht2
113  hpv(i)=hp1+hp2
114  case(10)
115  z1=isotope(rrate(i)%parts(1))%p_nr
116  z2=isotope(rrate(i)%parts(2))%p_nr
117  z3=isotope(rrate(i)%parts(3))%p_nr
118  z4=isotope(rrate(i)%parts(4))%p_nr
119  z5=z1+z2
120  z6=z3+z4
121  a1=isotope(rrate(i)%parts(1))%mass
122  a2=isotope(rrate(i)%parts(2))%mass
123  a3=isotope(rrate(i)%parts(3))%mass
124  a4=isotope(rrate(i)%parts(4))%mass
125  a5=a1+a2
126  a6=a3+a4
127  call screening(t9,rho,z1,z2,a1,a2,ye,mode,h1,ht1,hp1)
128  call screening(t9,rho,z3,z4,a3,a4,ye,mode,h2,ht2,hp2)
129  call screening(t9,rho,z5,z6,a5,a6,ye,mode,h3,ht3,hp3)
130  hv(i)=h1+h2+h3
131  htv(i)=ht1+ht2+ht3
132  hpv(i)=hp1+hp2+hp3
133  end select
134  end do
135 
136  return
137  end subroutine screen
138 
139 
140 
141  !> Free energy according to parametrization of Kravchuk and Yakovlev
142  !!
143  !! This function calculates the free energy of a one-component plasma
144  !! according to equation 19 of Kravchuk & Yakovlev (2014).
145  !!
146  !! @see [Kravchuk & Yakovlev 2014](https://ui.adsabs.harvard.edu/abs/2014PhRvC..89a5802K/abstract)
147  !!
148  !! @author M. Reichert
149  !! @date 03.04.2023
150  function free_energy_kravchuk_yakovlev(gamma) result(f_C)
151  implicit none
152  real(r_kind),intent(in) :: gamma !< Ion coupling parameter
153  real(r_kind) :: f_c !< Free energy
154  ! Parameters from Kravchuk & Yakovlev (2014)
155  real(r_kind),parameter :: a_1= -0.907
156  real(r_kind),parameter :: a_2= 0.62954
157  real(r_kind),parameter :: a_3= 0.2771
158  real(r_kind),parameter :: b_1= 0.00456
159  real(r_kind),parameter :: b_2= 211.6
160  real(r_kind),parameter :: b_3= -0.0001
161  real(r_kind),parameter :: b_4= 0.00462
162 
163  f_c = a_1*( dsqrt(gamma*(a_2 + gamma)) - a_2 * dlog( dsqrt(gamma/a_2) + dsqrt(1d0+gamma/a_2))) &
164  +2d0*a_3 * (dsqrt(gamma)-datan(dsqrt(gamma))) &
165  +b_1 * (gamma - b_2 * dlog(1d0+gamma/b_2)) &
166  +b_3/2d0 * dlog(1d0 + gamma**2d0 / b_4)
167 
168  end function free_energy_kravchuk_yakovlev
169 
170 
171 
172 
173  !> Interface for the screening.
174  !!
175  !! This subroutine is an interface for the different
176  !! screening prescriptions.
177  !!
178  !! @author M. Reichert
179  !! @date 03.04.2023
180  subroutine screening(t9,rho,z1,z2,a1,a2,ye,mode,h,ht,hp)
183  implicit none
184  integer,intent(in) :: mode !< =0 no derivatives are calculated,
185  !! =1 ht=dln(f)/d(t9)=dh/dt9,
186  !! hp=dln(f)/d(rho)=dh/d(rho)
187  real(r_kind),intent(in) :: t9 !< temperature [GK]
188  real(r_kind),intent(in) :: rho !< density [g/cm^3]
189  integer,intent(in) :: z1,z2 !< charge numbers of colliding nuclei
190  integer,intent(in) :: a1,a2 !< mass numbers of colliding nuclei
191  real(r_kind),intent(in) :: ye !< electron fraction
192  real(r_kind),intent(out) :: h !< screening function
193  real(r_kind),intent(out) :: ht !< dln(f)/d(t9)=dh/dt9
194  real(r_kind),intent(out) :: hp !< dln(f)/d(rho)=dh/d(rho)
195  !
196  integer,parameter :: screen_mode =1
197 
198  if (screen_mode .eq. 1) then
199  call screening_kravchuk_yakovlev(t9,rho,z1,z2,a1,a2,ye,mode,h,ht,hp)
200  else
201  call raise_exception('Unknown screening mode, got '//int_to_str(screening_mode)//".",&
202  "screening",400003)
203  end if
204 
205  end subroutine screening
206 
207 
208 
209  !> Screening function according to Kravchuk & Yakovlev (2014)
210  !!
211  !! This function calculates the screening function according to
212  !! equation 62 of Kravchuk & Yakovlev (2014) using the "combined" model.
213  !!
214  !! @note This function is in principle only valid for the strong
215  !! screening regime does however not deviate too much for the weak
216  !! screening as well.
217  !!
218  !! @author M. Reichert
219  !! @date 03.04.2023
220  subroutine screening_kravchuk_yakovlev(t9,rho,z1,z2,a1,a2,ye,mode,h,ht,hp)
222  implicit none
223  integer,intent(in) :: mode !< =0 no derivatives are calculated,
224  !! =1 ht=dln(f)/d(t9)=dh/dt9,
225  !! hp=dln(f)/d(rho)=dh/d(rho)
226  real(r_kind),intent(in) :: t9 !< temperature [GK]
227  real(r_kind),intent(in) :: rho !< density [g/cm^3]
228  integer,intent(in) :: z1,z2 !< charge numbers of colliding nuclei
229  integer,intent(in) :: a1,a2 !< mass numbers of colliding nuclei
230  real(r_kind),intent(in) :: ye !< electron fraction
231  real(r_kind),intent(out) :: h !< screening function
232  real(r_kind),intent(out) :: ht !< dln(f)/d(t9)=dh/dt9
233  real(r_kind),intent(out) :: hp !< dln(f)/d(rho)=dh/d(rho)
234  !
235  real(r_kind) :: zz !< helper variable for combined z's
236  real(r_kind) :: tau !< helper variable (Eq. 5 of K&Y 2014)
237  real(r_kind) :: xi !< xi = 3 gamma_12 / tau
238  real(r_kind) :: gamma_12 !< Combined gamma
239  real(r_kind) :: zfrac !< Fraction of z1 and z2
240  real(r_kind) :: gamma_1 !< Gamma of reacting nucleus 1
241  real(r_kind) :: gamma_2 !< Gamma of reacting nucleus 2
242  real(r_kind) :: gamma_c !< Gamma of compound nucleus
243  real(r_kind) :: b0 !< Salpeter parameter
244  real(r_kind) :: b2 !< b2 parameter that gets multiplied to xi**2
245  real(r_kind) :: b4 !< b4 parameter that gets multiplied to xi**4
246  real(r_kind) :: z1r,z2r !< z variables as doubles
247 
248  h = 0.d0
249  ht = 0.d0
250  hp = 0.d0
251 
252  ! Don't screen if a neutron is involved
253  if(z1.eq.0 .or. z2.eq.0) then
254  return
255  endif
256 
257  ! Initialize gammas
258  gamma_12= 0.d0
259  gamma_1 = 0.d0
260  gamma_2 = 0.d0
261  gamma_c = 0.d0
262 
263  ! Convert the integers to a double
264  z1r = dble(z1)
265  z2r = dble(z2)
266  ! Calculate xi, gamma_12, and tau (Eq. 5 of K&Y 2014)
267  zz = 2.d0*z1r*z2r/(z1r**(1.d0/3.d0)+z2r**(1.d0/3.d0))
268  tau = 3.3722d0*(2.d0*a1*a2/(a1+a2)*(z1r*z2r)**2/t9)**(1.d0/3.d0)
269  gamma_12= zz*0.22747d-3*(rho*ye)**(1.d0/3.d0)/t9
270  xi=3.d0*gamma_12/tau
271 
272  ! Gamma of nucleus 1
273  zz=z1r**(5.0/3.0)
274  gamma_1= zz*0.22747e-3*(rho*ye)**(1.e0/3.e0)/t9
275  ! Gamma of nucleus 2
276  zz=z2r**(5.0/3.0)
277  gamma_2= zz*0.22747e-3*(rho*ye)**(1.e0/3.e0)/t9
278  ! Gamma of compound nucleus
279  zz=(z1r+z2r)**(5.0/3.0)
280  gamma_c= zz*0.22747e-3*(rho*ye)**(1.e0/3.e0)/t9
281 
282  ! Calculate b0 ( Eq. 18 of K&Y 2014)
283  b0 = (free_energy_kravchuk_yakovlev(gamma_1) + &
284  free_energy_kravchuk_yakovlev(gamma_2) - &
285  free_energy_kravchuk_yakovlev(gamma_c))/gamma_12
286  ! Calculate b2 ( Eq. 14 of K&Y 2014)
287  zfrac = z1r/z2r
288  b2 = -1d0/(16d0) * (1d0+zfrac**(1d0/3d0))**3d0 / (1d0 + zfrac)
289  ! Calculate b4 ( Eq. 15 of K&Y 2014)
290  b4 = zfrac/(64d0) * (1d0+zfrac**(1d0/3d0))**5d0 / ((1d0 + zfrac)**(11d0/3d0))
291 
292  ! Calculate the screening correction (Eq 62 of K&Y 2014)
293  h = gamma_12 * ( b0 + 5d0/8d0*b2*xi**2d0 + 63d0/128d0*b4*xi**4d0 )
294 
295  ! Calculate derivatives if requested
296  if (mode.eq.1) then
297  call raise_exception('Derivatives not implemented yet.',&
298  'screening_kravchuk_yakovlev', 400004)
299  end if
300 
301  end subroutine screening_kravchuk_yakovlev
302 
303 
304 end module screening_module
screening_module
Module to calculate electron screening.
Definition: screening_module.f90:17
global_class::rrate
type(reactionrate_type), dimension(:), allocatable, public rrate
array containing all reaction rates used in the network
Definition: global_class.f90:65
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
error_msg_class::int_to_str
character(:) function, allocatable, public int_to_str(num)
Converts a given integer to a string.
Definition: error_msg_class.f90:224
parameter_class::screening_mode
integer screening_mode
Mode for coulomb corrections: 0 - no screening, 1 - screening using the prescription of Kravchuk & Ya...
Definition: parameter_class.f90:150
error_msg_class::raise_exception
subroutine, public raise_exception(msg, sub, error_code)
Raise a exception with a given error message.
Definition: error_msg_class.f90:245
global_class::isotope
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
Definition: global_class.f90:34
screening_module::screening_kravchuk_yakovlev
subroutine, private screening_kravchuk_yakovlev(t9, rho, z1, z2, a1, a2, ye, mode, h, ht, hp)
Screening function according to Kravchuk & Yakovlev (2014)
Definition: screening_module.f90:221
screening_module::init_screening
subroutine, public init_screening(nreac)
Initialize the screening module.
Definition: screening_module.f90:43
screening_module::htv
real(r_kind), dimension(:), allocatable, public htv
temp. derivative
Definition: screening_module.f90:21
screening
Definition: screening.py:1
screening_module::hpv
real(r_kind), dimension(:), allocatable, public hpv
density derivative
Definition: screening_module.f90:22
r_kind
#define r_kind
Definition: macros.h:46
screening_module::hv
real(r_kind), dimension(:), allocatable, public hv
Screening correction.
Definition: screening_module.f90:20
screening_module::screen
subroutine, public screen(t9, rho, n, ye, mode)
This function calculates the screening coefficients hv.
Definition: screening_module.f90:78
global_class
Contains types and objects shared between multiple modules.
Definition: global_class.f90:19
screening_module::iscreen
logical, public iscreen
Flag whether screening is enabled or not.
Definition: screening_module.f90:24
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
screening_module::free_energy_kravchuk_yakovlev
real(r_kind) function, private free_energy_kravchuk_yakovlev(gamma)
Free energy according to parametrization of Kravchuk and Yakovlev.
Definition: screening_module.f90:151