nucstuff_class.f90
Go to the documentation of this file.
1 !> @file nucstuff_class.f90
2 !!
3 !! The error file code for this file is ***W32***.
4 !!
5 !! @brief Module \ref nucstuff_class with nuclear physics helpers
6 !!
7 
8 !> Module with helper functions such as rate tabulation, partition functions,
9 !! and theoretical weak rates.
10 #include "macros.h"
13 
14  implicit none
15  real(r_kind),dimension(9), public :: t9_pow !< Powers of T, used for the rates
16  !< @see calc_t9_pow
17  integer,public :: ntgp !< (24/72) Number of temp grid points for the partition functions
18  real(r_kind),dimension(:),allocatable,public :: pf !< partition functions
19 
20  !
21  ! Public and private fields and methods of the module.
22  !
23  public:: &
25 
26  ! private:: &
27  ! nothing here
28 
29 contains
30 
31 
32 
33 !> Initialize nucstuff class
34 !!
35 !! Allocate the partition function array.
36 !!
37 !! @author M. Reichert
38 !! @date 26.07.22
39 subroutine init_nucstuff()
40  use global_class, only: net_size
42  implicit none
43  integer :: istat !< Allocation variable
44 
45  ! Allocate the partition function array
46  allocate(pf(0:net_size),stat = istat)
47 
48  ! Throw exception
49  if (istat .ne. 0) then
50  call raise_exception('Allocation of "pf" failed.',"init_nucstuff",320001)
51  end if
52 
53 end subroutine init_nucstuff
54 
55 !> Function to decide whether a given isotope is stable or not
56 !!
57 !! ### Example
58 !!~~~~~~~~~~~~~~.f90
59 !! b = is_stable(2,2)
60 !!~~~~~~~~~~~~~~
61 !! b will be true.
62 !!
63 !! @author M. Reichert
64 function is_stable(Z,N)
65  implicit none
66  integer, intent(in) :: z !< proton number
67  integer, intent(in) :: n !< neutron number
68  logical :: is_stable !< is the isotope stable?
69  integer :: i !< loop variable
70  integer,parameter :: numstable=253 !< number of stable isotopes
71  integer, dimension(numstable) :: nstable = &
72  (/ 0, 1, 1, 2, 3, 4, 5, 5, 6, 6, 7, 7, 8, 8, 9, 10, 10, 10, &
73  11, 12, 12, 12, 13, 14, 14, 14, 15, 16, 16, 16, 17, 18, 20, 18, 20, 18, &
74  20, 22, 20, 22, 20, 22, 23, 24, 26, 24, 24, 25, 26, 27, 28, 28, 26, 28, &
75  29, 30, 30, 28, 30, 31, 32, 32, 30, 32, 33, 34, 36, 34, 36, 34, 36, 37, &
76  38, 40, 38, 40, 38, 40, 41, 42, 42, 40, 42, 43, 44, 46, 44, 46, 42, 44, &
77  46, 47, 48, 50, 48, 46, 48, 49, 50, 50, 50, 51, 52, 54, 52, 50, 52, 53, &
78  54, 55, 56, 52, 54, 55, 56, 57, 58, 60, 58, 56, 58, 59, 60, 62, 64, 60, &
79  62, 58, 60, 62, 63, 64, 66, 64, 62, 64, 65, 66, 67, 68, 69, 70, 72, 74, &
80  70, 72, 68, 70, 71, 72, 73, 74, 74, 70, 72, 74, 75, 76, 77, 78, 80, 78, &
81  74, 76, 78, 79, 80, 81, 82, 82, 78, 80, 82, 84, 82, 82, 83, 85, 86, 88, &
82  82, 87, 88, 90, 92, 90, 90, 91, 92, 93, 94, 96, 94, 90, 92, 94, 95, 96, &
83  97, 98, 98, 94, 96, 98, 99, 100, 102, 100, 98, 100, 101, 102, 103, 104, 106, 104, &
84  104, 105, 106, 107, 108, 108, 108, 109, 110, 112, 110, 111, 112, 113, 114, 116, 114, 116, &
85  114, 116, 117, 118, 120, 118, 116, 118, 119, 120, 121, 122, 124, 122, 124, 122, 124, 125, &
86  126/)
87  integer, dimension(numstable) :: zstable = &
88  (/ 1, 1, 2, 2, 3, 3, 4, 5, 5, 6, 6, 7, 7, 8, 8, 8, 9, 10, 10, 10, 11, 12, 12, 12, &
89  13, 14, 14, 14, 15, 16, 16, 16, 16, 17, 17, 18, 18, 18, 19, 19, 20, 20, 20, 20, 20, 21, 22, 22, &
90  22, 22, 22, 23, 24, 24, 24, 24, 25, 26, 26, 26, 26, 27, 28, 28, 28, 28, 28, 29, 29, 30, 30, 30, &
91  30, 30, 31, 31, 32, 32, 32, 32, 33, 34, 34, 34, 34, 34, 35, 35, 36, 36, 36, 36, 36, 36, 37, 38, &
92  38, 38, 38, 39, 40, 40, 40, 40, 41, 42, 42, 42, 42, 42, 42, 44, 44, 44, 44, 44, 44, 44, 45, 46, &
93  46, 46, 46, 46, 46, 47, 47, 48, 48, 48, 48, 48, 48, 49, 50, 50, 50, 50, 50, 50, 50, 50, 50, 50, &
94  51, 51, 52, 52, 52, 52, 52, 52, 53, 54, 54, 54, 54, 54, 54, 54, 54, 55, 56, 56, 56, 56, 56, 56, &
95  56, 57, 58, 58, 58, 58, 59, 60, 60, 60, 60, 60, 62, 62, 62, 62, 62, 63, 64, 64, 64, 64, 64, 64, &
96  65, 66, 66, 66, 66, 66, 66, 66, 67, 68, 68, 68, 68, 68, 68, 69, 70, 70, 70, 70, 70, 70, 70, 71, &
97  72, 72, 72, 72, 72, 73, 74, 74, 74, 74, 75, 76, 76, 76, 76, 76, 77, 77, 78, 78, 78, 78, 78, 79, &
98  80, 80, 80, 80, 80, 80, 80, 81, 81, 82, 82, 82, 82 /)
99 
100  is_stable = .false.
101  if ((n .gt. maxval(nstable)) .or. (n .lt. minval(nstable))) then
102  is_stable = .false.
103  elseif ((z .gt. maxval(zstable)) .or. (z .lt. minval(zstable))) then
104  is_stable = .false.
105  else
106  do i=1,numstable
107  if ((n .eq. nstable(i)) .and. (z .eq. zstable(i))) then
108  is_stable = .true.
109  exit
110  end if
111  end do
112  end if
113 
114 end function is_stable
115 
116 
117 
118 
119 !>
120 !! @brief Calculates partition function
121 !!
122 !! The partition functions are interpolated from
123 !! the temperature grid (stored in \ref t9_data, read from the winvn in
124 !! \ref benam_class::get_nuclear_properties (index 1-24) and the htpf file
125 !! in \ref benam_class::read_htpf (index 25-72)) and the tabulated
126 !! partition functions \ref global_class::isotope\%part_func.
127 !!
128 !! \b Edited:
129 !! - MR : 19.01.2021 - set ntgp to 72
130 !! .
131 subroutine inter_partf (temp, interpol)
132  implicit none
133 
134  real(r_kind),intent(in) :: temp !< [in] temperature [GK]
135  real(r_kind),dimension(0:net_size),intent(out) :: interpol !< [out] partition function
136  !
137  integer :: i,k !< Loop variables
138  real(r_kind) :: grad !< Gradient
139  real(r_kind) :: lpfk, lpfkl !< log values of the partition functions at different indices
140 
141  interpol(0)=1.d0
142 
143  if (temp .gt. t9_data(ntgp)) then
144  k=ntgp+1
145  else
146  do k=1,ntgp
147  if (temp .le. t9_data(k)) exit
148  end do
149  end if
150 
151  if (k .eq. 1) then ! The input temperature is lower than the grid
152  do i=1,net_size
153  interpol(i) = isotope(i)%part_func(1)
154  end do
155  elseif (k .eq. ntgp+1) then ! The input temperature is hotter than the grid
156  do i=1,net_size
157  interpol(i) = isotope(i)%part_func(ntgp)
158  end do
159  else ! The input temperature lies in the grid
160  do i=1,net_size
161  lpfk = dlog(isotope(i)%part_func(k))
162  lpfkl = dlog(isotope(i)%part_func(k-1))
163  grad=(lpfk-lpfkl)/(t9_data(k)-t9_data(k-1))
164  interpol(i) = dexp(lpfkl + (temp-t9_data(k-1))*grad)
165  end do
166  end if
167 
168  return
169 end subroutine inter_partf
170 
171 
172 !>
173 !! A helper to compute powers of temperature used in the reaction rates
174 !!
175 !! The reaclib reaction rates are calculated with the following fit formula:
176 !! \f[
177 !! \lambda = \mathrm{exp} \left[ a_0 + \sum \limits _{i=1} ^5 a_i T_9 ^{\frac{2i-5}{3}} a_6 \, \mathrm{ln} T_9 \right].
178 !! \f]
179 !! The helper array \ref t9_pow stores the powers of the temperature used for this calculation
180 !! (starting with index 2 for i=1, index 1 stores unity). The \ref t9_pow array is after the call given
181 !! by \f[ \mathrm{t9\_pow} = [ T_9 ^{0}, T_9 ^{-1}, T_9 ^{-1/3}, T_9 ^{1/3}, T_9 ^{1},
182 !! T_9 ^{5/3}, \log T_9, T_9 ^{7/3}, T_9 ^{9/3} ] \f]
183 !!
184 !! @returns Array (\ref t9_pow) that contains the temperature with different exponents
185 !!
186 !! \b Edited:
187 !! - MR : 19.01.2021 - renamed subroutine and removed rho as input
188 !! .
189 subroutine calc_t9_pow(t9)
190  implicit none
191 
192  real(r_kind),intent(in) :: t9 !< Temperature [GK]
193 
194  t9_pow(1) = 1.d0 ! t9^(0)
195  t9_pow(2) = 1.d0/t9 ! t9^-1
196  t9_pow(4) = t9**(1.d0/3.d0) ! t9^(1/3)
197  t9_pow(3) = 1.d0/t9_pow(4) ! t9^(-1/3)
198  t9_pow(5) = t9 ! t9^(1)
199  t9_pow(6) = t9_pow(4)**5.d0 ! t9^(5/3)
200  t9_pow(7) = dlog(t9) ! log(t9)
201  t9_pow(8) = t9_pow(4)**7.d0 ! t9^(7/3)
202  t9_pow(9) = t9_pow(4)**9.d0 ! t9^(9/3)
203 
204 end subroutine calc_t9_pow
205 
206 
207 !>
208 !! Computes the electron fraction
209 !!
210 !! The electron fraction is defined as:
211 !! \f[ Y_e = \sum Z(i) \cdot Y(i) \f],
212 !! with the number of protons Z and the abundance Y
213 !! of each isotope i.
214 !!
215 !! \b Edited:
216 !! - MR : 19.01.2021
217 !! .
218 subroutine el_ab (Y, Ye)
219  implicit none
220 
221  real(r_kind),dimension(:),intent(in) :: y !< Abundances
222  real(r_kind),intent(out) :: ye !< Electron fraction
223 
224  ye= sum(isotope(1:net_size)%p_nr*y(1:net_size))
225 
226 end subroutine el_ab
227 
228 
229 
230 
231 !> Get the reaclib chapter based on nr. of prods. and educts.
232 !!
233 !! This function translates the number of educts and products
234 !! into the corresponding reaclib chapter.
235 !!
236 !! ### Example
237 !!~~~~~~~~~~~~~~.f90
238 !! b = get_chapter(2,2)
239 !!~~~~~~~~~~~~~~
240 !! b will be 5 afterwards.
241 !!
242 !! @Author M. Reichert
243 !! @date 01.08.22
244 function get_chapter(nr_react,nr_prod)
246  implicit none
247  integer,intent(in) :: nr_react !< Nr. reactants
248  integer,intent(in) :: nr_prod !< Nr. products
249  integer :: get_chapter !< Reaclib chapter
250 
251 
252  if ((nr_react .eq. 1) .and. (nr_prod .eq. 1)) then
253  get_chapter = 1
254  elseif ((nr_react .eq. 1) .and. (nr_prod .eq. 2)) then
255  get_chapter = 2
256  elseif ((nr_react .eq. 1) .and. (nr_prod .eq. 3)) then
257  get_chapter = 3
258  elseif ((nr_react .eq. 2) .and. (nr_prod .eq. 1)) then
259  get_chapter = 4
260  elseif ((nr_react .eq. 2) .and. (nr_prod .eq. 2)) then
261  get_chapter = 5
262  elseif ((nr_react .eq. 2) .and. (nr_prod .eq. 3)) then
263  get_chapter = 6
264  elseif ((nr_react .eq. 2) .and. (nr_prod .eq. 4)) then
265  get_chapter = 7
266  elseif ((nr_react .eq. 3) .and. (nr_prod .eq. 1)) then
267  get_chapter = 8
268  elseif ((nr_react .eq. 3) .and. (nr_prod .eq. 2)) then
269  get_chapter = 9
270  elseif ((nr_react .eq. 4) .and. (nr_prod .eq. 2)) then
271  get_chapter = 10
272  elseif ((nr_react .eq. 1) .and. (nr_prod .eq. 4)) then
273  get_chapter = 11
274  else
275  call raise_exception("Corresponding Reaclib chapter not known ("//&
276  "nr. educts: "//int_to_str(nr_react)//&
277  ", nr. products: "//int_to_str(nr_prod)//").",&
278  "get_nr_educts",320004)
279  end if
280 
281  return
282 end function get_chapter
283 
284 
285 
286 !> Get number of reactants of the reaction based on the reaclib chapter
287 !!
288 !! Returns the number of reactants in the reaction.
289 !!
290 !! ### Example
291 !!~~~~~~~~~~~~~~.f90
292 !! b = get_nr_reactants(2)
293 !!~~~~~~~~~~~~~~
294 !! b will be 1 afterwards.
295 !!
296 !! @see [Reaclib help](https://reaclib.jinaweb.org/help.php?topic=reaclib_format&intCurrentNum=0)
297 !!
298 !! @Author M. Reichert
299 !! @date 01.08.22
300 function get_nr_reactants(group)
302  implicit none
303  integer,intent(in) :: group !< Reaclib chapter
304  integer :: get_nr_reactants !< Amount of educts
305 
306  ! Default value
307  get_nr_reactants = 0
308 
309  select case(group)
310  case(1:3,11)
311  get_nr_reactants = 1
312  case(4:7)
313  get_nr_reactants = 2
314  case(8:9)
315  get_nr_reactants = 3
316  case(10)
317  get_nr_reactants = 4
318  case default
319  call raise_exception("Unknown Reaclib chapter ("//int_to_str(group)//").",&
320  "get_nr_reactants",320003)
321  end select
322 
323  return
324 end function get_nr_reactants
325 
326 
327 !> Get number of products of the reaction based on the reaclib chapter
328 !!
329 !! Returns the number of products in the reaction.
330 !!
331 !! ### Example
332 !!~~~~~~~~~~~~~~.f90
333 !! b = get_nr_products(2)
334 !!~~~~~~~~~~~~~~
335 !! b will be 2 afterwards.
336 !!
337 !! @warning Chapter 8 may return a different value in the original reaclib format.
338 !! There, reactions can also be chapter 9 reactions.
339 !!
340 !! @see [Reaclib help](https://reaclib.jinaweb.org/help.php?topic=reaclib_format&intCurrentNum=0)
341 !!
342 !! @Author M. Reichert
343 !! @date 01.08.22
344 function get_nr_products(group)
346  implicit none
347  integer,intent(in) :: group !< Reaclib chapter
348  integer :: get_nr_products !< Amount of educts
349 
350  ! Default value
351  get_nr_products = 0
352 
353  select case(group)
354  case(1,4,8)
355  get_nr_products = 1
356  case(2,5,9,10)
357  get_nr_products = 2
358  case(3,6)
359  get_nr_products = 3
360  case(7,11)
361  get_nr_products = 4
362  case default
363  call raise_exception("Unknown Reaclib chapter ("//int_to_str(group)//").",&
364  "get_nr_products",320003)
365  end select
366 
367  return
368 end function get_nr_products
369 
370 
371 
372 !> Total mass used to check the mass conservation
373 !!
374 !! This subroutine calculates
375 !! \f[ \mathrm{m\_tot} = \sum A_i \cdot Y_i \f]
376 !!
377 !! @note This subroutine used to calculate the neutron excess as well
378 !! and it can be commented in again.
379 !!
380 !! \b Edited:
381 !! - MR : 20.01.21 - Removed neutron excess
382 !! .
383 subroutine masscalc (Y, m_tot)
384  implicit none
385 
386  real(r_kind), dimension(:), intent(in) :: y !< Abundances
387  real(r_kind), intent(out) :: m_tot !< Sum of mass fractions
388  ! real(r_kind), intent(out), optional :: nexc
389  ! real(r_kind) :: m_p, m_n
390 
391  m_tot= sum(y(1:net_size)*isotope(1:net_size)%mass)
392  ! if(present(nexc)) then
393  ! m_p= sum(Y(1:net_size)*isotope(1:net_size)%p_nr)
394  ! m_n= sum(Y(1:net_size)*isotope(1:net_size)%n_nr)
395  ! nexc= (m_n - m_p)/m_tot
396  ! endif
397 end subroutine masscalc
398 
399 
400 
401 
402 !> Analyze a string and split it with delimiter ";"
403 !!
404 !! This routine is used to analyze the parameters
405 !! parameter_class::detailed_balance_src_ignore, parameter_class::detailed_balance_src_q_reac,
406 !! parameter_class::detailed_balance_src_q_winvn. It takes a string and splits it
407 !! if there is a ";" in it. Afterwards it returns an array with the splitted strings.
408 !!
409 !! ### Example
410 !!~~~~~~~~~~~~~~.f90
411 !! a = "rath; pkrF;abc"
412 !! b = "ths8"
413 !! call analyze_src_string(a,c,d)
414 !! call analyze_src_string(b,e,f)
415 !!~~~~~~~~~~~~~~
416 !! Afterwards, c will be an array containing (/"rath", "pkrF", " abc"/), d will be 3,
417 !! e will be (/"ths8"/), and f will be 1.
418 !!
419 !! @author M. Reichert
420 !! @date 04.08.22
421 subroutine analyze_src_string(input_string,output_array,length_output)
422  use parameter_class, only: max_fname_len
423  implicit none
424  character(len=max_fname_len),intent(in) :: input_string !< String with src to analyse, separated by ";"
425  character(len=4),dimension(:),allocatable,intent(out) :: output_array !< Array with sources
426  integer,intent(out) :: length_output!< Length of sources
427  ! Internal variables
428  integer :: i !< Loop variable
429  integer :: count !< helper variable
430  character(len=50) :: help_string !< helper variable
431  character,parameter :: delimiter = ";" !< Delimiter for separating sources
432 
433  info_entry("analyze_src_string")
434 
435  ! Do nothing for an empty string
436  if (trim(adjustl(input_string)) .eq. "") then
437  length_output = 0
438  allocate(output_array(1)) !TODO throw exception if allocation fails
439  output_array(:) = ""
440  return
441  end if
442 
443  ! Count the amount of source files given
444  length_output = 1
445  do i=1,max_fname_len
446  if (input_string(i:i) .eq. delimiter) length_output = length_output + 1
447  end do
448  ! Allocate
449  allocate(output_array(length_output)) !TODO throw exception if allocation fails
450 
451  help_string = ""
452  count = 0
453  do i=1,max_fname_len
454  if (input_string(i:i) .eq. delimiter) then
455  count = count + 1
456  output_array(count) = trim(adjustl(help_string))
457  output_array(count) = adjustr(output_array(count))
458  help_string = ""
459  else
460  help_string = trim(adjustl(help_string))//input_string(i:i)
461  end if
462  end do
463  output_array(count+1) = trim(adjustl(help_string))
464 
465  info_exit("analyze_src_string")
466 
467  return
468  end subroutine analyze_src_string
469 
470 
471 
472 
473 end module nucstuff_class
nucstuff_class::init_nucstuff
subroutine init_nucstuff()
Initialize nucstuff class.
Definition: nucstuff_class.f90:40
global_class::t9_data
real(r_kind), dimension(:), allocatable, public t9_data
temperatures at which partition functions are given [GK]
Definition: global_class.f90:97
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
nucstuff_class::pf
real(r_kind), dimension(:), allocatable, public pf
partition functions
Definition: nucstuff_class.f90:18
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
nucstuff_class::masscalc
subroutine, public masscalc(Y, m_tot)
Total mass used to check the mass conservation.
Definition: nucstuff_class.f90:384
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
nucstuff_class::ntgp
integer, public ntgp
(24/72) Number of temp grid points for the partition functions
Definition: nucstuff_class.f90:17
parameter_class::max_fname_len
integer, parameter, public max_fname_len
maximum length of filenames
Definition: parameter_class.f90:58
global_class::isotope
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
Definition: global_class.f90:34
nucstuff_class
Module with helper functions such as rate tabulation, partition functions, and theoretical weak rates...
Definition: nucstuff_class.f90:11
nucstuff_class::el_ab
subroutine, public el_ab(Y, Ye)
Computes the electron fraction.
Definition: nucstuff_class.f90:219
global_class::net_size
integer, public net_size
total number of isotopes (network size)
Definition: global_class.f90:93
nucstuff_class::is_stable
logical function, public is_stable(Z, N)
Function to decide whether a given isotope is stable or not.
Definition: nucstuff_class.f90:65
r_kind
#define r_kind
Definition: macros.h:46
nucstuff_class::analyze_src_string
subroutine, public analyze_src_string(input_string, output_array, length_output)
Analyze a string and split it with delimiter ";".
Definition: nucstuff_class.f90:422
nucstuff_class::get_nr_reactants
integer function get_nr_reactants(group)
Get number of reactants of the reaction based on the reaclib chapter.
Definition: nucstuff_class.f90:301
nucstuff_class::t9_pow
real(r_kind), dimension(9), public t9_pow
Powers of T, used for the rates.
Definition: nucstuff_class.f90:15
nucstuff_class::inter_partf
subroutine, public inter_partf(temp, interpol)
Calculates partition function.
Definition: nucstuff_class.f90:132
global_class
Contains types and objects shared between multiple modules.
Definition: global_class.f90:19
nucstuff_class::get_chapter
integer function get_chapter(nr_react, nr_prod)
Get the reaclib chapter based on nr. of prods. and educts.
Definition: nucstuff_class.f90:245
nucstuff_class::calc_t9_pow
subroutine, public calc_t9_pow(t9)
A helper to compute powers of temperature used in the reaction rates.
Definition: nucstuff_class.f90:190
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
nucstuff_class::get_nr_products
integer function get_nr_products(group)
Get number of products of the reaction based on the reaclib chapter.
Definition: nucstuff_class.f90:345