parameter_class.f90
Go to the documentation of this file.
1 !> @file parameter_class.f90
2 !!
3 !! The error file code for this file is ***W34***.
4 !!
5 !! @brief Module \ref parameter_class with all simulation parameters
6 !!
7 
8 !> Contains all runtime parameters as well as phys and math constants
9 !!
10 !! Contains the following definitions:
11 !! \li all runtime simulation parameters;
12 !! \li mathematical and physical constants.
13 !!
14 !! @author Darko Mocelj
15 !! @date 22.01.03
16 !!
17 !! \b Editors:
18 !! \li 01.12.11: Christian Winteler
19 !! \li 22.07.13: Marcella Ugliano
20 !! \li 11.01.14: Oleg Korobkin
21 !! \li 11.01.21: Moritz Reichert
22 !! .
23 #include "macros.h"
26  implicit none
27 
28  public :: unit_define
29 
30  !> constants and unit conversion factors
31  type,public :: unit_type
32  real(r_kind) :: pi !< \f$\pi\f$
33  real(r_kind) :: mass_n !< Neutron mass [MeV/c^2]
34  real(r_kind) :: mass_p !< Proton mass [MeV/c^2]
35  real(r_kind) :: mass_u !< Atomic mass unit [MeV/c^2]
36  real(r_kind) :: mass_e !< Electron mass [MeV/c^2]
37  real(r_kind) :: me !< Electron mass [g]
38  real(r_kind) :: n_a !< Avogadro constant
39  real(r_kind) :: hbc !< hbar*c [Mev*fm]
40  real(r_kind) :: k_b !< Boltzman constant [J/K]
41  real(r_kind) :: k_mev !< Boltzmann constant [MeV/K]
42  real(r_kind) :: kerg !< Boltzmann constant [erg/K]
43  real(r_kind) :: conv_ev !< conversion factor eV to J
44  real(r_kind) :: clight !< speed of light in vacuum [cm/s]
45  real(r_kind) :: h !< Planck constant [J*s]
46  real(r_kind) :: h_mevs !< Planck constant [MeV*s]
47  real(r_kind) :: hbar_mev !< Planck constant reduced [MeV*s]
48  real(r_kind) :: hix !< Atomic mass unit [MeV/(cm/s)^2]
49  real(r_kind) :: amu !< Atomic mass unit [g]
50  real(r_kind) :: grav !< Gravitational Constant [cm^3/(g*s^2)]
51  real(r_kind) :: msol !< solar mass [g]
52  real(r_kind) :: ergtomev !< conversion from erg to MeV
53  end type unit_type
54  type(unit_type),public :: unit !< constants and unit conversion factors
55 
56 !>-- hardcoded parameters
57  integer,public,parameter :: param_name_len = 200 !< maximum length of a parameter name
58  integer,public,parameter :: max_fname_len = 400 !< maximum length of filenames
59 
60 !>-- runtime parameters set when reading parameter file
61  integer :: out_every !< main output frequency
62  integer :: snapshot_every !< snapshot output frequency
63  integer :: h_snapshot_every !< snapshot output frequency in hdf5 format
64  integer :: flow_every !< flow output frequency
65  integer :: h_flow_every !< flow output frequency in hdf5 format
66  integer :: timescales_every !< timescales output frequency
67  integer :: h_timescales_every !< timescales output frequency in hdf5 format
68  integer :: engen_every !< Energy generation output frequency
69  integer :: h_engen_every !< Energy generation output frequency in hdf5 format
70  integer :: nrdiag_every !< frequency of NR loop diagnostic messages (wrt iteration counter)
71  integer :: mainout_every !< frequency of mainout output
72  integer :: h_mainout_every !< HDF5 output frequency of the mainout
73  integer :: track_nuclei_every !< frequency of track nuclei output
74  integer :: h_track_nuclei_every !< frequency of track nuclei output in hdf5 format
75  integer :: top_engen_every !< frequency of energy generators toplist
76  logical :: use_alpha_decay_file !< Switch for using additional alpha decay rates
77  integer :: alpha_decay_zmin !< Minimum Z for additional alpha decay rates
78  integer :: alpha_decay_zmax !< Maximum Z for additional alpha decay rates
79  character(max_fname_len):: alpha_decay_src_ignore !< Source flag(s) to ignore within the alpha decay rates
80  logical :: alpha_decay_ignore_all !< Flag whether rates should actually get replaced or only added
81  integer :: iwformat !< defines format of the weak rates (0 = tabulated, 1 = log<ft>)
82  integer :: iwinterp !< defines the interpolation for the weak rates (0 = bilinear, 1 = bicubic)
83  real(r_kind) :: temp_reload_exp_weak_rates !< temperature below which one should not use theoretical weak rates so they are replaced with exp. weak rates (min 1.d-2)
84  real(r_kind) :: freeze_rate_temp !< Tmperature at which rates get frozen (for reacl. rates this should be 1d-2GK)
85  integer :: nuflag !< defines type of neutrino reactions used
86  integer :: fissflag !< defines type of fission fragment distribution used
87  integer :: expansiontype !< defines prescription used for parametrized expansion after the last timestep of the hydro input
88  integer :: extrapolation_width !< how many points from the end of trajectory to use when computing residual expansion
89  integer :: nse_calc_every !< Compute NSE abundances every x step.
90  character*20 :: trajectory_mode !< determines how trajectory is calculated (from_file|analytic|expand)
91  logical :: read_initial_composition !< specify whether initial distribution of abundances should be read from file
92  logical :: use_tabulated_rates !< switch for using tabulated rates (e.g. talysNGrates.dat)
93  logical :: use_beta_decay_file !< switch for using different format for beta decays
94  logical :: use_prepared_network !< Use a prepared folder with all necessary data in binary format
95  character(max_fname_len):: beta_decay_src_ignore !< Source flag(s) to ignore within the beta decay file
96  logical :: use_timmes_mue !< Use electron chemical potentials from timmes EOS for theoretical weak rates
97  logical :: use_detailed_balance !< Calculate the inverse reactions via detailed balance rather than using them form file
98  logical :: use_detailed_balance_q_reac !< Use Q-value from reaclib for the calculation of detailed balance
99  logical :: use_thermal_nu_loss !< Whether to include thermal neutrino loss or not.
100  integer :: nu_loss_every !< Output neutrino loss and gain.
101  integer :: h_nu_loss_every !< Output neutrino loss and gain in hdf5 format.
102  character(max_fname_len):: detailed_balance_src_ignore !< Source flag(s) to ignore within calculated detailed balance
103  character(max_fname_len):: detailed_balance_src_q_reac !< Source flag(s) to use q-value from rate file for inverse reaction
104  character(max_fname_len):: detailed_balance_src_q_winvn !< Source flag(s) to use q-value from winvn file for inverse reaction
105  logical :: use_neutrino_loss_file !< Use a file with Qnu values?
106  character(max_fname_len):: neutrino_loss_file !< Path to a file containing Qnu values
107  logical :: custom_snapshots !< If true, a file must be provided with numbers in days. Snapshots will be created for these points in time
108  logical :: h_custom_snapshots !< Same, but in hdf5 format
109  real(r_kind) :: engen !< total energy generation [MeV/s]
110  real(r_kind) :: engen_alpha !< energy generation from alpha-decays [MeV/s]
111  real(r_kind) :: engen_beta !< energy generation from beta-decays [MeV/s]
112  real(r_kind) :: engen_fiss !< energy generation from fission [MeV/s]
113  real(r_kind) :: initemp_cold !< T [GK] lowest allowed temperature to start the calculation from
114  real(r_kind) :: initemp_hot !< T [GK] for the starting point of the trajectory: =0: from the beginning; >0: from the last T>initemp
115  real(r_kind) :: nse_delt_t9min !< Minimum temperature [GK] when descending to desired temperature in NSE
116  real(r_kind) :: nse_nr_tol !< Tolerance for the NR loop in the NSE calculation
117  integer :: nse_max_it !< Maximum amount of NSE iterations
118  integer :: nse_solver !< Solver for calculating NSE. 0: Newton-Raphson, 1: Powell's hybrid method
119  real(r_kind) :: nsetemp_cold !< T [GK] for the nse->network switch
120  real(r_kind) :: nsetemp_hot !< T [GK] for the nse<-network switch
121  logical :: calc_nsep_energy !< calculate neutron separation energy?
122  logical :: h_engen_detailed !< Output the energy per parent nucleus and reaction type
123  real(r_kind) :: heating_frac !< use this fraction of nuclear-generated energy for heating
124  real(r_kind) :: heating_density !< Density at which nuclear heating will be switched on (-1) to always include heating
125  real(r_kind) :: nse_descend_t9start !< high initial temperature in GK for winnse_descend subroutine
126  real(r_kind) :: t_analytic !< for parameteric trajectories: initial time
127  integer :: termination_criterion !< condition to terminate the simulation ([0]=trajectory_file, 1=final_time, 2=final_temp, 3=final_dens, 4=neutron freeze-out)
128  real(r_kind) :: initial_stepsize !< this value is used as a stepsize at initial step
129  real(r_kind) :: final_time !< termination time in seconds
130  real(r_kind) :: final_temp !< termination temperature [GK]
131  real(r_kind) :: final_dens !< termination density [g/cm3]
132  real(r_kind) :: timestep_max !< Maximum factor for the change of the timestep. The new timestep is only allowed to be timestep_max * old_timestep. Default value is 2.
133  real(r_kind) :: timestep_factor !< Factor for the change of the timestep (see nu in Winteler 2012 Eq. 2.49). Default value is 1.0d-1
134  real(r_kind) :: timestep_hydro_factor !< Factor for the maximum change of the hydrodynamic quantities (density and temperature)
135  real(r_kind) :: timestep_ymin !< Lower limit of the abundance to contribute to the timestep calculation, default value is 1.0d-10
136  real(r_kind) :: gear_eps !< Abundance accuracy for gear solver
137  real(r_kind) :: gear_escale !< Normalization cutoff for gear solver, similar to timestep_Ymin for Euler
138  real(r_kind) :: gear_cfactor !< Conservative timestep factor for gear solver [0.1, ... , 0.4]
139  real(r_kind) :: gear_nr_eps !< Convergence criterion for the newton-raphson of the gear solver
140  real(r_kind) :: gear_timestep_max !< For gear solver
141  integer :: gear_nr_maxcount !< Maximum newton-raphson iterations for gear solver
142  integer :: gear_nr_mincount !< Minimum newton-raphson iterations for gear solver
143  logical :: gear_ignore_adapt_stepsize !< Flag whether gear should ignore the adapt stepsize loop
144  logical :: timestep_traj_limit !< Should the timestep be limited by the timestep of the trajectory
145  logical :: use_htpf !< Use high temperature partition functions or not
146  logical :: h_finab !< Store the finab in hdf5 format rather than in ascii format
147  integer :: solver !< solver flag (0 - implicit Euler, 1 - Gear's method, ...), is integer as it is faster than comparing strings every timestep
148  integer :: heating_mode !< Mode for heating: 0 - no heating, 1 - heating using an entropy equation, 2 - heating from the energy generation and trajectory changes
149  real(r_kind) :: heating_t9_tol !< Convergence parameter for the temperature in the heating mode
150  integer :: screening_mode !< Mode for coulomb corrections: 0 - no screening, 1 - screening using the prescription of Kravchuk & Yakovlev 2014
151  integer :: interp_mode !< Mode for interpolation of temperature and density
152  character(max_fname_len):: trajectory_file !< name of trajectory data file
153  character(max_fname_len):: seed_file !< name of file with initial seeds for trajectory run
154  character(max_fname_len):: seed_format !< Seed format
155  character(max_fname_len):: net_source !< list of isotopes included in the network (sunet)
156  character(max_fname_len):: isotopes_file !< properties of all isotopes in the network: masses, partition functions etc. (winvn)
157  character(max_fname_len):: htpf_file !< high-temperature partition functions (htpf.dat)
158  character(max_fname_len):: reaclib_file !< reaction rate library (reaclib)
159  character(max_fname_len):: fission_rates_spontaneous !< reaction library for spontaneous fission rates
160  character(max_fname_len):: fission_rates_n_induced !< reaction library for neutron induced fission rates
161  character(max_fname_len):: fission_rates_beta_delayed !< reaction library for beta delayed fission rates
162  integer :: fission_format_beta_delayed !< Format of beta-delayed fission rates (0: Off, 1: Reaclib, 2: Halflifes, 3: Probability)
163  integer :: fission_format_n_induced !< Format of neutron-induced fission rates (0: Off, 1: Reaclib)
164  integer :: fission_format_spontaneous !< Format of spontaneous fission rates (0: Off, 1: Reaclib, 2: Halflifes)
165  integer :: fission_frag_spontaneous !< Fragment distribution of spontaneous fission rates in case of custom fragments (fissflag=4)
166  integer :: fission_frag_n_induced !< Fragment distribution of n-induced fission rates in case of custom fragments (fissflag=4)
167  integer :: fission_frag_beta_delayed !< Fragment distribution of beta-delayed fission rates in case of custom fragments (fissflag=4)
168  integer :: fission_frag_missing !< Fragment distribution in case of missing fragments in case of custom fragments (fissflag=4)
169  character(max_fname_len):: weak_rates_file !< weak rates library (twr.dat)
170  character(max_fname_len):: tabulated_rates_file !< tabulated rates library (e.g. talysNGrates.dat)
171  character(max_fname_len):: tabulated_temperature_file !< file containing grid of tabulated temperature file ("default" for default grid)
172  character(max_fname_len):: chem_pot_file !< tabulated chemical potential of electron gas
173  character(max_fname_len):: nsep_energies_file !< neutron separation energies
174  character(max_fname_len):: nunucleo_rates_file !< neutrino reaction rates on nucleons
175  character(max_fname_len):: nuchannel_file !< Contains neutrino channel information as in Sieverding et al. 2018
176  character(max_fname_len):: nurates_file !< Neutrino reactions on heavy nuclei as in Sieverding et al. 2018
177  character(max_fname_len):: snapshot_file !< File that contains days, where a snapshot should be made
178  character(max_fname_len):: bfission_file !< Fission table for beta-delayed fission
179  character(max_fname_len):: nfission_file !< Fission table for neutron-induced fission
180  character(max_fname_len):: sfission_file !< Fission table for spontaneous fission
181  character(max_fname_len):: track_nuclei_file !< File of nuclei to track. Gives an output similar to mainout.dat
182  character(max_fname_len):: alpha_decay_file !< File with additional alpha decays
183  character(max_fname_len):: beta_decay_file !< File for reading in beta decays in different format
184  character(max_fname_len):: trajectory_format !< Format to read the trajectory
185  character(max_fname_len):: neutrino_mode !< Similar to trajectory mode
186  character(max_fname_len):: t9_analytic !< analytic temperature [T9]
187  character(max_fname_len):: rho_analytic !< analytic density [g/cm3]
188  character(max_fname_len):: rkm_analytic !< analytic radial scale [km]
189  character(max_fname_len):: ye_analytic !< analytic electron fraction
190  character(max_fname_len):: le !< electron-neutrino luminosities [erg/s]
191  character(max_fname_len):: lebar !< electron-antineutrino luminosities [erg/s]
192  character(max_fname_len):: enue !< average electron-neutrino energies [MeV]
193  character(max_fname_len):: enuebar !< average electron-antineutrino energies [MeV]
194  character(max_fname_len):: lx !< Muon and Tauon neutrino luminosities [erg/s]
195  character(max_fname_len):: lxbar !< Muon and Tauon antineutrino luminosities [erg/s]
196  character(max_fname_len):: enux !< average Muon and Tauon neutrino energies [MeV]
197  character(max_fname_len):: enuxbar !< average Muon and Tauon antineutrino energies [MeV]
198  real(r_kind) :: nu_max_time !< Maximum time for neutrino reactions to react
199  real(r_kind) :: nu_min_t !< Neutrino temperature cutoff for neutrino reactions [MeV]
200  real(r_kind) :: nu_min_l !< Neutrino luminosity cutoff for neutrino reactions [erg/g/s]
201  character(max_fname_len):: prepared_network_path !< Prepared network folder
202 
203 !>-- Newton-Raphson iterative loop parameters
204  integer :: nr_maxcount !< no more that this many iterations in NR
205  integer :: nr_mincount !< Minimum iterations in NR
206  real(r_kind) :: nr_tol !< exit NR if tolerance less than this value
207  integer :: adapt_stepsize_maxcount !< max. iterations in adapting the stepsize
208 
209 !> other static variables
210  character(len=*), private, parameter :: par_binary_name='parameter.windat'
211 
212 
213 !>-- parameters for efficient numerical integration of effphase in the interval [1,infinity]
214  real(r_kind), dimension(:), allocatable :: weights !< weights for the numerical integration
215  real(r_kind), dimension(:), allocatable :: xnodes !< corresponding nodes "
216  logical :: weightscalculated = .false. !< switch to calculated weights and nodes for [1,infinity]
217 
218  integer :: ncc = 256 !< nr of points for Clenshaw-Curtis integration
219  real(r_kind), dimension(:), allocatable :: dcc,matcc !< matrices for Clenshaw-Curtis integration
220  real(r_kind), dimension(:,:), allocatable :: mcc
221 
222 contains
223 
224 
225 
226 
227 
228 
229 
230 
231 
232 !>
233 !! Declares values for the elements in unit_type
234 !!
235 subroutine unit_define()
236  unit%pi = 3.14159265358979323846d0
237  unit%mass_n = 939.56533d0 ! mev/c^2
238  unit%mass_p = 938.271998d0 ! mev/c^2
239  unit%mass_u = 931.494013d0 ! mev/c^2
240  unit%mass_e = 0.510998910d0 ! mev
241  unit%me = 9.1093826d-28 ! g
242  unit%n_a = 6.02214179d23 ! mol^(-1)
243  unit%hbc = 197.327053d0 ! mev*fm
244  unit%k_b = 1.380662d-23 ! j/k
245  unit%k_mev = 8.617343d-11 ! mev/k
246  unit%conv_ev = 1.602189246d-19 ! 1ev = xxx j
247  unit%kerg = 1.3806504d-16 ! erg
248  unit%clight = 2.99792458d10 ! cm/s
249  unit%h = 6.62606876d-34 ! Js
250  unit%hbar_mev= 6.582122d-22 ! MeVs
251  unit%h_mevs = 4.135667273d-21 ! MeVs
252  unit%hix = 1.036427d-18 ! amu in MeV/(cm/s)^2 (convert from [erg/g] to [MeV/baryon])
253  unit%amu = 1.66053873d-24 ! g
254  unit%grav = 6.67384d-8 ! cm^3/(g*s^2)
255  unit%msol = 1.9891d33 ! g
256  unit%ergtomev= 0.62415d6 ! 1 erg = xxx MeV
257 end subroutine unit_define
258 
259 
260 !>
261 !! This function reads the parameter file
262 !!
263 !! Blank lines as well as comment lines are skipped.
264 !! The parameters are read into the proper variable
265 !! that are declarated at the beginning of the file.
266 !!
267 !! \b Edited:
268 !! - 01.02.14
269 !! .
270 subroutine read_param(parfile)
272  implicit none
273 
274  character(*),intent(in) :: parfile
275  !
276  character(1000) :: line
277  character(param_name_len) :: param_name
278  character(2000) :: param_value
279  character(2), parameter :: blanks = " "//achar(9)
280  integer :: parfile_unit, istat, ieq, i1,i2,ln
281 
282  parfile_unit= open_infile(parfile)
283 
284  ln= 1
285  read_loop: do
286  read (parfile_unit,'(A)',iostat=istat) line
287  if (istat .ne. 0) exit ! end of file
288  i1= verify(line,blanks)
289  if(i1.eq.0) cycle ! skip blank lines
290  i2= verify(line,blanks,back=.true.)
291  line= line(i1:i2) ! trim tabs and spaces
292  if(line(1:1).eq.'#') cycle ! skip comments, which start with '#'
293  ieq= index(line,'=') ! look for an '=' sign
294  if(ieq.eq.0) then
295  call raise_exception("Could not read parameter file in line # "//&
296  trim(adjustl(int_to_str(ln)))//" :"//new_line("A")//&
297  trim(adjustl(line)) ,"read_param",340003)
298  endif
299  i2= verify(line(1:ieq-1),blanks,back=.true.)
300  if(i2.eq.0) then
301  call raise_exception("Could not read parameter file in line # "//&
302  trim(adjustl(int_to_str(ln)))//" :"//new_line("A")//&
303  trim(adjustl(line)) ,"read_param",340003)
304  endif
305  param_name= line(1:i2) ! parse param_name and param_value
306  i2= verify(line,blanks,back=.true.)
307  i1= ieq-1 + verify(line(ieq:i2),blanks//"=")
308  param_value= line(i1:i2)
309  !print '(A," = :",A,";")', trim(param_name), trim(param_value)
310  call set_param(param_name,param_value)
311  ln= ln + 1
312  enddo read_loop
313 
314  ! Check the parameter for consistency
315  call check_param
316 
317  ! close the file
318  close(parfile_unit)
319 
320  return
321 
322 end subroutine read_param
323 
324 
325 !>
326 !! Sets a global parameter param_name to the value, given by its string
327 !! representation param_value
328 !!
329 !! \b Edited:
330 !! - M.R. 02.11.22, Implemented more meaningfull error msg, made use of *_params
331 !!.
332 subroutine set_param(param_name,param_value)
333 
334  implicit none
335  character(*), intent(in) :: param_name
336  character(*), intent(in) :: param_value
337  !
338  character(9999) :: all_possible_par
339  character(*), parameter :: integer_params = &
340  ":out_every" // &
341  ":snapshot_every" // &
342  ":nrdiag_every" // &
343  ":mainout_every" // &
344  ":iwformat" // &
345  ":timescales_every" // &
346  ":nuflag" // &
347  ":fissflag" // &
348  ":termination_criterion" // &
349  ":flow_every" // &
350  ":expansiontype" // &
351  ":h_snapshot_every" // &
352  ":track_nuclei_every" // &
353  ":nr_maxcount" // &
354  ":adapt_stepsize_maxcount" // &
355  ":extrapolation_width" // &
356  ":solver" // &
357  ":nse_calc_every" // &
358  ":engen_every" // &
359  ":top_engen_every" // &
360  ":h_mainout_every" // &
361  ":h_track_nuclei_every"//&
362  ":h_timescales_every" // &
363  ":h_flow_every" // &
364  ":h_engen_every" // &
365  ":gear_nr_maxcount" // &
366  ":iwinterp" // &
367  ":heating_mode"//&
368  ":fission_frag_beta_delayed"//&
369  ":fission_frag_n_induced"//&
370  ":fission_frag_spontaneous"//&
371  ":fission_frag_missing"//&
372  ":fission_format_spontaneous"//&
373  ":fission_format_beta_delayed"//&
374  ":fission_format_n_induced"//&
375  ":nr_mincount" // &
376  ":gear_nr_mincount" // &
377  ":alpha_decay_zmin" // &
378  ":alpha_decay_zmax" // &
379  ":nse_max_it" // &
380  ":screening_mode"//&
381  ":nu_loss_every" // &
382  ":h_nu_loss_every" // &
383  ":interp_mode" // &
384  ":nse_solver"
385  character(*), parameter :: real_params = &
386  ":temp_reload_exp_weak_rates" // &
387  ":engen"// &
388  ":initemp_cold"// &
389  ":initemp_hot"// &
390  ":nsetemp_cold" // &
391  ":nsetemp_hot"// &
392  ":heating_frac"// &
393  ":nse_descend_t9start" // &
394  ":t_analytic"// &
395  ":gear_eps"// &
396  ":gear_escale"// &
397  ":gear_cFactor"// &
398  ":gear_nr_eps" // &
399  ":timestep_max"// &
400  ":gear_timestep_max"// &
401  ":heating_T9_tol"// &
402  ":timestep_factor"// &
403  ":timestep_Ymin"// &
404  ":nr_tol"// &
405  ":timestep_hydro_factor"// &
406  ":final_time"// &
407  ":final_temp"// &
408  ":final_dens" // &
409  ":initial_stepsize"// &
410  ":nu_max_time"// &
411  ":nu_min_T"// &
412  ":nu_min_L"// &
413  ":freeze_rate_temp"// &
414  ":nse_nr_tol"// &
415  ":nse_delt_t9min" // &
416  ":heating_density"
417  character(*), parameter :: logical_params = &
418  ":read_initial_composition" // &
419  ":use_htpf" // &
420  ":h_finab" // &
421  ":gear_ignore_adapt_stepsize" // &
422  ":calc_nsep_energy" // &
423  ":timestep_traj_limit" // &
424  ":custom_snapshots" // &
425  ":h_custom_snapshots" // &
426  ":h_engen_detailed" // &
427  ":use_detailed_balance" // &
428  ":use_timmes_mue" // &
429  ":use_detailed_balance_q_reac" // &
430  ":use_tabulated_rates" // &
431  ":use_beta_decay_file" //&
432  ":use_alpha_decay_file" // &
433  ":alpha_decay_ignore_all"//&
434  ":use_neutrino_loss_file" // &
435  ":use_thermal_nu_loss"//&
436  ":use_prepared_network"
437  character(*), parameter :: string_params = &
438  ":trajectory_file" // &
439  ":seed_file" // &
440  ":net_source" // &
441  ":isotopes_file" // &
442  ":htpf_file" // &
443  ":reaclib_file" // &
444  ":fission_rates_spontaneous" // &
445  ":fission_rates_beta_delayed" // &
446  ":fission_rates_n_induced" // &
447  ":weak_rates_file" // &
448  ":chem_pot_file" // &
449  ":nsep_energies_file" // &
450  ":alpha_decay_src_ignore" // &
451  ":nunucleo_rates_file" // &
452  ":nuchannel_file" // &
453  ":nfission_file" // &
454  ":bfission_file" // &
455  ":sfission_file" // &
456  ":trajectory_mode" // &
457  ":trajectory_format" // &
458  ":track_nuclei_file" // &
459  ":nurates_file" // &
460  ":snapshot_file" // &
461  ":beta_decay_file" // &
462  ":neutrino_mode" // &
463  ":T9_analytic" // &
464  ":rho_analytic" // &
465  ":Rkm_analytic" // &
466  ":Ye_analytic" // &
467  ":Le" // &
468  ":Lebar" // &
469  ":Enue" // &
470  ":Enuebar" // &
471  ":seed_format" // &
472  ":Lx" // &
473  ":Lxbar" // &
474  ":Enux" // &
475  ":Enuxbar" // &
476  ":alpha_decay_file" // &
477  ":detailed_balance_src_ignore" // &
478  ":detailed_balance_src_q_reac" // &
479  ":detailed_balance_src_q_winvn" // &
480  ":tabulated_rates_file" // &
481  ":tabulated_temperature_file" // &
482  ":beta_decay_src_ignore" // &
483  ":neutrino_loss_file" // &
484  ":prepared_network_path"
485 
486  logical :: lparam_value
487  integer :: i2
488  real(r_kind) :: score
489  character(999) :: cl_par
490  character(2000) :: str_value
491  character(500) :: h_err_msg !< Helper error message
492 
493 
494  i2= index(param_value, "#")
495  if ((param_value(1:1).eq."'") .or.(param_value(1:1).eq.'"')) &
496  then
497  str_value= trim(param_value(2:len_trim(param_value)-1))
498  elseif(i2.gt.0) then
499  str_value= trim(param_value(1:i2-1))
500  else
501  str_value= trim(param_value)
502  endif
503 
504  if(len_trim(str_value).ge.5) then
505  lparam_value= (str_value(1:5).eq."'yes'") &
506  .or.(str_value(1:5).eq.'"yes"')
507  elseif(len_trim(str_value).ge.3) then
508  lparam_value= (str_value(1:3).eq."yes")
509  else
510  lparam_value= .false.
511  endif
512 
513 !--- integer parameters
514  if(param_name.eq."out_every") then
515  out_every = read_integer_param(str_value,param_name)
516  elseif(param_name.eq."snapshot_every") then
517  snapshot_every = read_integer_param(str_value,param_name)
518  elseif(param_name.eq."h_snapshot_every") then
519  h_snapshot_every = read_integer_param(str_value,param_name)
520  elseif(param_name.eq."h_mainout_every") then
521  h_mainout_every = read_integer_param(str_value,param_name)
522  elseif(param_name.eq."flow_every") then
523  flow_every = read_integer_param(str_value,param_name)
524  elseif(param_name.eq."h_flow_every") then
525  h_flow_every = read_integer_param(str_value,param_name)
526  elseif(param_name.eq."timescales_every") then
527  timescales_every = read_integer_param(str_value,param_name)
528  elseif(param_name.eq."h_timescales_every") then
529  h_timescales_every = read_integer_param(str_value,param_name)
530  elseif(param_name.eq."engen_every") then
531  engen_every = read_integer_param(str_value,param_name)
532  elseif(param_name.eq."h_engen_every") then
533  h_engen_every = read_integer_param(str_value,param_name)
534  elseif(param_name.eq."nrdiag_every") then
535  nrdiag_every = read_integer_param(str_value,param_name)
536  elseif(param_name.eq."mainout_every") then
537  mainout_every = read_integer_param(str_value,param_name)
538  elseif(param_name.eq."iwformat") then
539  iwformat = read_integer_param(str_value,param_name)
540  elseif(param_name.eq."iwinterp") then
541  iwinterp = read_integer_param(str_value,param_name)
542  elseif(param_name.eq."nuflag") then
543  nuflag = read_integer_param(str_value,param_name)
544  elseif(param_name.eq."fissflag") then
545  fissflag = read_integer_param(str_value,param_name)
546  elseif(param_name.eq."termination_criterion") then
547  termination_criterion = read_integer_param(str_value,param_name)
548  elseif(param_name.eq."expansiontype") then
549  expansiontype = read_integer_param(str_value,param_name)
550  elseif(param_name.eq."nr_maxcount") then
551  nr_maxcount = read_integer_param(str_value,param_name)
552  elseif(param_name.eq."nr_mincount") then
553  nr_mincount = read_integer_param(str_value,param_name)
554  elseif(param_name.eq."adapt_stepsize_maxcount") then
555  adapt_stepsize_maxcount = read_integer_param(str_value,param_name)
556  elseif(param_name.eq."track_nuclei_every") then
557  track_nuclei_every = read_integer_param(str_value,param_name)
558  elseif(param_name.eq."h_track_nuclei_every") then
559  h_track_nuclei_every = read_integer_param(str_value,param_name)
560  elseif(param_name.eq."top_engen_every") then
561  top_engen_every = read_integer_param(str_value,param_name)
562  elseif(param_name.eq."extrapolation_width") then
563  extrapolation_width = read_integer_param(str_value,param_name)
564  elseif(param_name.eq."solver") then
565  solver = read_integer_param(str_value,param_name)
566  elseif(param_name.eq."heating_mode") then
567  heating_mode = read_integer_param(str_value,param_name)
568  elseif(param_name.eq."fission_frag_beta_delayed") then
569  fission_frag_beta_delayed = read_integer_param(str_value,param_name)
570  elseif(param_name.eq."fission_frag_missing") then
571  fission_frag_missing = read_integer_param(str_value,param_name)
572  elseif(param_name.eq."fission_frag_n_induced") then
573  fission_frag_n_induced = read_integer_param(str_value,param_name)
574  elseif(param_name.eq."fission_frag_spontaneous") then
575  fission_frag_spontaneous = read_integer_param(str_value,param_name)
576  elseif(param_name.eq."fission_format_spontaneous") then
577  fission_format_spontaneous = read_integer_param(str_value,param_name)
578  elseif(param_name.eq."fission_format_beta_delayed") then
579  fission_format_beta_delayed = read_integer_param(str_value,param_name)
580  elseif(param_name.eq."fission_format_n_induced") then
581  fission_format_n_induced = read_integer_param(str_value,param_name)
582  elseif(param_name.eq."screening_mode") then
583  screening_mode = read_integer_param(str_value,param_name)
584  elseif(param_name.eq."interp_mode") then
585  interp_mode = read_integer_param(str_value,param_name)
586  elseif(param_name.eq."nse_calc_every") then
587  nse_calc_every = read_integer_param(str_value,param_name)
588  elseif(param_name.eq."gear_nr_maxcount") then
589  gear_nr_maxcount = read_integer_param(str_value,param_name)
590  elseif(param_name.eq."gear_nr_mincount") then
591  gear_nr_mincount = read_integer_param(str_value,param_name)
592  elseif(param_name.eq."alpha_decay_zmin") then
593  alpha_decay_zmin = read_integer_param(str_value,param_name)
594  elseif(param_name.eq."alpha_decay_zmax") then
595  alpha_decay_zmax = read_integer_param(str_value,param_name)
596  elseif(param_name.eq."nse_max_it") then
597  nse_max_it = read_integer_param(str_value,param_name)
598  elseif(param_name.eq."nse_solver") then
599  nse_solver = read_integer_param(str_value,param_name)
600  elseif(param_name.eq."nu_loss_every") then
601  nu_loss_every = read_integer_param(str_value,param_name)
602  elseif(param_name.eq."h_nu_loss_every") then
603  h_nu_loss_every = read_integer_param(str_value,param_name)
604 
605 !--- real parameters
606  elseif(param_name.eq."temp_reload_exp_weak_rates") then
607  temp_reload_exp_weak_rates= read_float_param(str_value,param_name)
608  elseif(param_name.eq."engen") then
609  engen= read_float_param(str_value,param_name)
610  elseif(param_name.eq."initemp_cold") then
611  initemp_cold= read_float_param(str_value,param_name)
612  elseif(param_name.eq."initemp_hot") then
613  initemp_hot= read_float_param(str_value,param_name)
614  elseif(param_name.eq."nsetemp_cold") then
615  nsetemp_cold= read_float_param(str_value,param_name)
616  elseif(param_name.eq."nse_nr_tol") then
617  nse_nr_tol= read_float_param(str_value,param_name)
618  elseif(param_name.eq."nse_delt_t9min") then
619  nse_delt_t9min= read_float_param(str_value,param_name)
620  elseif(param_name.eq."nsetemp_hot") then
621  nsetemp_hot= read_float_param(str_value,param_name)
622  elseif(param_name.eq."heating_frac") then
623  heating_frac= read_float_param(str_value,param_name)
624  elseif(param_name.eq."heating_density") then
625  heating_density= read_float_param(str_value,param_name)
626  elseif(param_name.eq."nse_descend_t9start") then
627  nse_descend_t9start= read_float_param(str_value,param_name)
628  elseif(param_name.eq."initial_stepsize") then
629  initial_stepsize= read_float_param(str_value,param_name)
630  elseif(param_name.eq."final_time") then
631  final_time= read_float_param(str_value,param_name)
632  elseif(param_name.eq."final_temp") then
633  final_temp= read_float_param(str_value,param_name)
634  elseif(param_name.eq."final_dens") then
635  final_dens= read_float_param(str_value,param_name)
636  elseif(param_name.eq."t_analytic") then
637  t_analytic= read_float_param(str_value,param_name)
638  elseif(param_name.eq."gear_eps") then
639  gear_eps= read_float_param(str_value,param_name)
640  elseif(param_name.eq."gear_escale") then
641  gear_escale= read_float_param(str_value,param_name)
642  elseif(param_name.eq."gear_cFactor") then
643  gear_cfactor= read_float_param(str_value,param_name)
644  elseif(param_name.eq."gear_nr_eps") then
645  gear_nr_eps= read_float_param(str_value,param_name)
646  elseif(param_name.eq."gear_timestep_max") then
647  gear_timestep_max= read_float_param(str_value,param_name)
648  elseif(param_name.eq."heating_T9_tol") then
649  heating_t9_tol= read_float_param(str_value,param_name)
650  elseif(param_name.eq."timestep_max") then
651  timestep_max= read_float_param(str_value,param_name)
652  elseif(param_name.eq."timestep_factor") then
653  timestep_factor= read_float_param(str_value,param_name)
654  elseif(param_name.eq."timestep_hydro_factor") then
655  timestep_hydro_factor= read_float_param(str_value,param_name)
656  elseif(param_name.eq."timestep_Ymin") then
657  timestep_ymin= read_float_param(str_value,param_name)
658  elseif(param_name.eq."nr_tol") then
659  nr_tol= read_float_param(str_value,param_name)
660  elseif(param_name.eq."freeze_rate_temp") then
661  freeze_rate_temp= read_float_param(str_value,param_name)
662  elseif(param_name.eq."nu_max_time") then
663  nu_max_time= read_float_param(str_value,param_name)
664  elseif(param_name.eq."nu_min_T") then
665  nu_min_t= read_float_param(str_value,param_name)
666  elseif(param_name.eq."nu_min_L") then
667  nu_min_l= read_float_param(str_value,param_name)
668 !--- logical type parameters
669  elseif(param_name.eq."read_initial_composition") then
670  read_initial_composition= lparam_value
671  elseif(param_name.eq."calc_nsep_energy") then
672  calc_nsep_energy= lparam_value
673  elseif(param_name.eq."h_engen_detailed") then
674  h_engen_detailed= lparam_value
675  elseif(param_name.eq."timestep_traj_limit") then
676  timestep_traj_limit= lparam_value
677  elseif(param_name.eq."custom_snapshots") then
678  custom_snapshots= lparam_value
679  elseif(param_name.eq."h_custom_snapshots") then
680  h_custom_snapshots= lparam_value
681  elseif(param_name.eq."use_htpf") then
682  use_htpf= lparam_value
683  elseif(param_name.eq."h_finab") then
684  h_finab= lparam_value
685  elseif(param_name.eq."use_timmes_mue") then
686  use_timmes_mue= lparam_value
687  elseif(param_name.eq."use_tabulated_rates") then
688  use_tabulated_rates= lparam_value
689  elseif(param_name.eq."use_beta_decay_file") then
690  use_beta_decay_file= lparam_value
691  elseif(param_name.eq."use_prepared_network") then
692  use_prepared_network= lparam_value
693  elseif(param_name.eq."use_alpha_decay_file") then
694  use_alpha_decay_file= lparam_value
695  elseif(param_name.eq."use_detailed_balance") then
696  use_detailed_balance= lparam_value
697  elseif(param_name.eq."use_detailed_balance_q_reac") then
698  use_detailed_balance_q_reac= lparam_value
699  elseif(param_name.eq."use_thermal_nu_loss") then
700  use_thermal_nu_loss= lparam_value
701  elseif(param_name.eq."use_neutrino_loss_file") then
702  use_neutrino_loss_file= lparam_value
703  elseif(param_name.eq."gear_ignore_adapt_stepsize") then
704  gear_ignore_adapt_stepsize= lparam_value
705  elseif(param_name.eq."alpha_decay_ignore_all") then
706  alpha_decay_ignore_all= lparam_value
707 !--- string parameters
708  elseif(param_name.eq."trajectory_mode") then
709  trajectory_mode= trim(str_value)
710  elseif(param_name.eq."trajectory_file") then
711  trajectory_file= trim(str_value)
712  elseif(param_name.eq."T9_analytic") then
713  t9_analytic= trim(str_value)
714  elseif(param_name.eq."rho_analytic") then
715  rho_analytic= trim(str_value)
716  elseif(param_name.eq."Rkm_analytic") then
717  rkm_analytic= trim(str_value)
718  elseif(param_name.eq."Ye_analytic") then
719  ye_analytic= trim(str_value)
720  elseif(param_name.eq."alpha_decay_file") then
721  alpha_decay_file= trim(str_value)
722  elseif(param_name.eq."beta_decay_file") then
723  beta_decay_file= trim(str_value)
724  elseif(param_name.eq."seed_file") then
725  seed_file= trim(str_value)
726  elseif(param_name.eq."seed_format") then
727  seed_format= trim(str_value)
728  elseif(param_name.eq."snapshot_file") then
729  snapshot_file= trim(str_value)
730  elseif(param_name.eq."net_source") then
731  net_source= trim(str_value)
732  elseif(param_name.eq."isotopes_file") then
733  isotopes_file= trim(str_value)
734  elseif(param_name.eq."prepared_network_path") then
735  prepared_network_path= trim(str_value)
736  elseif(param_name.eq."htpf_file") then
737  htpf_file= trim(str_value)
738  elseif(param_name.eq."reaclib_file") then
739  reaclib_file= trim(str_value)
740  elseif(param_name.eq."fission_rates_beta_delayed") then
741  fission_rates_beta_delayed= trim(str_value)
742  elseif(param_name.eq."fission_rates_spontaneous") then
743  fission_rates_spontaneous= trim(str_value)
744  elseif(param_name.eq."fission_rates_n_induced") then
745  fission_rates_n_induced= trim(str_value)
746  elseif(param_name.eq."weak_rates_file") then
747  weak_rates_file= trim(str_value)
748  elseif(param_name.eq."tabulated_rates_file") then
749  tabulated_rates_file= trim(str_value)
750  elseif(param_name.eq."tabulated_temperature_file") then
751  tabulated_temperature_file= trim(str_value)
752  elseif(param_name.eq."chem_pot_file") then
753  chem_pot_file= trim(str_value)
754  elseif(param_name.eq."nsep_energies_file") then
755  nsep_energies_file= trim(str_value)
756  elseif(param_name.eq."nuchannel_file") then
757  nuchannel_file= trim(str_value)
758  elseif(param_name.eq."nurates_file") then
759  nurates_file= trim(str_value)
760  elseif(param_name.eq."nunucleo_rates_file") then
761  nunucleo_rates_file= trim(str_value)
762  elseif(param_name.eq."nfission_file") then
763  nfission_file= trim(str_value)
764  elseif(param_name.eq."bfission_file") then
765  bfission_file= trim(str_value)
766  elseif(param_name.eq."sfission_file") then
767  sfission_file= trim(str_value)
768  elseif(param_name.eq."trajectory_format") then
769  trajectory_format= trim(str_value)
770  elseif(param_name.eq."track_nuclei_file") then
771  track_nuclei_file= trim(str_value)
772  elseif(param_name.eq."neutrino_mode") then
773  neutrino_mode= trim(str_value)
774  elseif(param_name.eq."Le") then
775  le = trim(str_value)
776  elseif(param_name.eq."Lebar") then
777  lebar = trim(str_value)
778  elseif(param_name.eq."Enue") then
779  enue = trim(str_value)
780  elseif(param_name.eq."Enuebar") then
781  enuebar = trim(str_value)
782  elseif(param_name.eq."Lx") then
783  lx = trim(str_value)
784  elseif(param_name.eq."Lxbar") then
785  lxbar = trim(str_value)
786  elseif(param_name.eq."Enux") then
787  enux = trim(str_value)
788  elseif(param_name.eq."Enuxbar") then
789  enuxbar = trim(str_value)
790  elseif(param_name.eq."beta_decay_src_ignore") then
791  beta_decay_src_ignore = trim(str_value)
792  elseif(param_name.eq."alpha_decay_src_ignore") then
793  alpha_decay_src_ignore = trim(str_value)
794  elseif(param_name.eq."detailed_balance_src_ignore") then
795  detailed_balance_src_ignore = trim(str_value)
796  elseif(param_name.eq."detailed_balance_src_q_reac") then
797  detailed_balance_src_q_reac = trim(str_value)
798  elseif(param_name.eq."detailed_balance_src_q_winvn") then
799  detailed_balance_src_q_winvn = trim(str_value)
800  elseif(param_name.eq."neutrino_loss_file") then
801  neutrino_loss_file = trim(str_value)
802  else
803  ! Give a detailed error message
804  ! For this first merge all possible parameters:
805  all_possible_par = integer_params//real_params//logical_params//string_params
806 
807  ! Calculate score for similarity
808  call search_close_parameter(trim(adjustl(all_possible_par)),trim(adjustl(param_name)),score,cl_par)
809  ! Tell the user if there is a close parameter
810  ! Probably he meant this?
811  if (score .lt. max(len_trim(adjustl(param_name)),&
812  len_trim(adjustl(cl_par)))/2) then
813  ! I found something close
814  h_err_msg = new_line('A')//"Did you mean '"//trim(adjustl(cl_par))//"'?"
815  else
816  ! No clue what the user was thinking, dont give more information
817  h_err_msg =""
818  end if
819  ! Finally raise the exception
820  call raise_exception('Unknown parameter: '//trim(adjustl(param_name))//"."&
821  //trim(adjustl(h_err_msg)),"set_param",340004)
822  endif
823 end subroutine set_param
824 
825 
826 
827 
828 !> Converts a string to an integer
829 !!
830 !! If the string is not a valid integer, an error message is raised.
831 !!
832 !! @author Moritz Reichert
833 !! @date 22.01.21
834 function read_integer_param(input_string,param_name)
835  implicit none
836  character(len=*),intent(in) :: input_string !< String from param file
837  character(len=*),intent(in) :: param_name !< Parameter name
838  integer :: read_integer_param !< Converted integer value from input string
839  integer :: rstat !< iostat flag
840 
841  !< Convert string to integer
842  read(input_string,'(I10)',iostat=rstat) read_integer_param
843 
844  ! Raise an exception if converting does not work
845  if (rstat .ne. 0) then
846  call raise_exception('Could not parse parameter "'//trim(adjustl(param_name))//&
847  '". '//new_line("A")//'The value "'//&
848  trim(adjustl(input_string))//&
849  '" is not valid for this parameter. '//new_line("A")//&
850  'This parameter assumes an integer.', &
851  "read_integer_param",&
852  340005)
853  end if
854 end function read_integer_param
855 
856 
857 !> Converts a string to an float
858 !!
859 !! If the string is not a valid float, an error message is raised.
860 !!
861 !! @author Moritz Reichert
862 !! @date 22.01.21
863 function read_float_param(input_string,param_name)
864  implicit none
865  character(len=*),intent(in) :: input_string !< String from param file
866  character(len=*),intent(in) :: param_name !< Parameter name
867  real(r_kind) :: read_float_param !< Converted float value from input string
868  integer :: rstat !< iostat flag
869 
870  !< Convert string to float
871  read(input_string,*,iostat=rstat) read_float_param
872 
873  ! Raise an exception if converting does not work
874  if (rstat .ne. 0) then
875  call raise_exception('Could not parse parameter "'//trim(adjustl(param_name))//&
876  '". '//new_line("A")//'The value "'//&
877  trim(adjustl(input_string))//&
878  '" is not valid for this parameter. '//new_line("A")//&
879  'This parameter assumes a float.', &
880  "read_float_param",&
881  340005)
882  end if
883 end function read_float_param
884 
885 
886 
887 
888 !>
889 !! Sets default parameters
890 !! Parameters are sorted in alphabetical order
891 !!
893  implicit none
894  ! Variables
895  character(len=100) :: win_path ! Variable to store the value of the environment variable
896  integer :: status ! Variable to store the status of the retrieval
897 
898 
899  ! Get the value of the environment variable 'WinNet_path'
900  call get_environment_variable('WinNet_path', win_path, status)
901 
902  ! Check if it was set and complain if not
903  if (status == 0) then
904  ! Check if the environment variable was successfully retrieved
905  win_path = ""
906  if (verbose_level .ge. 1) then
907  write(*,*) 'Environment variable "WinNet_path" is not set. Default parameters may not work!'
908  end if
909  else
910  ! Set the environment variable
911  win_path = trim(win_path)//"/data/"
912  end if
913 
914  !
915  alpha_decay_ignore_all = .true.
916  alpha_decay_file = trim(adjustl(win_path))//"alpha_decays.dat"
917  alpha_decay_src_ignore = "wc07;wc12;wc17"
918  alpha_decay_zmax = 184
919  alpha_decay_zmin = 50
921  beta_decay_file = trim(adjustl(win_path))//"beta_decay_marketin.dat"
922  beta_decay_src_ignore = "wc07;wc12;wc17"
923  bfission_file = trim(adjustl(win_path))//"FISS_Mumpower"
924  calc_nsep_energy = .false.
925  chem_pot_file = trim(adjustl(win_path))//"chem_table.dat"
926  custom_snapshots = .false.
927  h_custom_snapshots = .false.
928  engen_every = 0
929  h_engen_every = 0
930  enue = "4.0"
931  enuebar = "5.4"
932  enux = "4.0"
933  enuxbar = "5.4"
934  expansiontype = 1
936  final_dens = 1.e0
937  final_temp = 1.e-2
938  final_time = 0.e0
939  fissflag = 0
940  flow_every = 0
941  freeze_rate_temp = 1.d-2
942  gear_eps = 1.0d-3
943  gear_escale = 1.0d-12
944  gear_cfactor = 0.25
945  gear_nr_maxcount = 10
946  gear_nr_mincount = 1
947  gear_nr_eps = 1.0d-6
949  gear_timestep_max = 10d0
950  h_engen_detailed = .false.
951  h_flow_every = 0
952  h_finab = .false.
953  h_mainout_every = 0
954  heating_frac = 0.4d0
955  heating_density = 1d11
956  heating_mode = 0
957  heating_t9_tol = 1d-4
958  htpf_file = trim(adjustl(win_path))//"datafile2.txt"
959  initemp_cold = 9.e0
960  initemp_hot = 9.e0
961  initial_stepsize = 1.d-12
962  interp_mode = 5
963  isotopes_file = trim(adjustl(win_path))//"winvne_v2.0.dat"
964  iwformat = 0
965  iwinterp = 0
966  le = "2.0e51"
967  lebar = "2.7e51"
968  lx = "2.0e51"
969  lxbar = "2.7e51"
970  mainout_every = 1
971  net_source = trim(adjustl(win_path))//"sunet_complete"
972  neutrino_loss_file = trim(adjustl(win_path))//"nu_loss_data.dat"
973  nfission_file = trim(adjustl(win_path))//"FISS_Mumpower"
974  nrdiag_every = 0
975  nr_tol = 1.e-5
976  nr_maxcount = 3
977  nr_mincount = 2
978  nse_calc_every = 1
979  nse_delt_t9min = 1d-16
980  nse_max_it = 25
981  nse_nr_tol = 1d-6
982  nse_descend_t9start = 100.0
983  nse_solver = 0
984  nsep_energies_file = trim(adjustl(win_path))//"frdm_sn.dat"
985  nsetemp_hot = 8.e0
986  nsetemp_cold = 7.e0
987  nuflag = 0
988  nu_max_time = -1d0 ! For CCSN 1d2 may be good e.g. Roberts & Reddy 2017 (https://ui.adsabs.harvard.edu/abs/2017hsn..book.1605R/abstract)
989  nu_min_l = 1d0
990  nu_min_t = 1d0
991  neutrino_mode = 'analytic'
992  nuchannel_file = trim(adjustl(win_path))//"nu_channels"
993  nu_loss_every = 0
994  h_nu_loss_every = 0
995  nunucleo_rates_file = trim(adjustl(win_path))//"neunucleons.dat"
996  nurates_file = trim(adjustl(win_path))//"nucross.dat"
997  out_every = 10
998  reaclib_file = trim(adjustl(win_path))//"Reaclib_18_9_20"
1006  fission_rates_beta_delayed = trim(adjustl(win_path))//"fissionrates_beta_delayed_mp22"
1007  fission_rates_n_induced = trim(adjustl(win_path))//"fissionrates_n_induced"
1008  fission_rates_spontaneous = trim(adjustl(win_path))//"fissionrates_spontaneous"
1009  read_initial_composition = .false.
1010  rho_analytic = "1.e12"
1011  rkm_analytic = "50.e0"
1012  screening_mode = 1
1013  seed_file = "seed"
1014  seed_format = "Name X"
1015  sfission_file = trim(adjustl(win_path))//"FISS_Mumpower"
1016  snapshot_every = 0
1017  h_snapshot_every = 0
1018  snapshot_file = trim(adjustl(win_path))//"snapshot_freq.dat"
1019  solver = 0
1020  t_analytic = 0.e0
1021  t9_analytic = "10.e0"
1022  tabulated_rates_file = trim(adjustl(win_path))//"talysNGrates.dat"
1023  tabulated_temperature_file = "default"
1026  timescales_every = 0
1027  h_timescales_every = 0
1028  timestep_max = 2.0e0
1029  timestep_factor = 1.0e-1
1030  timestep_hydro_factor = 5.0e-2
1031  timestep_ymin = 1.0e-10
1032  timestep_traj_limit = .true.
1033  track_nuclei_every = 0
1035  top_engen_every = 0
1036  track_nuclei_file = trim(adjustl(win_path))//"track_nuclei_file"
1037  prepared_network_path = "None"
1038  trajectory_format = "time temp dens rad ye"
1039  trajectory_mode = "from_file"
1040  trajectory_file = trim(adjustl(win_path))//"trajectory.dat"
1044  use_htpf = .false.
1045  use_tabulated_rates = .false.
1046  use_beta_decay_file = .false.
1047  use_prepared_network = .false.
1048  use_alpha_decay_file = .false.
1049  use_thermal_nu_loss = .true.
1050  use_timmes_mue = .true.
1051  use_detailed_balance = .false.
1052  use_detailed_balance_q_reac = .false.
1053  use_neutrino_loss_file = .false.
1054  weak_rates_file = trim(adjustl(win_path))//"theoretical_weak_rates.dat"
1055  ye_analytic = "0.1e0"
1056 
1057 end subroutine set_default_param
1058 
1059 !>
1060 !! Output parameters to a file
1061 !!
1062 !! Parameters are sorted in alphabetical order
1063 !!
1064 subroutine output_param
1066  implicit none
1067  !
1068  integer :: ofile
1069  character(3) :: yesno
1070 
1071  if (verbose_level .ge. 2) then
1072 
1073  ofile= open_outfile("param.out")
1074  write(ofile,'(A,I5)') 'adapt_stepsize_maxcount = ' , adapt_stepsize_maxcount
1075  write(ofile,'(2A)') 'alpha_decay_ignore_all = ' , yesno(alpha_decay_ignore_all)
1076  write(ofile,'(3A)') 'alpha_decay_src_ignore = "', trim(alpha_decay_src_ignore),'"'
1077  write(ofile,'(3A)') 'alpha_decay_file = "', trim(alpha_decay_file),'"'
1078  write(ofile,'(A,I5)') 'alpha_decay_zmax = ' , alpha_decay_zmax
1079  write(ofile,'(A,I5)') 'alpha_decay_zmin = ' , alpha_decay_zmin
1080  write(ofile,'(3A)') 'beta_decay_file = "', trim(beta_decay_file),'"'
1081  write(ofile,'(3A)') 'beta_decay_src_ignore = "', trim(beta_decay_src_ignore),'"'
1082  write(ofile,'(3A)') 'bfission_file = "', trim(bfission_file),'"'
1083  write(ofile,'(2A)') 'calc_nsep_energy = ' , yesno(calc_nsep_energy)
1084  write(ofile,'(3A)') 'chem_pot_file = "', trim(chem_pot_file),'"'
1085  write(ofile,'(2A)') 'custom_snapshots = ' , yesno(custom_snapshots)
1086  write(ofile,'(3A)') 'detailed_balance_src_ignore = "', trim(detailed_balance_src_ignore),'"'
1087  write(ofile,'(3A)') 'detailed_balance_src_q_reac = "', trim(detailed_balance_src_q_reac),'"'
1088  write(ofile,'(3A)') 'detailed_balance_src_q_winvn= "', trim(detailed_balance_src_q_winvn),'"'
1089  write(ofile,'(A,I5)') 'engen_every = ' , engen_every
1090  write(ofile,'(3A)') 'Enue ="' , trim(enue),'"'
1091  write(ofile,'(3A)') 'Enuebar ="' , trim(enuebar),'"'
1092  write(ofile,'(3A)') 'Enux ="' , trim(enux),'"'
1093  write(ofile,'(3A)') 'Enuxbar ="' , trim(enuxbar),'"'
1094  write(ofile,'(A,I1)') 'expansiontype = ' , expansiontype
1095  write(ofile,'(A,I4)') 'extrapolation_width = ' , extrapolation_width
1096  write(ofile,'(A,es14.7)') 'final_dens =' , final_dens
1097  write(ofile,'(A,es14.7)') 'final_temp =' , final_temp
1098  write(ofile,'(A,es14.7)') 'final_time =' , final_time
1099  write(ofile,'(A,I1)') 'fissflag = ' , fissflag
1100  write(ofile,'(A,I1)') 'fission_frag_beta_delayed = ' , fission_frag_beta_delayed
1101  write(ofile,'(A,I1)') 'fission_frag_missing = ' , fission_frag_missing
1102  write(ofile,'(A,I1)') 'fission_frag_n_induced = ' , fission_frag_n_induced
1103  write(ofile,'(A,I1)') 'fission_frag_spontaneous = ' , fission_frag_spontaneous
1104  write(ofile,'(A,I1)') 'fission_format_beta_delayed = ' , fission_format_beta_delayed
1105  write(ofile,'(A,I1)') 'fission_format_n_induced = ' , fission_format_n_induced
1106  write(ofile,'(A,I1)') 'fission_format_spontaneous = ' , fission_format_spontaneous
1107  write(ofile,'(3A)') 'fission_rates_beta_delayed = "', trim(fission_rates_beta_delayed),'"'
1108  write(ofile,'(3A)') 'fission_rates_n_induced = "', trim(fission_rates_n_induced),'"'
1109  write(ofile,'(3A)') 'fission_rates_spontaneous = "', trim(fission_rates_spontaneous),'"'
1110  write(ofile,'(A,I5)') 'flow_every = ' , flow_every
1111  write(ofile,'(A,es14.7)') 'freeze_rate_temp =' , freeze_rate_temp
1112  write(ofile,'(A,es14.7)') 'gear_cFactor =' , gear_cfactor
1113  write(ofile,'(A,es14.7)') 'gear_eps =' , gear_eps
1114  write(ofile,'(A,es14.7)') 'gear_escale =' , gear_escale
1115  write(ofile,'(2A)') 'gear_ignore_adapt_stepsize = ' , yesno(gear_ignore_adapt_stepsize)
1116  write(ofile,'(A,es14.7)') 'gear_nr_eps =' , gear_nr_eps
1117  write(ofile,'(A,I5)') 'gear_nr_maxcount = ' , gear_nr_maxcount
1118  write(ofile,'(A,I5)') 'gear_nr_mincount = ' , gear_nr_mincount
1119  write(ofile,'(A,es14.7)') 'gear_timestep_max =' , gear_timestep_max
1120  write(ofile,'(2A)') 'h_custom_snapshots = ' , yesno(h_custom_snapshots)
1121  write(ofile,'(2A)') 'h_engen_detailed = ' , yesno(h_engen_detailed)
1122  write(ofile,'(A,I5)') 'h_engen_every = ' , h_engen_every
1123  write(ofile,'(2A)') 'h_finab = ' , yesno(h_finab)
1124  write(ofile,'(A,I5)') 'h_flow_every = ' , h_flow_every
1125  write(ofile,'(A,I5)') 'h_mainout_every = ' , h_mainout_every
1126  write(ofile,'(A,I5)') 'h_nu_loss_every = ' , h_nu_loss_every
1127  write(ofile,'(A,I5)') 'h_snapshot_every = ' , h_snapshot_every
1128  write(ofile,'(A,I5)') 'h_track_nuclei_every = ' , h_track_nuclei_every
1129  write(ofile,'(A,I5)') 'h_timescales_every = ' , h_timescales_every
1130  write(ofile,'(A,es14.7)') 'heating_density =' , heating_density
1131  write(ofile,'(A,es14.7)') 'heating_frac =' , heating_frac
1132  write(ofile,'(A,I1)') 'heating_mode = ' , heating_mode
1133  write(ofile,'(A,es14.7)') 'heating_T9_tol =' , heating_t9_tol
1134  write(ofile,'(3A)') 'htpf_file = "', trim(htpf_file),'"'
1135  write(ofile,'(A,es14.7)') 'initemp_cold =' , initemp_cold
1136  write(ofile,'(A,es14.7)') 'initemp_hot =' , initemp_hot
1137  write(ofile,'(A,es14.7)') 'initial_stepsize =' , initial_stepsize
1138  write(ofile,'(3A)') 'isotopes_file = "', trim(isotopes_file),'"'
1139  write(ofile,'(A,I1)') 'interp_mode = ' , interp_mode
1140  write(ofile,'(A,I1)') 'iwformat = ' , iwformat
1141  write(ofile,'(A,I1)') 'iwinterp = ' , iwinterp
1142  write(ofile,'(3A)') 'Le ="' , trim(le),'"'
1143  write(ofile,'(3A)') 'Lebar ="' , trim(lebar),'"'
1144  write(ofile,'(3A)') 'Lx ="' , trim(lx),'"'
1145  write(ofile,'(3A)') 'Lxbar ="' , trim(lxbar),'"'
1146  write(ofile,'(A,I5)') 'mainout_every = ' , mainout_every
1147  write(ofile,'(3A)') 'net_source = "', trim(net_source),'"'
1148  write(ofile,'(3A)') 'nfission_file = "', trim(nfission_file),'"'
1149  write(ofile,'(3A)') 'neutrino_loss_file = "', trim(neutrino_loss_file),'"'
1150  write(ofile,'(3A)') 'neutrino_mode = ' , trim(neutrino_mode)
1151  write(ofile,'(A,I5)') 'nr_maxcount = ' , nr_maxcount
1152  write(ofile,'(A,I5)') 'nr_mincount = ' , nr_mincount
1153  write(ofile,'(A,es14.7)') 'nr_tol =' , nr_tol
1154  write(ofile,'(A,I5)') 'nrdiag_every = ' , nrdiag_every
1155  write(ofile,'(A,I5)') 'nse_calc_every = ' , nse_calc_every
1156  write(ofile,'(A,es14.7)') 'nse_delt_t9min =' , nse_delt_t9min
1157  write(ofile,'(A,es14.7)') 'nse_descend_t9start =' , nse_descend_t9start
1158  write(ofile,'(A,I5)') 'nse_max_it = ' , nse_max_it
1159  write(ofile,'(A,es14.7)') 'nse_nr_tol =' , nse_nr_tol
1160  write(ofile,'(A,I5)') 'nse_solver = ' , nse_solver
1161  write(ofile,'(3A)') 'nsep_energies_file = "', trim(nsep_energies_file),'"'
1162  write(ofile,'(A,es14.7)') 'nsetemp_cold =' , nsetemp_cold
1163  write(ofile,'(A,es14.7)') 'nsetemp_hot =' , nsetemp_hot
1164  write(ofile,'(A,I1)') 'nuflag = ' , nuflag
1165  write(ofile,'(3A)') 'nuchannel_file = "', trim(nuchannel_file),'"'
1166  write(ofile,'(A,I5)') 'nu_loss_every = ' , nu_loss_every
1167  write(ofile,'(A,es14.7)') 'nu_max_time = ' , nu_max_time
1168  write(ofile,'(A,es14.7)') 'nu_min_L = ' , nu_min_l
1169  write(ofile,'(A,es14.7)') 'nu_min_T = ' , nu_min_t
1170  write(ofile,'(3A)') 'nunucleo_rates_file = "', trim(nunucleo_rates_file),'"'
1171  write(ofile,'(3A)') 'nurates_file = "', trim(nurates_file),'"'
1172  write(ofile,'(A,I5)') 'out_every = ' , out_every
1173  write(ofile,'(3A)') 'prepared_network_path = "', trim(prepared_network_path),'"'
1174  write(ofile,'(3A)') 'reaclib_file = "', trim(reaclib_file),'"'
1175  write(ofile,'(2A)') 'read_initial_composition = ' , yesno(read_initial_composition)
1176  write(ofile,'(3A)') 'rho_analytic = "', trim(rho_analytic),'"'
1177  write(ofile,'(3A)') 'Rkm_analytic = "', trim(rkm_analytic),'"'
1178  write(ofile,'(A,I1)') 'screening_mode = ' , screening_mode
1179  write(ofile,'(3A)') 'seed_file = "', trim(seed_file),'"'
1180  write(ofile,'(3A)') 'seed_format = "', trim(seed_format),'"'
1181  write(ofile,'(3A)') 'sfission_file = "', trim(sfission_file),'"'
1182  write(ofile,'(A,I5)') 'snapshot_every = ' , snapshot_every
1183  write(ofile,'(3A)') 'snapshot_file = "', trim(snapshot_file),'"'
1184  write(ofile,'(A,I1)') 'solver = ' , solver
1185  write(ofile,'(A,es14.7)') 't_analytic =' , t_analytic
1186  write(ofile,'(3A)') 'T9_analytic = "', trim(t9_analytic),'"'
1187  write(ofile,'(3A)') 'tabulated_rates_file = "', trim(tabulated_rates_file),'"'
1188  write(ofile,'(3A)') 'tabulated_temperature_file = "', trim(tabulated_temperature_file),'"'
1189  write(ofile,'(A,es14.7)') 'temp_reload_exp_weak_rates = ' , temp_reload_exp_weak_rates
1190  write(ofile,'(A,I1)') 'termination_criterion = ' , termination_criterion
1191  write(ofile,'(A,I5)') 'timescales_every = ' , timescales_every
1192  write(ofile,'(A,es14.7)') 'timestep_max =' , timestep_max
1193  write(ofile,'(A,es14.7)') 'timestep_factor =' , timestep_factor
1194  write(ofile,'(A,es14.7)') 'timestep_hydro_factor =' , timestep_hydro_factor
1195  write(ofile,'(A,es14.7)') 'timestep_Ymin =' , timestep_ymin
1196  write(ofile,'(2A)') 'timestep_traj_limit = ' , yesno(timestep_traj_limit)
1197  write(ofile,'(A,I5)') 'top_engen_every = ' , top_engen_every
1198  write(ofile,'(A,I5)') 'track_nuclei_every = ' , track_nuclei_every
1199  write(ofile,'(3A)') 'track_nuclei_file = "', trim(track_nuclei_file),'"'
1200  write(ofile,'(3A)') 'trajectory_file = "', trim(trajectory_file),'"'
1201  write(ofile,'(3A)') 'trajectory_format = "', trim(trajectory_format),'"'
1202  write(ofile,'(3A)') 'trajectory_mode = "', trajectory_mode,'"'
1203  write(ofile,'(2A)') 'use_alpha_decay_file = ' , yesno(use_alpha_decay_file)
1204  write(ofile,'(2A)') 'use_beta_decay_file = ' , yesno(use_beta_decay_file)
1205  write(ofile,'(2A)') 'use_detailed_balance = ' , yesno(use_detailed_balance)
1206  write(ofile,'(2A)') 'use_detailed_balance_q_reac = ' , yesno(use_detailed_balance_q_reac)
1207  write(ofile,'(2A)') 'use_htpf = ' , yesno(use_htpf)
1208  write(ofile,'(2A)') 'use_neutrino_loss_file = ' , yesno(use_neutrino_loss_file)
1209  write(ofile,'(2A)') 'use_prepared_network = ' , yesno(use_prepared_network)
1210  write(ofile,'(2A)') 'use_tabulated_rates = ' , yesno(use_tabulated_rates)
1211  write(ofile,'(2A)') 'use_thermal_nu_loss = ' , yesno(use_thermal_nu_loss)
1212  write(ofile,'(2A)') 'use_timmes_mue = ' , yesno(use_timmes_mue)
1213  write(ofile,'(3A)') 'weak_rates_file = "', trim(weak_rates_file),'"'
1214  write(ofile,'(3A)') 'Ye_analytic = "', trim(ye_analytic),'"'
1215 
1216  close(ofile)
1217  end if
1218 
1219 end subroutine output_param
1220 
1221 
1222 !>
1223 !! Check for consistency of parameter
1224 !!
1225 !! Some parameters might not work together or might cause inconsistencies.
1226 !! This routine checks the user input and complains.
1227 !!
1228 !! @author: M. Reichert
1229 !!
1230 !! \b Edited:
1231 !! - 21.05.19, MR
1232 !! .
1233 subroutine check_param
1234  implicit none
1235  integer :: help_int !< Helper integer
1236 
1237  ! NSE temperatures are not set correct
1238  if (nsetemp_cold .gt. nsetemp_hot) then
1239  call raise_exception('The parameter "nsetemp_cold" ('//trim(adjustl(num_to_str(nsetemp_cold)))//&
1240  ' GK) should be smaller than "nsetemp_hot" ('//&
1241  trim(adjustl(num_to_str(nsetemp_cold)))//' GK).' ,&
1242  "check_param", 340006)
1243  end if
1244 
1245  ! Init temperatures are correct
1246  if (initemp_cold .gt. initemp_hot) then
1247  call raise_exception('The parameter "initemp_cold" ('//trim(adjustl(num_to_str(initemp_cold)))//&
1248  ' GK) should be smaller than "initemp_hot" ('//&
1249  trim(adjustl(num_to_str(initemp_hot)))//' GK).' ,&
1250  "check_param",340007)
1251  endif
1252 
1253  if (nr_mincount .gt. nr_maxcount) then
1254  call raise_exception('The parameter "nr_mincount" ('//trim(adjustl(int_to_str(nr_mincount)))//&
1255  ') should be smaller than "nr_maxcount" ('//&
1256  trim(adjustl(int_to_str(nr_maxcount)))//').' ,&
1257  "check_param",340008)
1258  end if
1259 
1260  if (gear_nr_mincount .gt. gear_nr_maxcount) then
1261  call raise_exception('The parameter "gear_nr_mincount" ('//trim(adjustl(int_to_str(gear_nr_mincount)))//&
1262  ') should be smaller than "gear_nr_maxcount" ('//&
1263  trim(adjustl(int_to_str(gear_nr_maxcount)))//').' ,&
1264  "check_param",340008)
1265  end if
1266 
1267  ! Check that termination criterium can be fullfilled
1268  if ((termination_criterion .eq. 0) .and. (trim(adjustl(trajectory_mode)) .eq. "analytic")) then
1269  call raise_exception('The parameter "termination_criterion" is set to "0" (after end of trajectory)'//&
1270  'but the trajectory mode is set to "analytic".',&
1271  "check_param",340009)
1272  end if
1273 
1274  ! Ensure that prepared_network_path ends with a slash, i.e., that it is a folder
1275  if (use_prepared_network) then
1276  help_int = len(trim(adjustl(prepared_network_path)))
1277  if (prepared_network_path(help_int:help_int) .ne. "/") then
1278  prepared_network_path = trim(adjustl(prepared_network_path))//"/"
1279  end if
1280  end if
1281 
1282 
1283  ! Check that there are no inconsistencies in the parameters of the prepared binary files
1284  ! and the parameter file
1286 
1287 end subroutine check_param
1288 
1289 
1290 
1291 
1292 !> Search for similar existing parameters.
1293 !!
1294 !! Takes a list of parameters that are separated by ":" and a comparison
1295 !! parameter and returns the most similar parameter from the list. Furthermore,
1296 !! a score is returned that gives a measure of the similarity of the strings.
1297 !! This function is only called if a user specified parameter was not included
1298 !! in the list of possible parameters.
1299 !!
1300 !! @author M. Reichert
1301 !! @date 02.11.22
1302 subroutine search_close_parameter(possible_pars,input_par,score,cl_par)
1303  implicit none
1304  character(*),intent(in) :: possible_pars !< All possible parameter, long string
1305  ! that is separated by ":"
1306  character(*),intent(in) :: input_par !< Parameter to compare
1307  character(*),intent(out) :: cl_par !< Most similar parameter
1308  real(r_kind),intent(out) :: score !< Minimum distance between parameters
1309  character(999) :: helper_char !< Helping string
1310  character(999) :: ms_par !< Most similar parameter
1311  real(r_kind) :: cl_dist !< Closest distance
1312  real(r_kind) :: h_dist !< helping distance
1313  integer :: length !< length of closest word
1314  integer :: k !< Loop variable
1315 
1316  ms_par = "" ! Initialize empty
1317  cl_dist = 999 ! Initialize with large number
1318  length = 999 ! Initialize with large number
1319  helper_char = "" ! Initialize empty
1320  ! Start from 2 since first character is a ":"
1321  do k=2,len(possible_pars)
1322 
1323  ! Separate the parameters that are separated by ":"
1324  if (possible_pars(k:k) .ne. ":") then
1325  helper_char = trim(adjustl(helper_char))//possible_pars(k:k)
1326  end if
1327 
1328  if ((possible_pars(k:k) .eq. ":") .or. (k .eq. len(possible_pars))) then
1329  ! Calculate Levenshtein distance and check similarity, only take the
1330  ! most similar one
1331  h_dist = levenshteindistance(trim(adjustl(helper_char)),trim(adjustl(input_par)))
1332  if (h_dist .lt. cl_dist) then
1333  cl_dist = h_dist
1334  ms_par = trim(adjustl(helper_char))
1335  end if
1336  ! Reset the parameter
1337  helper_char = ""
1338  end if
1339 
1340  end do
1341 
1342  ! Fill the output
1343  score = cl_dist
1344  cl_par = trim(adjustl(ms_par))
1345 
1346 end subroutine search_close_parameter
1347 
1348 
1349 !> Calculates the Levenshtein distance between two strings
1350 !!
1351 !! The Levenshtein distance gives a measure of the similarity between
1352 !! two strings. The similarity is expressed in terms of a float afterwards.
1353 !! This routine follows the pseudocode [here](https://en.wikipedia.org/wiki/Levenshtein_distance)
1354 !!
1355 !! @author M. Reichert
1356 !! @date 02.11.22
1357 function levenshteindistance(par1,par2) result(dist)
1358  implicit none
1359  character(*),intent(in) :: par1 !< Input string 1
1360  character(*),intent(in) :: par2 !< Input string 2
1361  real(r_kind) :: dist !< Measure of the similarity
1362  character(1) :: upper1 !< Helper character
1363  character(1) :: upper2 !< Helper character
1364  integer :: i, j, h !< Loop variables
1365  integer :: m, n !< Lengths of par1 and par2
1366  integer :: stat !< Allocation status
1367  real(r_kind) :: scost !< Substitution cost
1368  real(r_kind),dimension(:,:),allocatable :: d !< Helper matrix
1369 
1370  ! Get the length of the strings
1371  m = len(par1)
1372  n = len(par2)
1373 
1374  allocate(d(0:m,0:n),stat=stat)
1375  if (stat .ne. 0) call raise_exception('Allocation of "d" failed.',&
1376  "LevenshteinDistance",320001)
1377 
1378  ! Initialize with zeros
1379  d(:,:) = 0
1380 
1381  ! Fill the first column
1382  do i=1, m
1383  d(i, 0) = i
1384  end do
1385  ! Fill the first row
1386  do j=1, n
1387  d(0, j) = j
1388  end do
1389 
1390  do j=1,n
1391  do i=1,m
1392  if (par1(i:i) .eq. par2(j:j)) then
1393  scost = 0
1394  else
1395  ! Check if it is only a case insensitivity
1396  h = iachar(par1(i:i))
1397  if (h>= iachar("a") .and. h<=iachar("z") ) then
1398  upper1 = achar(iachar(par1(i:i))-32)
1399  else
1400  upper1 = par1(i:i)
1401  end if
1402  h = iachar(par2(j:j))
1403  if (h>= iachar("a") .and. h<=iachar("z") ) then
1404  upper2 = achar(iachar(par2(j:j))-32)
1405  else
1406  upper2 = par2(j:j)
1407  end if
1408 
1409  ! It is not as bad when its only a mismatch in the upper/lower case
1410  if (upper2 .eq. upper1) then
1411  scost = 0.2
1412  else
1413  scost = 1
1414  end if
1415  end if
1416  ! Calculate the total cost of substitutions and exchanges
1417  d(i,j) = min(d(i-1,j)+1, d(i, j-1) + 1, d(i-1, j-1) + scost)
1418  end do
1419  end do
1420 
1421  ! Return value
1422  dist = d(m,n)
1423 
1424 end function levenshteindistance
1425 
1426 
1427 !> Read important parameters from a binary file and check for consistency
1428 !!
1429 !! This routine reads important parameters from a binary file and checks
1430 !! if they are consistent with the current run. This is done to check if
1431 !! the binary files are compatible with the current parameter file.
1432 !!
1433 !! @note This routine is only called if the parameter "use_prepared_network"
1434 !! is set to ".true."
1435 !!
1436 !! @author M. Reichert
1437 !! @date 21.07.23
1441  implicit none
1442  ! Internal variables
1443  integer :: file_id !< File ID
1444  integer :: int_helper !< Integer helper
1445  logical :: log_helper !< logical helper
1446 
1447  if (use_prepared_network) then
1448  ! Only check if the file exists otherwise other errors may be thrown or
1449  ! use_prepared_network may be set to false later on for the preparation step
1450  inquire(file=trim(adjustl(prepared_network_path))//trim(adjustl(par_binary_name)),exist=log_helper)
1451 
1452  if ((.not. log_helper) .or. (data_creation_mode)) then
1453  return
1454  end if
1455 
1456  ! Open an unformatted file
1457  file_id = open_unformatted_infile(trim(adjustl(prepared_network_path))//trim(adjustl(par_binary_name)))
1458  read(file_id) int_helper
1459  if (int_helper .ne. nuflag) then
1460  call raise_exception("The prepared network file does not match the nuflag of the current run. "// &
1461  "Got "//int_to_str(nuflag)//" and expected "//int_to_str(int_helper)//". "//&
1462  "Please check the prepared network file.",&
1463  "read_sanity_check_prepared_network",340010)
1464  end if
1465  read(file_id) int_helper
1466  if (int_helper .ne. fissflag) then
1467  call raise_exception("The prepared network file does not match the fissflag of the current run. "// &
1468  "Got "//int_to_str(fissflag)//" and expected "//int_to_str(int_helper)//". "//&
1469  "Please check the prepared network file.",&
1470  "read_sanity_check_prepared_network",340010)
1471  end if
1472  read(file_id) int_helper
1473  if (int_helper .ne. iwformat) then
1474  call raise_exception("The prepared network file does not match the iwformat of the current run. "// &
1475  "Got "//int_to_str(iwformat)//" and expected "//int_to_str(int_helper)//". "//&
1476  "Please check the prepared network file.",&
1477  "read_sanity_check_prepared_network",340010)
1478  end if
1479  read(file_id) int_helper
1480  if (int_helper .ne. iwinterp) then
1481  call raise_exception("The prepared network file does not match the iwinterp of the current run. "// &
1482  "Got "//int_to_str(iwinterp)//" and expected "//int_to_str(int_helper)//". "//&
1483  "Please check the prepared network file.",&
1484  "read_sanity_check_prepared_network",340010)
1485  end if
1486  read(file_id) log_helper
1487  if (log_helper .neqv. use_alpha_decay_file) then
1488  call raise_exception("The prepared network file does not match the use_alpha_decay_file of the current run. "// &
1489  "Please check the prepared network file.",&
1490  "read_sanity_check_prepared_network",340010)
1491  end if
1492  read(file_id) log_helper
1493  if (log_helper .neqv. use_beta_decay_file) then
1494  call raise_exception("The prepared network file does not match the use_beta_decay_file of the current run. "// &
1495  "Please check the prepared network file.",&
1496  "read_sanity_check_prepared_network",340010)
1497  end if
1498  read(file_id) log_helper
1499  if (log_helper .neqv. use_tabulated_rates) then
1500  call raise_exception("The prepared network file does not match the use_tabulated_rates of the current run. "// &
1501  "Please check the prepared network file.",&
1502  "read_sanity_check_prepared_network",340010)
1503  end if
1504  read(file_id) log_helper
1505  if (log_helper .neqv. use_detailed_balance) then
1506  call raise_exception("The prepared network file does not match the use_detailed_balance of the current run. "// &
1507  "Please check the prepared network file.",&
1508  "read_sanity_check_prepared_network",340010)
1509  end if
1510  read(file_id) log_helper
1511  if (log_helper .neqv. use_neutrino_loss_file) then
1512  call raise_exception("The prepared network file does not match the use_neutrino_loss_file of the current run. "// &
1513  "Please check the prepared network file.",&
1514  "read_sanity_check_prepared_network",340010)
1515  end if
1516  read(file_id) log_helper
1517  if (log_helper .neqv. use_htpf) then
1518  call raise_exception("The prepared network file does not match the use_htpf of the current run. "// &
1519  "Please check the prepared network file.",&
1520  "read_sanity_check_prepared_network",340010)
1521  end if
1522  read(file_id) log_helper
1523  if (log_helper .neqv. use_timmes_mue) then
1524  call raise_exception("The prepared network file does not match the use_timmes_mue of the current run. "// &
1525  "Please check the prepared network file.",&
1526  "read_sanity_check_prepared_network",340010)
1527  end if
1528 
1529  close(file_id)
1530 
1531  end if
1533 
1534 
1535 
1536 !>
1537 !! Output relevant parameters to a file in the prepared network path
1538 !!
1539 !! Parameters are sorted according to category
1540 !!
1543  implicit none
1544  !
1545  character(len=*), intent(in) :: path !< Path to the output directory
1546  integer :: ofile
1547  character(3) :: yesno
1548 
1549  ofile= open_outfile(path//"Information.out")
1550 
1551  ! Write header
1552  write(ofile,'(A)') 'Folder containing network and reaction data in unformatted binary format.'
1553  write(ofile,'(A)') ''
1554  write(ofile,'(A)') ''
1555  write(ofile,'(A)') 'The following list contains relevant parameters that were used to create the network data:'
1556  write(ofile,'(A)') '=========================================================================================='
1557  write(ofile,'(A)') ''
1558 
1559  ! General files
1560  write(ofile,'(3A)') 'isotopes_file = "', trim(isotopes_file),'"'
1561  write(ofile,'(3A)') 'net_source = "', trim(net_source),'"'
1562  write(ofile,'(3A)') 'reaclib_file = "', trim(reaclib_file),'"'
1563  write(ofile,'(A)') ''
1564 
1565 
1566  ! Additional alpha decays
1567  write(ofile,'(2A)') 'use_alpha_decay_file = ' , yesno(use_alpha_decay_file)
1568  if (use_alpha_decay_file) then
1569  write(ofile,'(2A)') 'alpha_decay_ignore_all = ' , yesno(alpha_decay_ignore_all)
1570  write(ofile,'(3A)') 'alpha_decay_src_ignore = "', trim(alpha_decay_src_ignore),'"'
1571  write(ofile,'(3A)') 'alpha_decay_file = "', trim(alpha_decay_file),'"'
1572  write(ofile,'(A,I5)') 'alpha_decay_zmax = ' , alpha_decay_zmax
1573  write(ofile,'(A,I5)') 'alpha_decay_zmin = ' , alpha_decay_zmin
1574  end if
1575  write(ofile,'(A)') ''
1576 
1577 
1578  ! Additional beta decays
1579  write(ofile,'(2A)') 'use_beta_decay_file = ' , yesno(use_beta_decay_file)
1580  if (use_beta_decay_file) then
1581  write(ofile,'(3A)') 'beta_decay_file = "', trim(beta_decay_file),'"'
1582  write(ofile,'(3A)') 'beta_decay_src_ignore = "', trim(beta_decay_src_ignore),'"'
1583  end if
1584  write(ofile,'(A)') ''
1585 
1586 
1587  ! Include detailed balance
1588  write(ofile,'(2A)') 'use_detailed_balance = ' , yesno(use_detailed_balance)
1589  if (use_detailed_balance) then
1590  write(ofile,'(2A)') 'use_detailed_balance_q_reac = ' , yesno(use_detailed_balance_q_reac)
1591  write(ofile,'(3A)') 'detailed_balance_src_ignore = "', trim(detailed_balance_src_ignore),'"'
1592  write(ofile,'(3A)') 'detailed_balance_src_q_reac = "', trim(detailed_balance_src_q_reac),'"'
1593  write(ofile,'(3A)') 'detailed_balance_src_q_winvn= "', trim(detailed_balance_src_q_winvn),'"'
1594  end if
1595  write(ofile,'(A)') ''
1596 
1597 
1598  ! Theoretical weak reates
1599  write(ofile,'(A,I1)') 'iwformat = ' , iwformat
1600  if (iwformat .gt. 0) then
1601  write(ofile,'(A,I1)') 'iwinterp = ' , iwinterp
1602  write(ofile,'(3A)') 'weak_rates_file = "', trim(weak_rates_file),'"'
1603  write(ofile,'(3A)') 'chem_pot_file = "', trim(chem_pot_file),'"'
1604  write(ofile,'(2A)') 'use_timmes_mue = ' , yesno(use_timmes_mue)
1605  end if
1606  write(ofile,'(A)') ''
1607 
1608 
1609  ! Tabulated rates
1610  write(ofile,'(2A)') 'use_tabulated_rates = ' , yesno(use_tabulated_rates)
1611  if (use_tabulated_rates) then
1612  write(ofile,'(3A)') 'tabulated_rates_file = "', trim(tabulated_rates_file),'"'
1613  write(ofile,'(3A)') 'tabulated_temperature_file = "', trim(tabulated_temperature_file),'"'
1614  end if
1615  write(ofile,'(A)') ''
1616 
1617  ! High temperature partition functions
1618  write(ofile,'(2A)') 'use_htpf = ' , yesno(use_htpf)
1619  if (use_htpf) then
1620  write(ofile,'(3A)') 'htpf_file = "', trim(htpf_file),'"'
1621  end if
1622  write(ofile,'(A)') ''
1623 
1624  ! Neutrinos
1625  write(ofile,'(A,I1)') 'nuflag = ' , nuflag
1626  if ((nuflag) .gt. 0) then
1627  write(ofile,'(3A)') 'nunucleo_rates_file = "', trim(nunucleo_rates_file),'"'
1628  if (nuflag .gt. 1) then
1629  write(ofile,'(3A)') 'nuchannel_file = "', trim(nuchannel_file),'"'
1630  write(ofile,'(3A)') 'nurates_file = "', trim(nurates_file),'"'
1631  end if
1632  end if
1633  write(ofile,'(A)') ''
1634 
1635  ! Fission
1636  write(ofile,'(A,I1)') 'fissflag = ' , fissflag
1637  if (fissflag .gt. 0) then
1638  write(ofile,'(3A)') 'fission_rates_beta_delayed = "', trim(fission_rates_beta_delayed),'"'
1639  write(ofile,'(3A)') 'fission_rates_n_induced = "', trim(fission_rates_n_induced),'"'
1640  write(ofile,'(3A)') 'fission_rates_spontaneous = "', trim(fission_rates_spontaneous),'"'
1641  write(ofile,'(A,I1)')'fission_format_beta_delayed = "', fission_format_beta_delayed
1642  write(ofile,'(A,I1)')'fission_format_n_induced = "', fission_format_n_induced
1643  write(ofile,'(A,I1)')'fission_format_spontaneous = "', fission_format_spontaneous
1644  if (fissflag .gt. 3) then
1645  write(ofile,'(3A)') 'nfission_file = "', trim(nfission_file),'"'
1646  end if
1647  if (fissflag .eq. 4) then
1648  write(ofile,'(3A)') 'bfission_file = "', trim(bfission_file),'"'
1649  write(ofile,'(3A)') 'sfission_file = "', trim(sfission_file),'"'
1650  end if
1651  end if
1652  write(ofile,'(A)') ''
1653 
1654  ! Neutrino loss file
1655  write(ofile,'(2A)') 'use_neutrino_loss_file = ' , yesno(use_neutrino_loss_file)
1656  if (use_neutrino_loss_file) then
1657  write(ofile,'(3A)') 'neutrino_loss_file = "', trim(neutrino_loss_file),'"'
1658  end if
1659 
1660  close(ofile)
1661 
1662  end subroutine output_param_prepared_network
1663 
1664 !> Output the parameter data to a binary file
1665 !!
1666 !! This routine outputs important parameters to a binary file.
1667 !! This is exclusively done to check later when reading the binary
1668 !! rate files.
1669 !!
1670 !! @author M. Reichert
1671 !! @date 21.07.23
1674  implicit none
1675  ! Internal variables
1676  character(len=*), intent(in) :: path !< Path to the output directory
1677  integer :: file_id !< File ID
1678 
1679  ! Open an unformatted file
1680  file_id = open_unformatted_outfile(trim(adjustl(path))//trim(adjustl(par_binary_name)))
1681  write(file_id) nuflag
1682  write(file_id) fissflag
1683  write(file_id) iwformat
1684  write(file_id) iwinterp
1685  write(file_id) use_alpha_decay_file
1686  write(file_id) use_beta_decay_file
1687  write(file_id) use_tabulated_rates
1688  write(file_id) use_detailed_balance
1689  write(file_id) use_neutrino_loss_file
1690  write(file_id) use_htpf
1691  write(file_id) use_timmes_mue
1692 
1693  close(file_id)
1694 
1695  end subroutine output_binary_parameter_data
1696 
1697 
1698 end module parameter_class
1699 
1700 
1701 !>
1702 !! Converts .TRUE.->"yes", .FALSE. -> "no"
1703 !!
1704 function yesno(claim) result(quote)
1705  implicit none
1706  character(3) :: quote
1707  logical,intent(in) :: claim
1708  if(claim) then
1709  quote= "yes"
1710  else
1711  quote= "no"
1712  endif
1713 end function
parameter_class::h_track_nuclei_every
integer h_track_nuclei_every
frequency of track nuclei output in hdf5 format
Definition: parameter_class.f90:74
parameter_class::sfission_file
character(max_fname_len) sfission_file
Fission table for spontaneous fission.
Definition: parameter_class.f90:180
parameter_class::iwformat
integer iwformat
defines format of the weak rates (0 = tabulated, 1 = log<ft>)
Definition: parameter_class.f90:81
parameter_class::engen_every
integer engen_every
Energy generation output frequency.
Definition: parameter_class.f90:68
parameter_class::lxbar
character(max_fname_len) lxbar
Muon and Tauon antineutrino luminosities [erg/s].
Definition: parameter_class.f90:195
parameter_class::bfission_file
character(max_fname_len) bfission_file
Fission table for beta-delayed fission.
Definition: parameter_class.f90:178
parameter_class::nse_descend_t9start
real(r_kind) nse_descend_t9start
high initial temperature in GK for winnse_descend subroutine
Definition: parameter_class.f90:125
parameter_class::weights
real(r_kind), dimension(:), allocatable weights
– parameters for efficient numerical integration of effphase in the interval [1,infinity]
Definition: parameter_class.f90:214
parameter_class::out_every
integer out_every
– runtime parameters set when reading parameter file
Definition: parameter_class.f90:61
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
parameter_class::track_nuclei_every
integer track_nuclei_every
frequency of track nuclei output
Definition: parameter_class.f90:73
parameter_class::freeze_rate_temp
real(r_kind) freeze_rate_temp
Tmperature at which rates get frozen (for reacl. rates this should be 1d-2GK)
Definition: parameter_class.f90:84
parameter_class::timestep_ymin
real(r_kind) timestep_ymin
Lower limit of the abundance to contribute to the timestep calculation, default value is 1....
Definition: parameter_class.f90:135
parameter_class::nse_calc_every
integer nse_calc_every
Compute NSE abundances every x step.
Definition: parameter_class.f90:89
parameter_class::output_param
subroutine output_param
Output parameters to a file.
Definition: parameter_class.f90:1065
parameter_class::enuebar
character(max_fname_len) enuebar
average electron-antineutrino energies [MeV]
Definition: parameter_class.f90:193
parameter_class::gear_eps
real(r_kind) gear_eps
Abundance accuracy for gear solver.
Definition: parameter_class.f90:136
parameter_class::weightscalculated
logical weightscalculated
switch to calculated weights and nodes for [1,infinity]
Definition: parameter_class.f90:216
parameter_class::levenshteindistance
real(r_kind) function levenshteindistance(par1, par2)
Calculates the Levenshtein distance between two strings.
Definition: parameter_class.f90:1358
parameter_class::beta_decay_file
character(max_fname_len) beta_decay_file
File for reading in beta decays in different format.
Definition: parameter_class.f90:183
parameter_class::h_timescales_every
integer h_timescales_every
timescales output frequency in hdf5 format
Definition: parameter_class.f90:67
parameter_class::use_detailed_balance
logical use_detailed_balance
Calculate the inverse reactions via detailed balance rather than using them form file.
Definition: parameter_class.f90:97
parameter_class::timestep_factor
real(r_kind) timestep_factor
Factor for the change of the timestep (see nu in Winteler 2012 Eq. 2.49). Default value is 1....
Definition: parameter_class.f90:133
parameter_class::gear_nr_maxcount
integer gear_nr_maxcount
Maximum newton-raphson iterations for gear solver.
Definition: parameter_class.f90:141
parameter_class::beta_decay_src_ignore
character(max_fname_len) beta_decay_src_ignore
Source flag(s) to ignore within the beta decay file.
Definition: parameter_class.f90:95
parameter_class::unit_type
constants and unit conversion factors
Definition: parameter_class.f90:31
parameter_class::engen_alpha
real(r_kind) engen_alpha
energy generation from alpha-decays [MeV/s]
Definition: parameter_class.f90:110
parameter_class::flow_every
integer flow_every
flow output frequency
Definition: parameter_class.f90:64
parameter_class::fission_format_spontaneous
integer fission_format_spontaneous
Format of spontaneous fission rates (0: Off, 1: Reaclib, 2: Halflifes)
Definition: parameter_class.f90:164
parameter_class::timestep_max
real(r_kind) timestep_max
Maximum factor for the change of the timestep. The new timestep is only allowed to be timestep_max * ...
Definition: parameter_class.f90:132
parameter_class::alpha_decay_zmin
integer alpha_decay_zmin
Minimum Z for additional alpha decay rates.
Definition: parameter_class.f90:77
parameter_class::tabulated_temperature_file
character(max_fname_len) tabulated_temperature_file
file containing grid of tabulated temperature file ("default" for default grid)
Definition: parameter_class.f90:171
parameter_class::nse_solver
integer nse_solver
Solver for calculating NSE. 0: Newton-Raphson, 1: Powell's hybrid method.
Definition: parameter_class.f90:118
parameter_class::gear_nr_eps
real(r_kind) gear_nr_eps
Convergence criterion for the newton-raphson of the gear solver.
Definition: parameter_class.f90:139
parameter_class::h_flow_every
integer h_flow_every
flow output frequency in hdf5 format
Definition: parameter_class.f90:65
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
parameter_class::expansiontype
integer expansiontype
defines prescription used for parametrized expansion after the last timestep of the hydro input
Definition: parameter_class.f90:87
parameter_class::matcc
real(r_kind), dimension(:), allocatable matcc
matrices for Clenshaw-Curtis integration
Definition: parameter_class.f90:219
parameter_class::termination_criterion
integer termination_criterion
condition to terminate the simulation ([0]=trajectory_file, 1=final_time, 2=final_temp,...
Definition: parameter_class.f90:127
parameter_class::check_param
subroutine check_param
Check for consistency of parameter.
Definition: parameter_class.f90:1234
yesno
character(3) function yesno(claim)
Converts .TRUE.->"yes", .FALSE. -> "no".
Definition: parameter_class.f90:1705
parameter_class::gear_escale
real(r_kind) gear_escale
Normalization cutoff for gear solver, similar to timestep_Ymin for Euler.
Definition: parameter_class.f90:137
parameter_class::unit_define
subroutine, public unit_define()
Declares values for the elements in unit_type.
Definition: parameter_class.f90:236
parameter_class::read_param
subroutine read_param(parfile)
This function reads the parameter file.
Definition: parameter_class.f90:271
parameter_class::use_neutrino_loss_file
logical use_neutrino_loss_file
Use a file with Qnu values?
Definition: parameter_class.f90:105
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
parameter_class::nsetemp_cold
real(r_kind) nsetemp_cold
T [GK] for the nse->network switch.
Definition: parameter_class.f90:119
parameter_class::timescales_every
integer timescales_every
timescales output frequency
Definition: parameter_class.f90:66
parameter_class::gear_cfactor
real(r_kind) gear_cfactor
Conservative timestep factor for gear solver [0.1, ... , 0.4].
Definition: parameter_class.f90:138
parameter_class::output_param_prepared_network
subroutine output_param_prepared_network(path)
Output relevant parameters to a file in the prepared network path.
Definition: parameter_class.f90:1542
parameter_class::use_beta_decay_file
logical use_beta_decay_file
switch for using different format for beta decays
Definition: parameter_class.f90:93
parameter_class::final_dens
real(r_kind) final_dens
termination density [g/cm3]
Definition: parameter_class.f90:131
parameter_class::nr_maxcount
integer nr_maxcount
– Newton-Raphson iterative loop parameters
Definition: parameter_class.f90:204
parameter_class::param_name_len
integer, parameter, public param_name_len
– hardcoded parameters
Definition: parameter_class.f90:57
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
parameter_class::initial_stepsize
real(r_kind) initial_stepsize
this value is used as a stepsize at initial step
Definition: parameter_class.f90:128
parameter_class::nr_mincount
integer nr_mincount
Minimum iterations in NR.
Definition: parameter_class.f90:205
parameter_class::timestep_traj_limit
logical timestep_traj_limit
Should the timestep be limited by the timestep of the trajectory.
Definition: parameter_class.f90:144
parameter_class::nsep_energies_file
character(max_fname_len) nsep_energies_file
neutron separation energies
Definition: parameter_class.f90:173
parameter_class::timestep_hydro_factor
real(r_kind) timestep_hydro_factor
Factor for the maximum change of the hydrodynamic quantities (density and temperature)
Definition: parameter_class.f90:134
parameter_class::top_engen_every
integer top_engen_every
frequency of energy generators toplist
Definition: parameter_class.f90:75
parameter_class::nu_min_t
real(r_kind) nu_min_t
Neutrino temperature cutoff for neutrino reactions [MeV].
Definition: parameter_class.f90:199
parameter_class::enux
character(max_fname_len) enux
average Muon and Tauon neutrino energies [MeV]
Definition: parameter_class.f90:196
parameter_class::use_timmes_mue
logical use_timmes_mue
Use electron chemical potentials from timmes EOS for theoretical weak rates.
Definition: parameter_class.f90:96
parameter_class::neutrino_mode
character(max_fname_len) neutrino_mode
Similar to trajectory mode.
Definition: parameter_class.f90:185
parameter_class::gear_nr_mincount
integer gear_nr_mincount
Minimum newton-raphson iterations for gear solver.
Definition: parameter_class.f90:142
parameter_class::gear_ignore_adapt_stepsize
logical gear_ignore_adapt_stepsize
Flag whether gear should ignore the adapt stepsize loop.
Definition: parameter_class.f90:143
parameter_class::max_fname_len
integer, parameter, public max_fname_len
maximum length of filenames
Definition: parameter_class.f90:58
parameter_class::trajectory_file
character(max_fname_len) trajectory_file
name of trajectory data file
Definition: parameter_class.f90:152
parameter_class::use_alpha_decay_file
logical use_alpha_decay_file
Switch for using additional alpha decay rates.
Definition: parameter_class.f90:76
parameter_class::nu_min_l
real(r_kind) nu_min_l
Neutrino luminosity cutoff for neutrino reactions [erg/g/s].
Definition: parameter_class.f90:200
parameter_class::h_finab
logical h_finab
Store the finab in hdf5 format rather than in ascii format.
Definition: parameter_class.f90:146
parameter_class::rho_analytic
character(max_fname_len) rho_analytic
analytic density [g/cm3]
Definition: parameter_class.f90:187
parameter_class::iwinterp
integer iwinterp
defines the interpolation for the weak rates (0 = bilinear, 1 = bicubic)
Definition: parameter_class.f90:82
parameter_class::fission_rates_spontaneous
character(max_fname_len) fission_rates_spontaneous
reaction library for spontaneous fission rates
Definition: parameter_class.f90:159
parameter_class::use_htpf
logical use_htpf
Use high temperature partition functions or not.
Definition: parameter_class.f90:145
parameter_class::rkm_analytic
character(max_fname_len) rkm_analytic
analytic radial scale [km]
Definition: parameter_class.f90:188
parameter_class::alpha_decay_file
character(max_fname_len) alpha_decay_file
File with additional alpha decays.
Definition: parameter_class.f90:182
parameter_class::heating_density
real(r_kind) heating_density
Density at which nuclear heating will be switched on (-1) to always include heating.
Definition: parameter_class.f90:124
parameter_class::xnodes
real(r_kind), dimension(:), allocatable xnodes
corresponding nodes "
Definition: parameter_class.f90:215
parameter_class::fissflag
integer fissflag
defines type of fission fragment distribution used
Definition: parameter_class.f90:86
parameter_class::heating_t9_tol
real(r_kind) heating_t9_tol
Convergence parameter for the temperature in the heating mode.
Definition: parameter_class.f90:149
error_msg_class::data_creation_mode
logical, public data_creation_mode
Flag for rate creation mode.
Definition: error_msg_class.f90:23
parameter_class::alpha_decay_zmax
integer alpha_decay_zmax
Maximum Z for additional alpha decay rates.
Definition: parameter_class.f90:78
parameter_class::h_nu_loss_every
integer h_nu_loss_every
Output neutrino loss and gain in hdf5 format.
Definition: parameter_class.f90:101
parameter_class::trajectory_format
character(max_fname_len) trajectory_format
Format to read the trajectory.
Definition: parameter_class.f90:184
parameter_class::detailed_balance_src_ignore
character(max_fname_len) detailed_balance_src_ignore
Source flag(s) to ignore within calculated detailed balance.
Definition: parameter_class.f90:102
parameter_class::output_binary_parameter_data
subroutine output_binary_parameter_data(path)
Output the parameter data to a binary file.
Definition: parameter_class.f90:1673
parameter_class::h_engen_detailed
logical h_engen_detailed
Output the energy per parent nucleus and reaction type.
Definition: parameter_class.f90:122
parameter_class::use_tabulated_rates
logical use_tabulated_rates
switch for using tabulated rates (e.g. talysNGrates.dat)
Definition: parameter_class.f90:92
parameter_class::isotopes_file
character(max_fname_len) isotopes_file
properties of all isotopes in the network: masses, partition functions etc. (winvn)
Definition: parameter_class.f90:156
parameter_class::read_initial_composition
logical read_initial_composition
specify whether initial distribution of abundances should be read from file
Definition: parameter_class.f90:91
parameter_class::t_analytic
real(r_kind) t_analytic
for parameteric trajectories: initial time
Definition: parameter_class.f90:126
parameter_class::detailed_balance_src_q_reac
character(max_fname_len) detailed_balance_src_q_reac
Source flag(s) to use q-value from rate file for inverse reaction.
Definition: parameter_class.f90:103
parameter_class::search_close_parameter
subroutine search_close_parameter(possible_pars, input_par, score, cl_par)
Search for similar existing parameters.
Definition: parameter_class.f90:1303
parameter_class::read_integer_param
integer function read_integer_param(input_string, param_name)
Converts a string to an integer.
Definition: parameter_class.f90:835
parameter_class::ncc
integer ncc
nr of points for Clenshaw-Curtis integration
Definition: parameter_class.f90:218
parameter_class::htpf_file
character(max_fname_len) htpf_file
high-temperature partition functions (htpf.dat)
Definition: parameter_class.f90:157
parameter_class::nuchannel_file
character(max_fname_len) nuchannel_file
Contains neutrino channel information as in Sieverding et al. 2018.
Definition: parameter_class.f90:175
parameter_class::solver
integer solver
solver flag (0 - implicit Euler, 1 - Gear's method, ...), is integer as it is faster than comparing s...
Definition: parameter_class.f90:147
parameter_class::interp_mode
integer interp_mode
Mode for interpolation of temperature and density.
Definition: parameter_class.f90:151
parameter_class::seed_file
character(max_fname_len) seed_file
name of file with initial seeds for trajectory run
Definition: parameter_class.f90:153
parameter_class::le
character(max_fname_len) le
electron-neutrino luminosities [erg/s]
Definition: parameter_class.f90:190
parameter_class::track_nuclei_file
character(max_fname_len) track_nuclei_file
File of nuclei to track. Gives an output similar to mainout.dat.
Definition: parameter_class.f90:181
parameter_class::unit
type(unit_type), public unit
constants and unit conversion factors
Definition: parameter_class.f90:54
parameter_class::heating_frac
real(r_kind) heating_frac
use this fraction of nuclear-generated energy for heating
Definition: parameter_class.f90:123
parameter_class::nunucleo_rates_file
character(max_fname_len) nunucleo_rates_file
neutrino reaction rates on nucleons
Definition: parameter_class.f90:174
parameter_class::adapt_stepsize_maxcount
integer adapt_stepsize_maxcount
max. iterations in adapting the stepsize
Definition: parameter_class.f90:207
file_handling_class
Provide some basic file-handling routines.
Definition: file_handling_class.f90:18
parameter_class::fission_frag_n_induced
integer fission_frag_n_induced
Fragment distribution of n-induced fission rates in case of custom fragments (fissflag=4)
Definition: parameter_class.f90:166
parameter_class::trajectory_mode
character *20 trajectory_mode
determines how trajectory is calculated (from_file|analytic|expand)
Definition: parameter_class.f90:90
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
parameter_class::fission_frag_spontaneous
integer fission_frag_spontaneous
Fragment distribution of spontaneous fission rates in case of custom fragments (fissflag=4)
Definition: parameter_class.f90:165
parameter_class::heating_mode
integer heating_mode
Mode for heating: 0 - no heating, 1 - heating using an entropy equation, 2 - heating from the energy ...
Definition: parameter_class.f90:148
parameter_class::nrdiag_every
integer nrdiag_every
frequency of NR loop diagnostic messages (wrt iteration counter)
Definition: parameter_class.f90:70
parameter_class::weak_rates_file
character(max_fname_len) weak_rates_file
weak rates library (twr.dat)
Definition: parameter_class.f90:169
parameter_class::nfission_file
character(max_fname_len) nfission_file
Fission table for neutron-induced fission.
Definition: parameter_class.f90:179
parameter_class::tabulated_rates_file
character(max_fname_len) tabulated_rates_file
tabulated rates library (e.g. talysNGrates.dat)
Definition: parameter_class.f90:170
r_kind
#define r_kind
Definition: macros.h:46
parameter_class::h_mainout_every
integer h_mainout_every
HDF5 output frequency of the mainout.
Definition: parameter_class.f90:72
parameter_class::fission_format_beta_delayed
integer fission_format_beta_delayed
Format of beta-delayed fission rates (0: Off, 1: Reaclib, 2: Halflifes, 3: Probability)
Definition: parameter_class.f90:162
parameter_class::engen
real(r_kind) engen
total energy generation [MeV/s]
Definition: parameter_class.f90:109
parameter_class::reaclib_file
character(max_fname_len) reaclib_file
reaction rate library (reaclib)
Definition: parameter_class.f90:158
parameter_class::h_custom_snapshots
logical h_custom_snapshots
Same, but in hdf5 format.
Definition: parameter_class.f90:108
parameter_class::detailed_balance_src_q_winvn
character(max_fname_len) detailed_balance_src_q_winvn
Source flag(s) to use q-value from winvn file for inverse reaction.
Definition: parameter_class.f90:104
parameter_class::read_sanity_check_prepared_network
subroutine read_sanity_check_prepared_network
Read important parameters from a binary file and check for consistency.
Definition: parameter_class.f90:1439
parameter_class::seed_format
character(max_fname_len) seed_format
Seed format.
Definition: parameter_class.f90:154
parameter_class::nsetemp_hot
real(r_kind) nsetemp_hot
T [GK] for the nse<-network switch.
Definition: parameter_class.f90:120
parameter_class::nr_tol
real(r_kind) nr_tol
exit NR if tolerance less than this value
Definition: parameter_class.f90:206
parameter_class::use_thermal_nu_loss
logical use_thermal_nu_loss
Whether to include thermal neutrino loss or not.
Definition: parameter_class.f90:99
parameter_class::neutrino_loss_file
character(max_fname_len) neutrino_loss_file
Path to a file containing Qnu values.
Definition: parameter_class.f90:106
parameter_class::final_time
real(r_kind) final_time
termination time in seconds
Definition: parameter_class.f90:129
parameter_class::nu_loss_every
integer nu_loss_every
Output neutrino loss and gain.
Definition: parameter_class.f90:100
parameter_class::fission_rates_n_induced
character(max_fname_len) fission_rates_n_induced
reaction library for neutron induced fission rates
Definition: parameter_class.f90:160
parameter_class::final_temp
real(r_kind) final_temp
termination temperature [GK]
Definition: parameter_class.f90:130
parameter_class::gear_timestep_max
real(r_kind) gear_timestep_max
For gear solver.
Definition: parameter_class.f90:140
parameter_class::set_param
subroutine set_param(param_name, param_value)
Sets a global parameter param_name to the value, given by its string representation param_value.
Definition: parameter_class.f90:333
parameter_class::snapshot_file
character(max_fname_len) snapshot_file
File that contains days, where a snapshot should be made.
Definition: parameter_class.f90:177
file_handling_class::open_infile
integer function, public open_infile(file_name)
Same for reading (input file)
Definition: file_handling_class.f90:126
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
parameter_class::use_detailed_balance_q_reac
logical use_detailed_balance_q_reac
Use Q-value from reaclib for the calculation of detailed balance.
Definition: parameter_class.f90:98
parameter_class::h_snapshot_every
integer h_snapshot_every
snapshot output frequency in hdf5 format
Definition: parameter_class.f90:63
parameter_class::nu_max_time
real(r_kind) nu_max_time
Maximum time for neutrino reactions to react.
Definition: parameter_class.f90:198
parameter_class::t9_analytic
character(max_fname_len) t9_analytic
analytic temperature [T9]
Definition: parameter_class.f90:186
parameter_class::fission_format_n_induced
integer fission_format_n_induced
Format of neutron-induced fission rates (0: Off, 1: Reaclib)
Definition: parameter_class.f90:163
parameter_class::dcc
real(r_kind), dimension(:), allocatable dcc
Definition: parameter_class.f90:219
parameter_class::enue
character(max_fname_len) enue
average electron-neutrino energies [MeV]
Definition: parameter_class.f90:192
parameter_class::temp_reload_exp_weak_rates
real(r_kind) temp_reload_exp_weak_rates
temperature below which one should not use theoretical weak rates so they are replaced with exp....
Definition: parameter_class.f90:83
parameter_class::nse_delt_t9min
real(r_kind) nse_delt_t9min
Minimum temperature [GK] when descending to desired temperature in NSE.
Definition: parameter_class.f90:115
parameter_class::engen_fiss
real(r_kind) engen_fiss
energy generation from fission [MeV/s]
Definition: parameter_class.f90:112
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::net_source
character(max_fname_len) net_source
list of isotopes included in the network (sunet)
Definition: parameter_class.f90:155
file_handling_class::open_unformatted_outfile
integer function, public open_unformatted_outfile(file_name)
Shorthand for opening a new unformatted file for writing (output file)
Definition: file_handling_class.f90:74
parameter_class::mainout_every
integer mainout_every
frequency of mainout output
Definition: parameter_class.f90:71
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
parameter_class::par_binary_name
character(len= *), parameter, private par_binary_name
other static variables
Definition: parameter_class.f90:210
parameter_class::lebar
character(max_fname_len) lebar
electron-antineutrino luminosities [erg/s]
Definition: parameter_class.f90:191
parameter_class::nse_nr_tol
real(r_kind) nse_nr_tol
Tolerance for the NR loop in the NSE calculation.
Definition: parameter_class.f90:116
file_handling_class::open_unformatted_infile
integer function open_unformatted_infile(file_name)
Open an unformatted file for reading.
Definition: file_handling_class.f90:89
parameter_class::read_float_param
real(r_kind) function read_float_param(input_string, param_name)
Converts a string to an float.
Definition: parameter_class.f90:864
parameter_class::custom_snapshots
logical custom_snapshots
If true, a file must be provided with numbers in days. Snapshots will be created for these points in ...
Definition: parameter_class.f90:107
parameter_class::nuflag
integer nuflag
defines type of neutrino reactions used
Definition: parameter_class.f90:85
parameter_class::set_default_param
subroutine set_default_param
Sets default parameters Parameters are sorted in alphabetical order.
Definition: parameter_class.f90:893
parameter_class::fission_frag_missing
integer fission_frag_missing
Fragment distribution in case of missing fragments in case of custom fragments (fissflag=4)
Definition: parameter_class.f90:168
parameter_class::chem_pot_file
character(max_fname_len) chem_pot_file
tabulated chemical potential of electron gas
Definition: parameter_class.f90:172
parameter_class::nurates_file
character(max_fname_len) nurates_file
Neutrino reactions on heavy nuclei as in Sieverding et al. 2018.
Definition: parameter_class.f90:176
parameter_class::mcc
real(r_kind), dimension(:,:), allocatable mcc
Definition: parameter_class.f90:220
parameter_class::prepared_network_path
character(max_fname_len) prepared_network_path
Prepared network folder.
Definition: parameter_class.f90:201
parameter_class::h_engen_every
integer h_engen_every
Energy generation output frequency in hdf5 format.
Definition: parameter_class.f90:69
parameter_class::ye_analytic
character(max_fname_len) ye_analytic
analytic electron fraction
Definition: parameter_class.f90:189
parameter_class::initemp_cold
real(r_kind) initemp_cold
T [GK] lowest allowed temperature to start the calculation from.
Definition: parameter_class.f90:113
parameter_class::extrapolation_width
integer extrapolation_width
how many points from the end of trajectory to use when computing residual expansion
Definition: parameter_class.f90:88
parameter_class::enuxbar
character(max_fname_len) enuxbar
average Muon and Tauon antineutrino energies [MeV]
Definition: parameter_class.f90:197
parameter_class::lx
character(max_fname_len) lx
Muon and Tauon neutrino luminosities [erg/s].
Definition: parameter_class.f90:194
parameter_class::snapshot_every
integer snapshot_every
snapshot output frequency
Definition: parameter_class.f90:62
parameter_class::engen_beta
real(r_kind) engen_beta
energy generation from beta-decays [MeV/s]
Definition: parameter_class.f90:111
parameter_class::calc_nsep_energy
logical calc_nsep_energy
calculate neutron separation energy?
Definition: parameter_class.f90:121
pi
real(r_kind) function pi()
Further information: http://netlib.org/quadpack/index.html https://orion.math.iastate....
Definition: quadpack_module.f90:193
parameter_class::fission_rates_beta_delayed
character(max_fname_len) fission_rates_beta_delayed
reaction library for beta delayed fission rates
Definition: parameter_class.f90:161
parameter_class::nse_max_it
integer nse_max_it
Maximum amount of NSE iterations.
Definition: parameter_class.f90:117
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
parameter_class::fission_frag_beta_delayed
integer fission_frag_beta_delayed
Fragment distribution of beta-delayed fission rates in case of custom fragments (fissflag=4)
Definition: parameter_class.f90:167
parameter_class::initemp_hot
real(r_kind) initemp_hot
T [GK] for the starting point of the trajectory: =0: from the beginning; >0: from the last T>initemp.
Definition: parameter_class.f90:114