alpha_decay_rate_module.f90
Go to the documentation of this file.
1 !> @file alpha_decay_rate_module.f90
2 !!
3 !! The error file code for this file is ***W46***.
4 !! Contains the module \ref alpha_decay_rate_module.
5 
6 
7 !>
8 !! @brief This module contains subroutines to add alpha decays
9 !!
10 !! The alpha decays given by an external file. The default file in WinNet uses a file that has been
11 !! calculated using the Viola-Seaborg formula. Hereby, a parameterization of the alpha-decay half life
12 !! of [Dong & Ren 2005](https://ui.adsabs.harvard.edu/abs/2005EPJA...26...69D/abstract) was used.
13 !! Via the Viola-Seaborg formula it is possible to calculate alpha-decay half lifes by knowing only the Qvalue of the
14 !! alpha decay. Within this model, reaclib rates can get replaced or additional alpha-decay rates can be added.
15 !!
16 !! @author Moritz Reichert
17 !! @date 10.03.23
18 #include "macros.h"
21  implicit none
22 
23  type(reactionrate_type),dimension(:),allocatable,private :: alpha_dec_rate !< Array storing the reaction rates
24  integer,private :: nalpha_dec !< Number of alpha decays
25  logical,private :: include_alpha_decays !< Flag whether alpha decays should be included or not
26 
27  ! Helper variables for ignoring specific sources
28  character(len=4),allocatable,dimension(:),private :: src_ignore
29  integer,private :: src_ignore_length
30 
31  character(15), private, parameter :: fileformat="(A5,3X,1pE11.5)"
32 
33  !
34  ! Public and private fields and methods of the module
35  !
36  public:: &
38 
39  private:: &
41 
42 
43 contains
44 
45 
46  !> Initialize alpha decay rates.
47  !!
48  !! This subroutine counts and reads the rates into the array
49  !! \ref beta_decays.
50  !!
51  !! @author M. Reichert
52  !! @date 25.01.21
58  implicit none
59  integer :: beta_unit !< File ID of external beta decay file
60  integer :: alloc_stat !< Allocation status
61 
62  if (.not. use_prepared_network) then
63  if (use_alpha_decay_file) then
64  ! Alpha decays will be used
65  include_alpha_decays = .true.
66 
67  ! Check if some reactions should not get replaced
69 
70  ! Count the amount of possible alpha decays to be added
72 
73  ! Create an array with alpha decays
75 
76  ! Say how many there were
77  if (verbose_level .ge. 1) then
78  call write_data_to_std_out("Amount alpha-decay format rates",int_to_str(nalpha_dec))
79  end if
80 
81  end if
82  end if
83 
84  end subroutine init_alpha_decay_rates
85 
86 
87  !> Creates a file with the decays
88  !!
89  !! This file is created for verbose_levels greater than 2. An example
90  !! could look like
91  !! \file{
92  !! Alpha decay rates that additionally have been added
93  !! po181 => he4 + pb177 T_1/2: 1.49E-09 s; a0: 2.00E+01 Qa: 1.02E+01
94  !! po182 => he4 + pb178 T_1/2: 3.89E-09 s; a0: 1.90E+01 Qa: 9.56E+00
95  !! ..
96  !! }
97  !! @author M. Reichert
98  !! @date 10.03.23
99  subroutine create_verbose_output_file(alpha_decay_rates,nalpha)
101  implicit none
102  type(reactionrate_type),dimension(:),intent(in) :: alpha_decay_rates !< Array storing the reaction rates
103  integer,intent(in) :: nalpha !< Number of alpha decays
104  ! Internal variables
105  integer :: i !< Loop variable
106  integer :: alpha_unit !< File ID of external alpha decay file
107 
108  ! Open the file
109  alpha_unit= open_outfile("debug_alpha_decay_rates.txt")
110 
111  ! Write the header
112  write(alpha_unit,*) "Alpha decay rates that additionally have been added"
113  write(alpha_unit,*)
114  ! Write the header
115  do i=1,nalpha
116  write(alpha_unit,"(A)") reaction_string(alpha_decay_rates(i))
117  end do
118 
119  end subroutine create_verbose_output_file
120 
121 
122  !>
123  !! @brief Return a string to represent a given reaction
124  !!
125  !! This routine is useful for error messages in case
126  !! a rate is not working as intented and is used for
127  !! verbose output only.
128  !!
129  !! ### Example
130  !! For rrate(i) being the alpha-decay of po181
131  !! ~~~~~~~~~~~.f90
132  !! a = reaction_string(rrate(i))
133  !! ~~~~~~~~~~~
134  !! will return a="po181 => he4 + pb177 T_1/2: 1.49E-09 s; a0: 2.00E+01 Qa: 1.02E+01".
135  !!
136  !! @author Moritz Reichert
137  function reaction_string(reac)
139  use error_msg_class, only: num_to_str
140  use benam_class, only: get_net_name
141  implicit none
142  type(reactionrate_type),intent(in) :: reac
143  character(150) :: reaction_string
144  integer :: i
145  real(r_kind) :: a0
146  logical :: s_prod
147 
148  reaction_string = trim(adjustl(net_names(reac%parts(1))))
149 
150  do i =2, 6
151  s_prod = .false.
152  ! Make a cut between educts and products
153  select case(reac%group)
154  case(1:3,11)
155  if (i .eq. 2) then
156  reaction_string = trim(adjustl(reaction_string))//" =>"
157  s_prod = .true.
158  end if
159  case(4:7)
160  if (i .eq. 3) then
161  reaction_string = trim(adjustl(reaction_string))//" =>"
162  s_prod = .true.
163  end if
164  case(8:9)
165  if (i .eq. 4) then
166  reaction_string = trim(adjustl(reaction_string))//" =>"
167  s_prod = .true.
168  end if
169  case(10)
170  if (i .eq. 5) then
171  reaction_string = trim(adjustl(reaction_string))//" =>"
172  s_prod = .true.
173  end if
174  end select
175 
176  ! Write the names of the isotopes
177  if (reac%parts(i) .ne. 0) then
178  if (.not. s_prod) then
179  reaction_string = trim(adjustl(reaction_string))//" + "//&
180  get_net_name(reac%parts(i))
181  else
182  reaction_string = trim(adjustl(reaction_string))//" "//&
183  get_net_name(reac%parts(i))
184  end if
185  end if
186 
187  end do
188  ! Add half life and reaclib parameter
189  a0 = reac%param(1)
190  reaction_string = trim(adjustl(reaction_string))//" T_1/2: "//num_to_str(dlog(2.0d0)/dexp(a0))//" s; a0: "//num_to_str(a0)//" Qa: "//num_to_str(reac%q_value)
191 
192  return
193  end function reaction_string
194 
195 
196  !> Merge alpha decays into the larger rate array.
197  !!
198  !! The return value of this routine will be a larger rate array
199  !! and a new length
200  !!
201  !! @author M. Reichert
202  !! @date 25.01.21
203  subroutine merge_alpha_decays(rrate_array,rrate_length)
207  implicit none
208  type(reactionrate_type),dimension(:),allocatable,intent(inout) :: rrate_array !< Large rate array, containing all reactions
209  integer,intent(inout) :: rrate_length !< length of rrate_array
210  integer :: alloc_stat !< Allocation state
211  type(reactionrate_type),dimension(:),allocatable :: helper !< Large rate array, containing all reactions
212  integer :: new_length !< new length of the array
213 
214 
215  if (.not. use_prepared_network) then
216  if (include_alpha_decays) then
217  ! Only merge if there are rates to be added
218  if (nalpha_dec .ne. 0) then
219  ! No reaclib rates are present, create the rate array only with alpha decays
220  if (.not. allocated(rrate_array)) then
221 
222  rrate_length = nalpha_dec
223  !-- Allocate the reaclib rate array
224  allocate(rrate_array(nalpha_dec),stat=alloc_stat)
225  if ( alloc_stat /= 0) call raise_exception('Allocation of "rrate_array" failed.',&
226  "merge_alpha_decays",&
227  460001)
228  rrate_array(1:nalpha_dec) = alpha_dec_rate(1:nalpha_dec)
229  else
230  ! Merge the rates as you desire
231  call unify_rate_array(rrate_array,alpha_dec_rate,helper,rrate_length,nalpha_dec,new_length)
232  ! Deallocate the array and allocate with new size
233  deallocate(rrate_array,stat=alloc_stat)
234  if ( alloc_stat /= 0) call raise_exception('Deallocation of "rrate_array" failed.',&
235  "merge_alpha_decays",&
236  460002)
237 
238  allocate(rrate_array(new_length),stat=alloc_stat)
239  if ( alloc_stat /= 0) call raise_exception('Allocation of "rrate_array" failed.',&
240  "merge_alpha_decays",&
241  460001)
242 
243  rrate_array(1:new_length) = helper(1:new_length)
244  rrate_length = new_length
245 
246  ! Now helper array can be deallocated
247  deallocate(helper,stat=alloc_stat)
248  if ( alloc_stat /= 0) call raise_exception('Deallocation of "helper" failed.',&
249  "merge_alpha_decays",&
250  460002)
251  end if
252 
253  ! Deallocate the alpha decay array to clean memory
254  deallocate(alpha_dec_rate,stat=alloc_stat)
255  if ( alloc_stat /= 0) call raise_exception('Deallocation of "alpha_dec_rate" failed.',&
256  "merge_alpha_decays",&
257  460002)
258  end if
259 
260  end if
261  end if
262 
263  end subroutine merge_alpha_decays
264 
265 
266  !> Merge reaclib rates and alpha decays into one array.
267  !!
268  !! Hereby the rates can be taken as addition or also replace the reaclib rates.
269  !!
270  !! @author M. Reichert
271  !! @date 25.01.21
272  subroutine unify_rate_array(rrate_array,alpha_dec_rate_array,merged_array,nrrate,nalpha,ntot)
273  use global_class, only: ihe4,isotope
274  use benam_class, only: findaz
277  implicit none
278  ! Declare the input
279  type(reactionrate_type),dimension(nrrate),intent(inout) :: rrate_array !< Reaclib rates
280  type(reactionrate_type),dimension(nalpha),intent(inout) :: alpha_dec_rate_array !< Alpha decay rates
281  type(reactionrate_type),dimension(:),allocatable,intent(out) :: merged_array !< Combined, merged array
282  integer,intent(in) :: nrrate !< Length of rrate_array
283  integer,intent(in) :: nalpha !< Length of alpha_dec_rate_array
284  integer,intent(out) :: ntot !< Length of merged_array
285  ! Internal variables
286  integer :: i, j !< Loop variable
287  logical, dimension(nrrate) :: mask_rrate !< Mask for rrate_array
288  logical, dimension(nalpha) :: mask_alpha !< Mask for alpha_dec_rate_array
289  integer :: replace_reaclib !< Number of replaced reaclib rates
290  integer :: replace_alpha !< Number of removed alpha decays
291  integer :: alloc_stat !< Allocation status variable
292  integer :: ztmp !< proton number
293  integer :: atmp !< mass number
294  integer :: daughter !< index of daughter nucleus
295 
296  ! Create masks for both arrays
297  mask_rrate(:) = .true.
298  mask_alpha(:) = .true.
299 
300  ! Keep track how many rates got replaced
301  replace_reaclib = 0
302  replace_alpha = 0
303 
304  do i=1,nrrate
305  ! Alpha decays are chapter 2, weak, and have an alpha in the products
306  if (rrate_array(i)%group .ne. 2) cycle
307  if (.not. rrate_array(i)%is_weak) cycle
308  if (.not. ((rrate_array(i)%parts(2) .eq. ihe4) .or. (rrate_array(i)%parts(3) .eq. ihe4))) cycle
309 
310  ! Also check if it is not an beta delayed alpha-decay
311  if (rrate_array(i)%parts(2) .eq. ihe4) then
312  ! Daughter is the second particle
313  daughter = rrate_array(i)%parts(3)
314  else
315  ! Daughter is the first particle
316  daughter = rrate_array(i)%parts(2)
317  end if
318 
319  if (isotope(daughter)%p_nr .ne. isotope(rrate_array(i)%parts(1))%p_nr-2) then
320  ! It is a beta delayed alpha decay
321  cycle
322  end if
323 
324  ! Check which rate has to be replaced for this reaction
325  if ((any(src_ignore .eq. adjustr(rrate_array(i)%source))) .or. (alpha_decay_ignore_all)) then
326  inner_loop: do j = 1,nalpha
327  if (rrate_array(i)%parts(1) .eq. alpha_dec_rate_array(j)%parts(1)) then
328  ! The same reaction is present in both arrays, remove the alpha rate here
329  mask_alpha(j) = .false.
330  replace_alpha = replace_alpha + 1
331  exit inner_loop
332  end if
333  end do inner_loop
334  else
335  ! Reaclib alpha decay rate is replaced by the alpha decay rate here
336  mask_rrate(i) = .false.
337  replace_reaclib = replace_reaclib + 1
338  end if
339  end do
340 
341  ! Total amount of reactions
342  ntot = nrrate + nalpha - replace_alpha - replace_reaclib
343  allocate(merged_array(ntot),stat=alloc_stat)
344  if (alloc_stat /= 0) call raise_exception("Allocation of 'merged_array' failed.",&
345  "unify_rate_array",&
346  460001)
347 
348  ! Write things to the merged array
349  merged_array(1:nrrate-replace_reaclib) = pack(rrate_array(1:nrrate),mask_rrate)
350  merged_array(nrrate-replace_reaclib+1:ntot) = pack(alpha_dec_rate_array(1:nalpha),mask_alpha)
351 
352  ! Say something
353  if (verbose_level .ge. 2) then
354  call write_data_to_std_out("Amount alpha decays replaced in Reaclib",int_to_str(replace_reaclib))
355  call write_data_to_std_out("Amount alpha decays replaced in V.S. eq.",int_to_str(replace_alpha))
356  end if
357  ! Write a file with the rates used
358  if (verbose_level .ge. 3) then
359  call create_verbose_output_file(pack(alpha_dec_rate_array(1:nalpha),mask_alpha),nalpha - replace_alpha)
360  end if
361 
362  end subroutine unify_rate_array
363 
364 
365  !> Count the amount of possible alpha decays
366  !!
367  !! Check which isotopes between \ref alpha_decay_zmin and \ref alpha_decay_zmax should
368  !! have an alpha decay.
369  !!
370  !! @author M. Reichert
371  !! @date 10.03.23
372  subroutine count_reactions(n)
373  use global_class, only: isotope
376  use benam_class, only: findaz, benam
378  implicit none
379  integer,intent(out) :: n !< Number of possible alpha decays
380  integer :: i !< Loop variable
381  integer :: idx_daughter !< Index of daughter
382  integer :: idx_parent !< Index of parent
383  integer :: n_tmp !< Number of neutrons
384  integer :: z_tmp !< Number of protons
385  integer :: file_id !< File id
386  logical :: include_rate !< Flag if the decay should be included
387  character(5) :: nametmp !< Name of the isotope
388  real(r_kind) :: thalf !< Half life of the isotope
389  integer :: read_stat !< Read status variable
390 
391  ! Reset the counter
392  n = 0
393  ! Open the file
394  file_id = open_infile(alpha_decay_file)
395 
396  ! Read the file
397  loop: do
398  read(file_id,fileformat, iostat = read_stat) nametmp, thalf
399  if (read_stat /= 0) exit loop
400 
401  ! Skip nuclei that are not included
402  idx_parent = benam(nametmp)
403  if (idx_parent .eq. 0) cycle loop
404  ! Skip nuclei that are not in desired Z range
405  if ((isotope(idx_parent)%p_nr .lt. alpha_decay_zmin) .and. (isotope(idx_parent)%p_nr .gt. alpha_decay_zmax)) cycle loop
406  idx_daughter = findaz(isotope(idx_parent)%mass-4,isotope(idx_parent)%p_nr-2)
407  ! Skip nuclei if the daughter is not included
408  if (idx_daughter .le. 0) cycle loop
409  ! Increase amount of reactions
410  n = n+1
411 
412  end do loop
413 
414  ! Close the fileagain
415  close(file_id)
416 
417  end subroutine count_reactions
418 
419 
420 
421  !> Read the alpha decays
422  !!
423  !! All isotopes between \ref alpha_decay_zmin and \ref alpha_decay_zmax should
424  !! have an alpha decay. This subroutine reads the file \ref alpha_decay_file
425  !! and creates the alpha decay rate array.
426  !! An example of the file could look like:
427  !! \file{
428  !! sb103 7.84058e+10
429  !! sb104 4.29655e+05
430  !! sb105 1.37511e+10
431  !! sb106 1.03780e+17
432  !! te103 8.30806e+02
433  !! ...
434  !! }
435  !!
436  !! @author M. Reichert
437  !! @date 14.03.23
438  subroutine read_reactions(alpha_rate_array,n)
439  use global_class, only: isotope,net_size,ihe4
445  implicit none
446  type(reactionrate_type),dimension(:),allocatable, intent(out) :: alpha_rate_array ! Alpha decay rate array
447  integer,intent(in) :: n !< Length of the rates
448  integer :: counter !< Counter
449  integer :: idx_daughter !< Index of daughter nucleus
450  integer :: n_tmp !< Number of neutrons
451  integer :: z_tmp !< Number of protons
452  real(r_kind) :: mexc_alpha !< Mass excess of alpha particle
453  real(r_kind) :: mexc_daughter!< Mass excess of daughter
454  real(r_kind) :: mexc_parent !< Mass excess of parent
455  real(r_kind) :: qa !< Q-value of alpha decay [MeV]
456  real(r_kind) :: a0_tmp !< Reaclib a0 parameter
457  real(r_kind) :: thalf !< Half life of the isotope
458  integer :: file_id !< File id
459  integer :: read_stat !< Read status variable
460  integer :: alloc_stat !< Allocation status variable
461  character(5) :: nametmp !< Name of the isotope
462  integer :: idx_parent !< Index of parent
463  logical :: include_rate !< Flag if the decay should be included or was problematic
464  type(reactionrate_type) :: rrate_tmp !< Temporary reaction rate
465 
466 
467  ! Allocate the array
468  allocate(alpha_rate_array(n),stat=alloc_stat)
469  if ( alloc_stat /= 0) call raise_exception('Allocation of "alpha_rate_array" failed',&
470  "read_reactions",&
471  460001)
472  ! Initialize the counter
473  counter = 1
474  ! Get mass excess of alpha particle
475  mexc_alpha = isotope(ihe4)%mass_exc
476 
477  ! Open the file
478  file_id = open_infile(alpha_decay_file)
479 
480  ! Read the file
481  loop: do
482  read(file_id,fileformat, iostat = read_stat) nametmp, thalf
483  if (read_stat /= 0) exit loop
484 
485  idx_parent = benam(nametmp)
486  ! Skip nuclei that are not included
487  if (idx_parent .eq. 0) cycle loop
488  ! Skip nuclei that are not in desired Z range
489  if ((isotope(idx_parent)%p_nr .lt. alpha_decay_zmin) .and. (isotope(idx_parent)%p_nr .gt. alpha_decay_zmax)) cycle loop
490  idx_daughter = findaz(isotope(idx_parent)%mass-4,isotope(idx_parent)%p_nr-2)
491  ! Skip nuclei if the daughter is not included
492  if (idx_daughter .le. 0) cycle loop
493 
494  ! Calculate the Q-value
495  mexc_daughter = isotope(idx_daughter)%mass_exc
496  mexc_parent = isotope(idx_parent)%mass_exc
497  qa = mexc_parent-mexc_daughter-mexc_alpha
498  ! Also save the numbers of neutrons and protons
499  n_tmp = isotope(idx_parent)%n_nr
500  z_tmp = isotope(idx_parent)%p_nr
501 
502  ! Calculate a0 parameter
503  a0_tmp = dlog((dlog(2.0d0)/(thalf)))
504 
505  ! Get the rate
506  rrate_tmp%parts(:) = 0 ! Initialize first with zero
507  rrate_tmp%source = "aext" ! Added alpha-decay
508  rrate_tmp%is_reverse = .false.
509  rrate_tmp%cached = -1
510  rrate_tmp%is_resonant = .false.
511  rrate_tmp%is_weak = .true.
512  rrate_tmp%is_const = .true.
513  rrate_tmp%q_value = qa ! Set the Qvalue
514  rrate_tmp%reac_src = rrs_aext ! Remember that this is an added alpha-decay
515  rrate_tmp%reac_type = rrt_alpd ! It's an alpha decay
516  rrate_tmp%one_over_n_fac = 1.0d0
517  rrate_tmp%group = 2 ! Alpha decays are in chapter 2
518  rrate_tmp%parts(1) = idx_parent ! parent nucleus index
519  rrate_tmp%parts(2) = ihe4 ! alpha index
520  rrate_tmp%parts(3) = idx_daughter ! daughter nucleus index
521  rrate_tmp%param(:) = 0 ! Reset parameter
522  rrate_tmp%param(1) = a0_tmp ! a0 parameter as calculated
523  rrate_tmp%nu_frac = 0 ! Fraction radiated away by neutrinos
524  ! Save the rate and increase the counter for the next rate
525  alpha_rate_array(counter) = rrate_tmp
526  counter = counter + 1
527  end do loop
528 
529  ! Make coefficients right
530  call getcoefficients(alpha_rate_array,n)
531 
532  end subroutine read_reactions
533 
534 
535 end module alpha_decay_rate_module
alpha_decay_rate_module::unify_rate_array
subroutine, private unify_rate_array(rrate_array, alpha_dec_rate_array, merged_array, nrrate, nalpha, ntot)
Merge reaclib rates and alpha decays into one array.
Definition: alpha_decay_rate_module.f90:273
parameter_class::use_prepared_network
logical use_prepared_network
Use a prepared folder with all necessary data in binary format.
Definition: parameter_class.f90:94
global_class::net_names
character *5, dimension(:), allocatable, public net_names
list of isotopes contained in the network
Definition: global_class.f90:95
global_class::reactionrate_type
reaction rate type
Definition: global_class.f90:44
benam_class::findaz
integer function, public findaz(ai, zi)
Finds an isotope index in the network table, given its A and Z. In case it was not found,...
Definition: benam_class.f90:887
parameter_class::alpha_decay_zmin
integer alpha_decay_zmin
Minimum Z for additional alpha decay rates.
Definition: parameter_class.f90:77
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
global_class::ihe4
integer, public ihe4
Definition: global_class.f90:94
benam_class::benam
integer function, public benam(name)
Returns the index number of isotope 'name'.
Definition: benam_class.f90:251
alpha_decay_rate_module::merge_alpha_decays
subroutine, public merge_alpha_decays(rrate_array, rrate_length)
Merge alpha decays into the larger rate array.
Definition: alpha_decay_rate_module.f90:204
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
rrs_aext
#define rrs_aext
Definition: macros.h:56
alpha_decay_rate_module
This module contains subroutines to add alpha decays.
Definition: alpha_decay_rate_module.f90:19
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
mergesort_module::rrate_ms
subroutine, public rrate_ms(x, xs, y, ys, r, ptz, rate_out)
Merges two tables of rates (of type global_class::reactionrate_type).
Definition: mergesort_module.f90:227
parameter_class::use_alpha_decay_file
logical use_alpha_decay_file
Switch for using additional alpha decay rates.
Definition: parameter_class.f90:76
global_class::isotope
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
Definition: global_class.f90:34
alpha_decay_rate_module::count_reactions
subroutine, private count_reactions(n)
Count the amount of possible alpha decays.
Definition: alpha_decay_rate_module.f90:373
error_msg_class::write_data_to_std_out
subroutine, public write_data_to_std_out(str_msg, value_str, unit)
Write data to the standard output (usually OUT)
Definition: error_msg_class.f90:122
alpha_decay_rate_module::src_ignore
character(len=4), dimension(:), allocatable, private src_ignore
Definition: alpha_decay_rate_module.f90:28
nucstuff_class
Module with helper functions such as rate tabulation, partition functions, and theoretical weak rates...
Definition: nucstuff_class.f90:11
rrt_alpd
#define rrt_alpd
Definition: macros.h:62
parameter_class::alpha_decay_file
character(max_fname_len) alpha_decay_file
File with additional alpha decays.
Definition: parameter_class.f90:182
parameter_class::alpha_decay_zmax
integer alpha_decay_zmax
Maximum Z for additional alpha decay rates.
Definition: parameter_class.f90:78
mergesort_module::rrate_sort
subroutine, public rrate_sort(num, rate_array)
Sorts chapter one of the rate array.
Definition: mergesort_module.f90:676
global_class::net_size
integer, public net_size
total number of isotopes (network size)
Definition: global_class.f90:93
alpha_decay_rate_module::src_ignore_length
integer, private src_ignore_length
Definition: alpha_decay_rate_module.f90:29
file_handling_class
Provide some basic file-handling routines.
Definition: file_handling_class.f90:18
error_msg_class::num_to_str
character(:) function, allocatable, public num_to_str(num)
Converts a given real to a string with format "(1pE10.2)".
Definition: error_msg_class.f90:205
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
alpha_decay_rate_module::fileformat
character(15), parameter, private fileformat
Definition: alpha_decay_rate_module.f90:31
file_handling_class::open_infile
integer function, public open_infile(file_name)
Same for reading (input file)
Definition: file_handling_class.f90:126
alpha_decay_rate_module::alpha_dec_rate
type(reactionrate_type), dimension(:), allocatable, private alpha_dec_rate
Array storing the reaction rates.
Definition: alpha_decay_rate_module.f90:23
file_handling_class::open_outfile
integer function, public open_outfile(file_name)
Shorthand for opening a new file for writing (output file)
Definition: file_handling_class.f90:108
global_class
Contains types and objects shared between multiple modules.
Definition: global_class.f90:19
benam_class::get_net_name
character(:) function, allocatable, public get_net_name(index, trimmed)
Getter of net_names, translating indices to a nucleus name.
Definition: benam_class.f90:280
parameter_class::alpha_decay_src_ignore
character(max_fname_len) alpha_decay_src_ignore
Source flag(s) to ignore within the alpha decay rates.
Definition: parameter_class.f90:79
parameter_class::alpha_decay_ignore_all
logical alpha_decay_ignore_all
Flag whether rates should actually get replaced or only added.
Definition: parameter_class.f90:80
alpha_decay_rate_module::include_alpha_decays
logical, private include_alpha_decays
Flag whether alpha decays should be included or not.
Definition: alpha_decay_rate_module.f90:25
alpha_decay_rate_module::init_alpha_decay_rates
subroutine, public init_alpha_decay_rates()
Initialize alpha decay rates.
Definition: alpha_decay_rate_module.f90:54
mergesort_module
Module mergesort_module for merging arrays of rates.
Definition: mergesort_module.f90:16
alpha_decay_rate_module::create_verbose_output_file
subroutine, private create_verbose_output_file(alpha_decay_rates, nalpha)
Creates a file with the decays.
Definition: alpha_decay_rate_module.f90:100
alpha_decay_rate_module::read_reactions
subroutine, private read_reactions(alpha_rate_array, n)
Read the alpha decays.
Definition: alpha_decay_rate_module.f90:439
alpha_decay_rate_module::nalpha_dec
integer, private nalpha_dec
Number of alpha decays.
Definition: alpha_decay_rate_module.f90:24
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
benam_class::getcoefficients
subroutine, public getcoefficients(rate_array, length_rate_array)
Returns the 1/n! factor where n is the number of equal isotopes entering a reaction....
Definition: benam_class.f90:307
alpha_decay_rate_module::reaction_string
character(150) function, private reaction_string(reac)
Return a string to represent a given reaction.
Definition: alpha_decay_rate_module.f90:138
benam_class
Subroutines needed to initialise the network.
Definition: benam_class.f90:11