Go to the documentation of this file.
28 character(len=4),
allocatable,
dimension(:),
private ::
src_ignore
31 character(15),
private,
parameter ::
fileformat=
"(A5,3X,1pE11.5)"
77 if (verbose_level .ge. 1)
then
78 call write_data_to_std_out(
"Amount alpha-decay format rates",int_to_str(
nalpha_dec))
103 integer,
intent(in) :: nalpha
106 integer :: alpha_unit
112 write(alpha_unit,*)
"Alpha decay rates that additionally have been added"
153 select case(reac%group)
177 if (reac%parts(i) .ne. 0)
then
178 if (.not. s_prod)
then
209 integer,
intent(inout) :: rrate_length
210 integer :: alloc_stat
212 integer :: new_length
220 if (.not.
allocated(rrate_array))
then
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",&
233 deallocate(rrate_array,stat=alloc_stat)
234 if ( alloc_stat /= 0)
call raise_exception(
'Deallocation of "rrate_array" failed.',&
235 "merge_alpha_decays",&
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",&
243 rrate_array(1:new_length) = helper(1:new_length)
244 rrate_length = new_length
247 deallocate(helper,stat=alloc_stat)
248 if ( alloc_stat /= 0)
call raise_exception(
'Deallocation of "helper" failed.',&
249 "merge_alpha_decays",&
255 if ( alloc_stat /= 0)
call raise_exception(
'Deallocation of "alpha_dec_rate" failed.',&
256 "merge_alpha_decays",&
272 subroutine unify_rate_array(rrate_array,alpha_dec_rate_array,merged_array,nrrate,nalpha,ntot)
282 integer,
intent(in) :: nrrate
283 integer,
intent(in) :: nalpha
284 integer,
intent(out) :: ntot
287 logical,
dimension(nrrate) :: mask_rrate
288 logical,
dimension(nalpha) :: mask_alpha
289 integer :: replace_reaclib
290 integer :: replace_alpha
291 integer :: alloc_stat
297 mask_rrate(:) = .true.
298 mask_alpha(:) = .true.
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
311 if (rrate_array(i)%parts(2) .eq.
ihe4)
then
313 daughter = rrate_array(i)%parts(3)
316 daughter = rrate_array(i)%parts(2)
319 if (
isotope(daughter)%p_nr .ne.
isotope(rrate_array(i)%parts(1))%p_nr-2)
then
326 inner_loop:
do j = 1,nalpha
327 if (rrate_array(i)%parts(1) .eq. alpha_dec_rate_array(j)%parts(1))
then
329 mask_alpha(j) = .false.
330 replace_alpha = replace_alpha + 1
336 mask_rrate(i) = .false.
337 replace_reaclib = replace_reaclib + 1
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.",&
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)
353 if (verbose_level .ge. 2)
then
358 if (verbose_level .ge. 3)
then
379 integer,
intent(out) :: n
381 integer :: idx_daughter
382 integer :: idx_parent
386 logical :: include_rate
387 character(5) :: nametmp
398 read(file_id,
fileformat, iostat = read_stat) nametmp, thalf
399 if (read_stat /= 0)
exit loop
402 idx_parent =
benam(nametmp)
403 if (idx_parent .eq. 0) cycle loop
408 if (idx_daughter .le. 0) cycle loop
446 type(
reactionrate_type),
dimension(:),
allocatable,
intent(out) :: alpha_rate_array
447 integer,
intent(in) :: n
449 integer :: idx_daughter
452 real(
r_kind) :: mexc_alpha
453 real(
r_kind) :: mexc_daughter
454 real(
r_kind) :: mexc_parent
460 integer :: alloc_stat
461 character(5) :: nametmp
462 integer :: idx_parent
463 logical :: include_rate
468 allocate(alpha_rate_array(n),stat=alloc_stat)
469 if ( alloc_stat /= 0)
call raise_exception(
'Allocation of "alpha_rate_array" failed',&
482 read(file_id,
fileformat, iostat = read_stat) nametmp, thalf
483 if (read_stat /= 0)
exit loop
485 idx_parent =
benam(nametmp)
487 if (idx_parent .eq. 0) cycle loop
492 if (idx_daughter .le. 0) cycle loop
495 mexc_daughter =
isotope(idx_daughter)%mass_exc
496 mexc_parent =
isotope(idx_parent)%mass_exc
497 qa = mexc_parent-mexc_daughter-mexc_alpha
499 n_tmp =
isotope(idx_parent)%n_nr
500 z_tmp =
isotope(idx_parent)%p_nr
503 a0_tmp = dlog((dlog(2.0d0)/(thalf)))
506 rrate_tmp%parts(:) = 0
507 rrate_tmp%source =
"aext"
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
516 rrate_tmp%one_over_n_fac = 1.0d0
518 rrate_tmp%parts(1) = idx_parent
519 rrate_tmp%parts(2) =
ihe4
520 rrate_tmp%parts(3) = idx_daughter
521 rrate_tmp%param(:) = 0
522 rrate_tmp%param(1) = a0_tmp
523 rrate_tmp%nu_frac = 0
525 alpha_rate_array(counter) = rrate_tmp
526 counter = counter + 1
535 end module alpha_decay_rate_module
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.
logical use_prepared_network
Use a prepared folder with all necessary data in binary format.
character *5, dimension(:), allocatable, public net_names
list of isotopes contained in the network
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,...
integer alpha_decay_zmin
Minimum Z for additional alpha decay rates.
integer function, public benam(name)
Returns the index number of isotope 'name'.
subroutine, public merge_alpha_decays(rrate_array, rrate_length)
Merge alpha decays into the larger rate array.
character(:) function, allocatable, public int_to_str(num)
Converts a given integer to a string.
This module contains subroutines to add alpha decays.
subroutine, public raise_exception(msg, sub, error_code)
Raise a exception with a given error message.
subroutine, public rrate_ms(x, xs, y, ys, r, ptz, rate_out)
Merges two tables of rates (of type global_class::reactionrate_type).
logical use_alpha_decay_file
Switch for using additional alpha decay rates.
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
subroutine, private count_reactions(n)
Count the amount of possible alpha decays.
subroutine, public write_data_to_std_out(str_msg, value_str, unit)
Write data to the standard output (usually OUT)
character(len=4), dimension(:), allocatable, private src_ignore
Module with helper functions such as rate tabulation, partition functions, and theoretical weak rates...
character(max_fname_len) alpha_decay_file
File with additional alpha decays.
integer alpha_decay_zmax
Maximum Z for additional alpha decay rates.
subroutine, public rrate_sort(num, rate_array)
Sorts chapter one of the rate array.
integer, public net_size
total number of isotopes (network size)
integer, private src_ignore_length
Provide some basic file-handling routines.
character(:) function, allocatable, public num_to_str(num)
Converts a given real to a string with format "(1pE10.2)".
subroutine, public analyze_src_string(input_string, output_array, length_output)
Analyze a string and split it with delimiter ";".
character(15), parameter, private fileformat
integer function, public open_infile(file_name)
Same for reading (input file)
type(reactionrate_type), dimension(:), allocatable, private alpha_dec_rate
Array storing the reaction rates.
integer function, public open_outfile(file_name)
Shorthand for opening a new file for writing (output file)
Contains types and objects shared between multiple modules.
character(:) function, allocatable, public get_net_name(index, trimmed)
Getter of net_names, translating indices to a nucleus name.
character(max_fname_len) alpha_decay_src_ignore
Source flag(s) to ignore within the alpha decay rates.
logical alpha_decay_ignore_all
Flag whether rates should actually get replaced or only added.
logical, private include_alpha_decays
Flag whether alpha decays should be included or not.
subroutine, public init_alpha_decay_rates()
Initialize alpha decay rates.
Module mergesort_module for merging arrays of rates.
subroutine, private create_verbose_output_file(alpha_decay_rates, nalpha)
Creates a file with the decays.
subroutine, private read_reactions(alpha_rate_array, n)
Read the alpha decays.
integer, private nalpha_dec
Number of alpha decays.
Contains all runtime parameters as well as phys and math constants.
subroutine, public getcoefficients(rate_array, length_rate_array)
Returns the 1/n! factor where n is the number of equal isotopes entering a reaction....
character(150) function, private reaction_string(reac)
Return a string to represent a given reaction.
Subroutines needed to initialise the network.