nuclear_heating.f90
Go to the documentation of this file.
1 !> @file nuclear_heating.f90
2 !!
3 !! The error file code for this file is ***W31***.
4 !!
5 !! @brief Module \ref nuclear_heating for self-consistent temperature updates
6 !!
7 
8 !> Takes care of the temperature and entropy updates
9 !! due to the nuclear energy release
10 #include "macros.h"
14  implicit none
15 
16  real(r_kind), private :: engen_nuc !< Total energy, generated by nuclear reactions
17  integer , private :: engen_unit !< Engen output file
18  integer , private :: debug_temp !< Debug file for temperature integration
19  integer , private :: debug_heatfrac!< Debug file for the heating fraction
20 
21  real(r_kind) , public, save :: qdot_bet = 0 !< Total energy radiated away by
22  real(r_kind) , public, save :: qdot_nu = 0 !< Total energy added to the system by neutrino
23  real(r_kind) , public, save :: qdot_th = 0 !< Total energy lost by thermal neutrinos
24 
25  ! Debug variables
26  real(r_kind) , private :: debug_ffn_qd=0 !< debug variable for the qdot caused by ffn rates
27  real(r_kind) , private :: debug_nu_qd=0 !< debug variable for the qdot caused by nu rates
28  real(r_kind) , private :: debug_bet_qd=0 !< debug variable for the qdot caused by beta decay rates
29  !
30  ! Public and private fields and methods of the module.
31  !
32  public:: &
34  private:: &
37 
38 contains
39 
40 !>
41 !! Nuclear heating initialization routine
42 !!
43 !! This subroutine creates some files (e.g., debug_engen.dat_) and
44 !! prepares the header for the _engen.dat_ file
45 !!
46 !! \b Edited:
47 !! - MR: 20.01.21 - Gave toplist file a header
48 !! - MR: 07.05.24 - Removed toplist and moved it to analysis module
49 !! .
50 subroutine nuclear_heating_init (T9, rho, Ye, Y, entropy)
55  use single_zone_vars, only: t9h, t9h_p
56  implicit none
57 
58  real(r_kind),intent(in) :: t9 !< temperature [GK]
59  real(r_kind),intent(in) :: rho !< density [g/cm^3]
60  real(r_kind),intent(in) :: ye !< electron fraction
61  real(r_kind),dimension(net_size),intent(in) :: y !< abundances
62  real(r_kind),intent(out) :: entropy !< [kB/baryon]
63 
64  info_entry("nuclear_heating_init")
65 
66  ! Check if heating mode is implemented
67  if ((heating_mode .gt. 3) .or. (heating_mode .lt. 0)) then
68  call raise_exception("Heating_mode not implemented, got "//int_to_str(heating_mode)//".",&
69  'nuclear_heating_init',310004)
70  end if
71 
72  ! Get the initial entropy
73  call start_heating (t9, rho, ye, y, entropy)
74 
75  engen_nuc= 0d0
76  engen = 0d0
77 
78  if (heating_mode .eq. 1) then
79  if (verbose_level .ge. 2) then
80  engen_unit= open_outfile("debug_engen.dat")
81  write(engen_unit,"(A)") "# 1:iteration 2:time[s] 3:timestep[s] 4:E_gen(tot) [erg/g] 5:E_gen(t) [erg/(g*s)] 6:E_gen(t) [MeV/(baryon*s)]"
82  end if
83  elseif (heating_mode .eq. 2) then
84  t9h = t9
85  t9h_p = t9
86  end if
87 
88 
89  if (verbose_level .ge. 2) then
91  ! Initialize debug variables
93  debug_heatfrac= open_outfile("debug_heatfrac_split.dat")
94  write(debug_heatfrac,"(A)") "# 1:time[s] 2:qdot 3: qdot_ffn 4: qdot_nu 5: qdot_bet 6: qdot_ffn/total 7: qdot_nu/total 8: qdot_bet/total"
95  end if
96 
97 
98  if (verbose_level .ge. 2) then
99  debug_temp = open_outfile("debug_heating_temp.dat")
100  write(debug_temp,"(A)") "# 1:Timestep[s] 2:NR_cnt 3:T9_new 4:T9_old 5:T9_taken"
101  end if
102 
103  ! Check if heating is switched on from the beginning.
104  heating_switch = .false.
105  if (heating_density .eq. -1) then
106  heating_switch = .true.
107  else if (heating_density .gt. rho) then
108  heating_switch = .true.
109  elseif (heating_density .le. rho) then
110  heating_switch = .false.
111  end if
112 
113  info_exit("nuclear_heating_init")
114 end subroutine nuclear_heating_init
115 
116 
117 !> Initialize the entrop and temperature for the heating
118 subroutine start_heating (T9, rho, Ye, Y, entropy)
119  use global_class, only: net_size, isotope
120  real(r_kind),intent(in) :: t9 !< temperature [GK]
121  real(r_kind),intent(in) :: rho !< density [g/cm^3]
122  real(r_kind),intent(in) :: ye !< electron fraction
123  real(r_kind),dimension(net_size),intent(in) :: y !< abundances
124  real(r_kind),intent(out) :: entropy !< [kB/baryon]
125  !
126  type(timmes_eos_state) :: state ! Timmes EOS state
127  integer :: eos_status
128  real(r_kind) :: ysum, yasum
129 
130  ! Get the initial entropy
131  ysum= sum(y(1:net_size))
132  yasum= sum(y(1:net_size)*isotope(1:net_size)%mass)
133  state%abar= yasum / ysum
134  call timmes_eos(ink,t9*1.d9,rho,ye,state,eos_status)
135 
136  if (eos_status .ne. 0 ) then
137  call raise_exception("The EOS did not converge, T="//num_to_str(t9)//"GK, "//&
138  "rho="//num_to_str(rho)//"g/ccm, Ye="//num_to_str(ye),&
139  "nuclear_heating_init",310003)
140  end if
141 
142  entropy = state%s
143 
144 end subroutine start_heating
145 
146 
147 
148 !> Reset the qdot variable.
149 !!
150 !! This is called by the Jacobian init whenever recalculating the
151 !! jacobian.
152 !!
153 !! @author M. Reichert
154 subroutine reset_qdot(time)
156  implicit none
157  real(r_kind),intent(in) :: time !< Current time
158  real(r_kind) :: denom !< helper variable
159  real(r_kind) :: qdot !< helper variable
160 
161  if ((heating_mode .gt. 0) .or. (nu_loss_every .gt. 0) .or. &
162  (h_nu_loss_every .gt. 0)) then
163  ! Output status for debugging, qdot splitted in contributions
164  if (verbose_level .gt. 2) then
165  qdot = qdot_bet + qdot_nu
166  ! Calculate denominator, ensure not to divide by zero
167  if (qdot .eq. 0) then
168  denom = 1
169  else
170  denom = abs(qdot)
171  end if
172 
173  ! Output
174  write(debug_heatfrac, '(es16.5,1x,es16.5,1x,es16.5,1x,es16.5,1x,es16.5,1x,f5.2,1x,f5.2,1x,f5.2)') &
175  time, qdot, debug_ffn_qd, debug_nu_qd, debug_bet_qd, &
176  debug_ffn_qd/denom, debug_nu_qd/denom, debug_bet_qd/denom
177 
178  ! Reset variables
180  end if
181 
182  qdot_bet = 0
183  qdot_nu = 0
184  end if
185 end subroutine reset_qdot
186 
187 
188 
189 !< Calculate the energy radiated away by neutrinos or added to the system
190 !!
191 !! This subroutine calculates the energy radiated away by neutrinos or added to the system
192 !! and saves it in the variable qdot.
193 !! The fraction of energy is either set by a user defined input file (\ref neutrino_loss_file),
194 !! by the beta decay file (\ref beta_decay_file),
195 !! by the ffn_type rates (\ref weak_rates_file),
196 !! or by a user defined variable (\ref heating_frac).
197 !!
198 !! @author M. Reichert
199 !! @date 02.04.2023
200 subroutine calculate_qdot(rrate,Y,h)
203  implicit none
204  type(reactionrate_type),intent(in) :: rrate !< Reaction rate
205  real(r_kind),dimension(net_size),intent(in) :: Y !< Abundances
206  real(r_kind),intent(in) :: h !< timestep
207  !-- Internal variables
208  integer :: group !< Reaclib chapter
209  real(r_kind) :: qdot_tmp !< Temporary energy released by beta-decay
210 
211  if ((rrate%is_weak) .and. (heating_mode .gt. 0) .or. (nu_loss_every .gt. 0) .or. &
212  (h_nu_loss_every .gt. 0)) then
213  ! Get reaclib group
214  group = rrate%group
215  select case(group)
216  case(1:3,11)
217  qdot_tmp = rrate%cached * rrate%q_value * rrate%nu_frac * &
218  y(rrate%parts(1)) * h
219  case(4:7)
220  qdot_tmp = rrate%cached * rrate%q_value * rrate%nu_frac * &
221  y(rrate%parts(1))*y(rrate%parts(2)) * h
222  case(8:9)
223  qdot_tmp = rrate%cached * rrate%q_value * rrate%nu_frac * &
224  y(rrate%parts(1))*y(rrate%parts(2))*y(rrate%parts(3)) * h
225  case(10)
226  qdot_tmp = rrate%cached * rrate%q_value * rrate%nu_frac * &
227  y(rrate%parts(1))*y(rrate%parts(2))*y(rrate%parts(3))*y(rrate%parts(4)) * h
228  end select
229 
230  if (verbose_level .ge. 2) then
231  ! Split the energy dependent on its reaction type
232  if (rrate%reac_src .eq. rrs_twr) then
233  debug_ffn_qd = debug_ffn_qd + qdot_tmp
234  elseif (rrate%reac_src .eq. rrs_nu) then
235  debug_nu_qd = debug_nu_qd + qdot_tmp
236  else
237  debug_bet_qd = debug_bet_qd + qdot_tmp
238  end if
239  end if
240 
241  if (rrate%reac_src .eq. rrs_nu) then
242  qdot_nu = qdot_nu + qdot_tmp
243  else
244  qdot_bet = qdot_bet + qdot_tmp
245  end if
246  end if
247 end subroutine calculate_qdot
248 
249 
250 !> Output the heating fractions to a debug file
251 !!
252 !! This subroutine outputs the heating fractions to a debug file. This is
253 !! useful for debugging purposes. The file is called debug_heating_nufrac.dat
254 !! and is located in the output directory. An example could look like
255 !! \file{
256 !! Group Isotope Source Nu_frac Q_value
257 !! 1 n wc12 0.40000 0.78230
258 !! 1 t wc12 0.40000 0.01860
259 !! 1 he3 ec 0.40000 -0.01900
260 !! 1 he6 wc12 0.55394 3.50510
261 !! 1 li9 wc12 0.45403 13.60600
262 !!...}
263 !!
264 !! @author M. Reichert
265 !! @date 30.03.2023
266 subroutine output_debug_nufrac(rrate_array,length)
269  implicit none
270  integer,intent(in) :: length !< Amount of reactions
271  type(reactionrate_type),dimension(length),intent(in) :: rrate_array !< Reaction rate array
272  !-- Internal variables
273  integer :: i
274  integer :: file_id
275 
276  ! Open the debug file
277  file_id = open_outfile("debug_heating_nufrac.dat")
278 
279  ! Write the header of the file, align the columns in the correct format
280  write(file_id,"(A5,2X,A10,2X,A10,2X,A10,2X,A10)") "Group","Isotope","Source","Nu_frac","Q_value"
281 
282  ! Write the data, note that the ffn rates are variable and the correct value will not be
283  ! reflected in the debug file. Same for the neutrino rates.
284  do i=1,length
285  if (rrate_array(i)%is_weak) then
286  write(file_id,"(2X,I3,2X,A10,2X,A10,2X,F10.5,2X,F10.5)") rrate_array(i)%group,&
287  net_names(rrate_array(i)%parts(1)),rrate_array(i)%source,&
288  rrate_array(i)%nu_frac,rrate_array(i)%q_value
289  end if
290  end do
291  close(file_id)
292 
293 end subroutine output_debug_nufrac
294 
295 
296 
297 
298 !>
299 !! Modifies the temperature and entropy to account for nuclear heating
300 !!
301 !! The temperature/entropy is solved (explicitely) in the same Newton-Raphson
302 !! scheme as used for the abundances in e.g.,
303 !! \ref timestep_module::advance_implicit_euler and
304 !! \ref timestep_module::advance_gear.
305 !!
306 !! There are 3 different heating modes:
307 !! <table>
308 !! <caption id="multi_row">Heating modes</caption>
309 !! <tr><th> Value <th> Evolved variable <th> Additional source term
310 !! <tr><td> 0 <td> No heating <td> -
311 !! <tr><td> 1 <td> Entropy <td> adiabatic
312 !! <tr><td> 2 <td> Temperature <td> trajectory
313 !! <tr><td> 3 <td> Temperature <td> adiabatic
314 !! </table>
315 !!
316 !! @author M. Reichert
317 !! @date 10.02.23
318 !! .
319 subroutine nuclear_heating_update(nr_count,rho,Ye,pf,Y_p,Y,entropy_p,entropy,T9_p,T9,T9_tr_p,T9_tr,timestep,T9conv)
320  use global_class, only: net_size,isotope
321  use nucstuff_class, only: inter_partf
325  implicit none
326 
327  integer,intent(in) :: nr_count !< NR-iteration count
328  real(r_kind),intent(in) :: rho !< density
329  real(r_kind),intent(in) :: ye !< electron fraction
330  real(r_kind),dimension(0:net_size),intent(out) :: pf !< partition functions
331  real(r_kind),dimension(net_size),intent(in) :: y_p !< abundances
332  real(r_kind),dimension(net_size),intent(in) :: y !< abundances at the next step
333  real(r_kind),intent(in) :: entropy_p !< entropy
334  real(r_kind),intent(out) :: entropy !< entropy for the next step
335  real(r_kind),intent(in) :: t9_tr_p !< temperature of the trajectory/analytic (prev.)
336  real(r_kind),intent(in) :: t9_tr !< temperature of the trajectory/analytic
337  real(r_kind),intent(in) :: t9_p !< temperature at the previous step
338  real(r_kind),intent(inout) :: t9 !< temperature at the next step
339  real(r_kind),intent(in) :: timestep !< timestep (s)
340  real(r_kind),intent(out) :: t9conv !< Convergence of the temperature
341 
342  real(r_kind) :: mic2, mui, kbt !< auxiliary variables and constants
343  type(timmes_eos_state) :: state !< Timmes EOS state
344  real(r_kind) :: gi !< statistical weight
345  real(r_kind) :: twopi_h2c2 !< 2\pi/(hc)^2 [MeV^-2 cm^-2]
346  real(r_kind) :: entropy_inc !< entropy increment during single timestep due to nuclear heating
347  real(r_kind) :: engen_i !< generated energy (per baryon) due to abundance changes of species i
348  real(r_kind) :: t9_old !< last temperature difference
349  real(r_kind) :: new_tdiff !< Temperature difference
350  real(r_kind) :: abar !< average mass number
351 
352  real(r_kind) :: ysum,yasum, temp_next
353  real(r_kind) :: t9_calc
354  integer :: i ! Loop variables
355  integer :: eos_status
356 
357  info_entry("nuclear_heating_update")
358 
359  ! Save the old temperature
360  t9_old = t9
361 
362  ! Only heat for T9 > freeze_rate_temp
363  if (t9 .gt. freeze_rate_temp*1.000001)then
364 
365  if (use_thermal_nu_loss) then
366  ysum= sum(y(1:net_size))
367  yasum= sum(y(1:net_size)*isotope(1:net_size)%mass)
368  abar= yasum / ysum
369  call thermal_neutrinos(abar, ye, t9, rho, timestep, qdot_th)
370  qdot_th = qdot_th * unit%hix ! erg/g -> MeV/baryon
371  else
372  qdot_th = 0d0
373  end if
374 
375  ! Different heating treatments
376  if (heating_mode .eq. 1) then
377  call nuclear_heating_entropy(rho,ye,pf,y_p,y,entropy_p,entropy,t9,eos_status)
378  elseif ((heating_mode .eq. 2) .or. (heating_mode .eq. 3)) then
379  call nuclear_heating_energy(rho,ye,pf,y_p,y,entropy_p,entropy,t9_p,t9,t9_tr_p,t9_tr,eos_status)
380  else
381  call raise_exception("Heating_mode not implemented, got "//int_to_str(heating_mode)//".",&
382  'nuclear_heating_update',310004)
383  end if
384 
385  t9_calc = t9
386  ! Avoid a crash here and do not care about the temperature
387  ! if the EOS fails
388  if (eos_status .ne. 0) then
389  t9 = t9_p
390  else
391  ! Check if there is a convergence problem
392  ! Sometimes there are alternating temperatures
393  ! obtained.
394  ! Therefore, if not converged after the first 3 iterations
395  ! limit the shooting!
396  new_tdiff = t9-t9_old
397 
398  if (nr_count .ge. 3) then
399  t9 = t9_old + new_tdiff*max((1d0/(float(nr_count)-1d0)),0.1d0)
400  end if
401 
402  end if
403 
404  ! Don't allow T9 to go below freeze_rate_temp and
405  ! avoid crazy unreasonable numbers
406  t9 = max(t9,freeze_rate_temp,t9_p/2d0)
407 
408  ! Update the entropy
409  ysum= sum(y(1:net_size))
410  yasum= sum(y(1:net_size)*isotope(1:net_size)%mass)
411  state%abar= yasum / ysum
412  call timmes_eos(ink,t9*1d9,rho,ye,state,eos_status)
413 
414  entropy = state%S
415 
416  else
417  t9 = t9
418  t9_calc = t9
419  end if
420 
421  if (verbose_level .ge. 2) then
422  write(debug_temp,"(es16.5,1x,I5,1x,es16.5,1x,es16.5,1x,es16.5)") &
423  timestep, nr_count, t9_calc, t9_old, t9
424  end if
425 
426  t9conv = dabs(max(t9_calc,t9_old)/min(t9_calc,t9_old) - 1d0)
427 
428  info_exit("nuclear_heating_update")
429 
430 end subroutine nuclear_heating_update
431 
432 
433 !>
434 !! Modifies the temperature to account for nuclear heating
435 !!
436 !! Here, an additional equation is calculated for the temperature.
437 !! The temperature is calculated by:
438 !! \f[ \dot{T}_\mathrm{nuc} = \frac{1}{c_v} \sum_i M_i dY_i \f]
439 !! with the symbols defined as:
440 !! <pre style="line-height:.5">
441 !! - M_i : mass excess [MeV] (see \ref global_class::isotope\%mass_exc)
442 !! - cv : Specific heat capacity at constant volume
443 !! .
444 !! </pre>
445 !!
446 !! For heating_mode 2, the temperature is calculated by:
447 !! \f[ \dot{T}_\mathrm{nuc} = \dot{T}_\mathrm{nuc} + \dot{T}_\mathrm{tr} \f]
448 !! where \f$\dot{T}_\mathrm{tr}\f$ is the temperature change of the external conditions,
449 !! i.e., the trajectory or the analytic equation.
450 !! For heating_mode 3, the temperature is calculated by:
451 !! \f[ \dot{T}_\mathrm{nuc} = \dot{T}_\mathrm{nuc} + \dot{T}_\mathrm{ad} \f]
452 !! where \f$\dot{T}_\mathrm{ad}\f$ is the temperature change assuming adiabatic conditions.
453 !!
454 !! @author M. Reichert
455 !! @date 10.02.23
456 !!
457 !! @see [Lippuner & Roberts 2017](https://ui.adsabs.harvard.edu/abs/2017ApJS..233...18L/abstract),
458 !! [XNet](https://github.com/starkiller-astro/XNet)
459 !! .
460 subroutine nuclear_heating_energy(rho,Ye,pf,Y_p,Y,entropy_p,entropy,T9_p,T9,T9_tr_p,T9_tr,eos_status)
461  use global_class, only: net_size,isotope
462  use nucstuff_class, only: inter_partf
463  use parameter_class, only: engen, top_engen_every, unit, &
466  implicit none
467 
468  real(r_kind),intent(in) :: rho !< density
469  real(r_kind),intent(in) :: ye !< electron fraction
470  real(r_kind),dimension(0:net_size),intent(out) :: pf !< partition functions
471  real(r_kind),dimension(net_size),intent(in) :: y_p !< abundances
472  real(r_kind),dimension(net_size),intent(in) :: y !< abundances at the next step
473  real(r_kind),intent(in) :: entropy_p !< entropy
474  real(r_kind),intent(out) :: entropy !< entropy for the next step
475  real(r_kind),intent(inout) :: t9 !< temperature at the next step
476  real(r_kind),intent(in) :: t9_p !< temperature at the previous step
477  real(r_kind),intent(in) :: t9_tr_p !< temperature of the trajectory/analytic (prev.)
478  real(r_kind),intent(in) :: t9_tr !< temperature of the trajectory/analytic
479  integer,intent(out) :: eos_status !< status of the EOS call
480 
481  real(r_kind) :: mic2, mui, kbt !< auxiliary variables and constants
482  type(timmes_eos_state) :: state !< Timmes EOS state
483  real(r_kind) :: gi !< statistical weight
484  real(r_kind) :: twopi_h2c2 !< 2\pi/(hc)^2 [MeV^-2 cm^-2]
485  real(r_kind) :: entropy_inc !< entropy increment during single timestep due to nuclear heating
486  real(r_kind) :: tdot_i
487  real(r_kind) :: tdot
488  real(r_kind) :: add_incr
489 
490  real(r_kind) :: ysum,yasum, temp_next, cv
491  integer :: i ! Loop variables
492 
493 
494  ! Call the Timmes EOS to get the specific heat at constant volume
495  ysum= sum(y(1:net_size))
496  yasum= sum(y(1:net_size)*isotope(1:net_size)%mass)
497  state%abar= yasum / ysum
498  call timmes_eos(ink,t9*1d9,rho,ye,state,eos_status)
499 
500  ! If this fails, return
501  if (eos_status .ne. 0) then
502  return
503  end if
504 
505  ! Calculate the energy increment due to nuclear heating
506  tdot = 0
507  do i=1,net_size
508  tdot_i = -(isotope(i)%mass_exc)*(y(i)-y_p(i)) / (state%cv)
509  tdot = tdot + tdot_i
510  end do
511 
512  ! Radiate energy away
513  tdot = tdot - (qdot_bet+qdot_nu+qdot_th) / (state%cv)
514 
515 
516  ! Only heat when the temperature is above freeze_rate_temp
517  if (t9 .gt. freeze_rate_temp*1.000001)then
518 
519  if (heating_mode .eq. 2) then
520  ! Heating mode 2 follows the trajectory until it ends,
521  ! afterwards adiabatic expansion is assumed
522  if (expand_count .ge. 1) then
523  call timmes_eos(ins,entropy_p,rho,ye,state,eos_status)
524 
525  ! If this fails, return
526  if (eos_status .ne. 0) then
527  return
528  end if
529 
530  add_incr = state%t*1d-9 - t9_p
531  else
532  add_incr = (t9_tr-t9_tr_p)
533  end if
534  elseif (heating_mode .eq. 3) then
535  ! Heating mode 3 assumes adiabatic expansion
536  call timmes_eos(ins,entropy_p,rho,ye,state,eos_status)
537 
538  ! If this fails, return
539  if (eos_status .ne. 0) then
540  return
541  end if
542 
543  add_incr = state%t*1d-9 - t9_p
544  end if
545 
546  t9 = t9_p + (tdot*1e-9) + add_incr
547 
548  else
549  eos_status = 0
550  t9 = t9
551  end if
552  ! Todo, maybe add the following as debug file
553  ! write(55,'(100(es23.16,2X))')T9,T9_p,T9_tr,T9_tr_p,(heating_frac*engen*1e-9), (T9_tr-T9_tr_p),T9-T9_p
554  end subroutine nuclear_heating_energy
555 
556 
557 
558 !>
559 !! Modifies the temperature and ent_p to account for nuclear heating
560 !!
561 !! Here, an additional equation is calculated for the entropy.
562 !! The entropy is calculated by:
563 !! \f[ E_\mathrm{gen} = \sum_i (m_i c^2 + \mu_i + Z_i \mu_e) dY_i -\Delta q \f]
564 !! , where \f$ \mu_i \f$ is given by
565 !! \f[
566 !! \mu_i = -k_B T \log \left( \frac{g_i G_i}{\rho N_A Y_i}
567 !! \left(\frac{2 \pi m_ic^2 k_B T}{h^2 c^2}\right)^{1.5} \right)
568 !! \f]
569 !! and the nuclear mass defined by the atomic mass excess:
570 !! \f[ m_ic^2 = M_i +Am_uc^2 - Z_i m_e c^2 .\f]
571 !! The symbols are defined as:
572 !! <pre style="line-height:.5">
573 !! - M_i : mass excess [MeV] (see \ref global_class::isotope\%mass_exc)
574 !! - m_ic^2 : nuclear mass (see \ref global_class::isotope\%mass [MeV])
575 !! - kB : Boltzman constant (see \ref parameter_class::unit\%k_mev)
576 !! - g_i : 2 * spin + 1 ( see \ref global_class::isotope\%spin )
577 !! - G_i : normalized partition function of isotope i
578 !! - rho : Density [cgs]
579 !! - \f$mu_e\f$ : Electron chemical potential
580 !! - Z_i : Proton number of isotope i
581 !! - Navo : Avogadro constant (see \ref parameter_class::unit\%n_a)
582 !! - Y_i : Abundance [mol/g]
583 !! - h : Planck constant [MeV*s] (see \ref parameter_class::unit\%h_mevs)
584 !! - c : Speed of light [cm/s] (see \ref parameter_class::unit\%clight)
585 !! .
586 !! </pre>
587 !! The entropy is converted to a temperature via the equation of state at the
588 !! end of this subroutine. Furthermore, \f$ \Delta q \f$ is the energy loss due
589 !! neutrinos that won't thermalize (\ref parameter_class::heating_frac ,
590 !! \ref beta_decay_file , \ref neutrino_loss_file).
591 !!
592 !! @see
593 !! [Freiburghaus et al. 1999, Eq. 2](https://ui.adsabs.harvard.edu/abs/1999ApJ...525L.121F/abstract)
594 !! [Mueller 1986](https://ui.adsabs.harvard.edu/abs/1986A%26A...162..103M/abstract)
595 !!
596 !! @author O. Korobkin
597 !!
598 !! \b Edited:
599 !! - MR: 20.01.21 - Separated top contributor to independent subroutine
600 !! .
601 subroutine nuclear_heating_entropy(rho,Ye,pf,Y_p,Y,entropy_p,entropy,T9,eos_status)
602  use global_class, only: net_size,isotope
603  use nucstuff_class, only: inter_partf
604  use parameter_class, only: engen, top_engen_every, unit, &
606  implicit none
607 
608  real(r_kind),intent(in) :: rho !< density
609  real(r_kind),intent(in) :: ye !< electron fraction
610  real(r_kind),dimension(0:net_size),intent(out) :: pf !< partition functions
611  real(r_kind),dimension(net_size),intent(in) :: y_p !< abundances
612  real(r_kind),dimension(net_size),intent(in) :: y !< abundances at the next step
613  real(r_kind),intent(in) :: entropy_p !< entropy
614  real(r_kind),intent(out) :: entropy !< entropy for the next step
615  real(r_kind),intent(inout) :: t9 !< temperature at the next step
616  integer,intent(out) :: eos_status !< Status of the EOS call
617 
618  real(r_kind) :: mic2, mui, kbt !< auxiliary variables and constants
619  type(timmes_eos_state) :: state !< Timmes EOS state
620  real(r_kind) :: gi !< statistical weight
621  real(r_kind) :: twopi_h2c2 !< 2\pi/(hc)^2 [MeV^-2 cm^-2]
622  real(r_kind) :: entropy_inc !< entropy increment during single timestep due to nuclear heating
623  real(r_kind) :: engen_i !< generated energy (per baryon) due to abundance changes of species i
624  real(r_kind) :: etaele,etapos !< Electron and positron chemical potentials from eos
625  real(r_kind) :: mue !< Electron and positron chemical potentials
626 
627  real(r_kind) :: ysum,yasum, temp_next
628  integer :: i ! Loop variables
629 
630  info_entry("nuclear_heating_entropy")
631 
632  ! calculate partition functions for all nuclei
633  call inter_partf (t9, pf)
634 
635  temp_next= t9 * 1.d9
636 
637 
638  ! Get the electron chemical potential
639  call chempot(temp_next,rho,ye,etaele,etapos)
640  mue = etaele * unit%k_mev * temp_next
641  mue = mue + unit%mass_e
642  ! calculate <A> based on abundances of the next timestep; this is needed for the EOS later
643  ysum= sum(y(1:net_size))
644  yasum= sum(y(1:net_size)*isotope(1:net_size)%mass)
645  state%abar= yasum / ysum
646 
647  ! update the temperature, using the entropy increment
648  ! entropy = engen / T
649  ! [entropy] = [MeV/baryon] / [K] -> kB [MeV/K] / baryon
650  ! calculate energy generated per baryon:
651  !
652  ! engen = sum_i (m_ic^2 + \mu_i + Z_i \mu_e) dY_i - \Delta q
653  !
654  ! where the chemical potential is:
655  ! { g_i G_i 2 \pi m_ic^2 kB T 3/2 }
656  ! \mu_i = -kB T log { ------------- ( ---------------- ) }
657  ! { rho Navo Y_i h^2 c^2 }
658  !
659  ! M_i = isotope(i)%mass_exc [MeV]
660  ! m_ic^2 = isotope(i)%mass [MeV]
661  ! kB = 8.6173324d-11 [Mev/K] = unit%k_mev
662  ! kB T = 8.6173324d-11 [Mev/K] * T [K] -> [MeV]
663  ! mu_e = Electron chemical potential [MeV]
664  ! g_i = isotope(i)%spin * 2 + 1
665  ! G_i = normalized partition function of isotope i
666  ! rho = rho [cgs]
667  ! Navo = 6.0221367d23 [1/mol] = unit%n_a
668  ! Y_i = Y(i) [mol/g] ... me: but also [1/baryon]?
669  ! h = 4.135667516e-21 [MeV*s] = unit%h_mevs
670  ! c = 2.99792458d10 [cm/s] = unit%clight
671  !
672  ! [engen] = MeV/nuc * nuc/baryon = MeV / baryon
673 
674  engen = 0.d0
675  kbt = temp_next * unit%k_mev ! 8.617332d-11 * T [MeV]
676 
677  do i=1,net_size
678  if (y(i).gt.1d-25) then
679  mic2 = isotope(i)%mass*unit%mass_u - isotope(i)%p_nr * unit%mass_e + isotope(i)%mass_exc ! [MeV]
680  gi = 2d0*isotope(i)%spin + 1d0 ! statistical weight
681  twopi_h2c2 = 2d0*unit%pi/(unit%h_mevs*unit%clight)**2 ! 2\pi/(hc)^2 [MeV^-2 cm^-2]
682  mui = -kbt*log( gi*pf(i) / (rho*y(i)*unit%n_a) * &
683  (twopi_h2c2 * isotope(i)%mass*unit%mass_u * kbt)**1.5d0 )
684  ! note that Amuc2 is a approximation of mic2. It is used in order to be consistent with what is
685  ! used in NSE.
686 
687  engen_i = -(mic2 + mui + isotope(i)%p_nr*mue)*(y(i)-y_p(i)) ! energy generated by species i [MeV/baryon]
688  engen = engen + engen_i
689  endif
690  end do
691 
692  ! the total energy from nuc. reactions
693  engen_nuc = engen_nuc + engen / unit%hix ! [erg/g]
694 
695  if (t9 .gt. freeze_rate_temp*1.000001)then
696  ! use only a fraction (=heating_frac) of engen: the rest is radiated away, e.g., due to neutrino cooling
697  entropy_inc= (engen - (qdot_bet + qdot_nu + qdot_th)) / kbt ! divide by kB in order to get entropy in units kB per baryon
698  entropy= entropy_p + entropy_inc ! [kB/baryon]
699 
700  ! Prevent unphysical negative entropy
701  ! This mostly happens for regions where the EOS is not
702  ! valid in any case, i.e., very high densities.
703  if (entropy .lt. 0) then
704  ! Complain about it at high verbose levels
705  if (verbose_level .gt. 1) then
706  write(*,*) "Warning! Restricting entropy as it was negative: ", entropy
707  end if
708  entropy = 0
709  end if
710 
711  call timmes_eos(ins,entropy,rho,ye,state,eos_status)
712 
713  if (eos_status .ne. 0 ) then
714  continue
715  ! Do nothing here as it can only happen for a bad NR iteration
716  ! call raise_exception("The EOS did not converge, "//NEW_LINE("A")//&
717  ! "T ="//num_to_str(T9)//"GK, "//NEW_LINE("A")//&
718  ! "rho ="//num_to_str(rho)//"g/ccm,"//NEW_LINE("A")//&
719  ! "Ye ="//num_to_str(Ye), "nuclear_heating_update",&
720  ! 310003)
721  else
722  temp_next= state%t ! new temperature with updated entropy
723  t9 = temp_next / 1d9 ! new temperature in [GK]
724  end if
725  t9 = temp_next / 1d9 ! new temperature in [GK]
726  else
727  eos_status = 0
728  t9= t9
729  end if
730 
731  info_exit("nuclear_heating_entropy")
732 
733 
734 end subroutine nuclear_heating_entropy
735 
736 
737 
738 !>
739 !! Output data related to nuclear heating
740 !!
741 !! For example the energy generation in the file _engen.dat_
742 !! <div style="width:800px;overflow:scroll;padding:5px;
743 !! background-color:#e8e8e8;scrollbar-base-color:#DEBB07;border:1px dashed grey;
744 !! display: inline-block">
745 !! <pre>
746 !! # 1:iteration 2:time[s] 3:timestep[s] 4:E_gen(tot) [erg/g] 5:E_gen(t) [erg/(g*s )] 6:E_gen(t) [MeV/(baryon*s)]
747 !! 0 0.000000000000000E+00 0.000000000000000E+00 0.000000000000000E+00 0.000000000000000E+00 0.000000000000000E+00
748 !! 0 2.000000000000000E-12 2.000000000000000E-12 2.100942703338183E+08 5.252356611052194E+19 5.443684205322992E+01
749 !! 1 6.000000000000000E-12 4.000000000000000E-12 6.302695988823750E+08 5.252191701420075E+19 5.443513288527704E+01
750 !! ...</pre></div>
751 !!
752 !! \b Edited:
753 !! - MR: 20.1.21 - Modified format of _toplist.dat_
754 !! - MR: 07.5.24 - Removed _toplist.dat_ from here
755 !! .
756 subroutine output_nuclear_heating(cnt,ctime)
757  use single_zone_vars, only: stepsize
758  use parameter_class, only: engen, unit
759  implicit none
760  integer,intent(in) :: cnt !< current iteration
761  real(r_kind),intent(in) :: ctime !< current global time [s]
762  !
763  real(r_kind) :: engen_per_s
764 
765  info_entry("output_nuclear_heating")
766  ! output nuclear energy generation
767  if ((stepsize .gt. 0.d0)) then ! engen calculated in nuclear_heating_update
768  engen_per_s = engen / stepsize
769  else
770  engen_per_s = engen ! engen from jacobian_init (already per second) and first entry
771  end if
772 
773  ! output nuclear energy generation
774  write(engen_unit,'(i10,5es23.15)') cnt, ctime, stepsize, engen_nuc, engen_per_s / unit%hix, engen_per_s
775 
776 
777  info_exit("output_nuclear_heating")
778 
779 end subroutine output_nuclear_heating
780 
781 
782 end module nuclear_heating
ls_timmes_eos_module::ink
integer, parameter ink
Definition: ls_timmes_eos_module.f:14
expansion_module::expand_count
integer expand_count
1 for the first timestep 2 for following steps, 0 for no expansion yet
Definition: expansion_module.f90:35
nuclear_heating::qdot_bet
real(r_kind), save, public qdot_bet
Total energy radiated away by.
Definition: nuclear_heating.f90:21
global_class::heating_switch
logical, public heating_switch
Variables related to nuclear heating.
Definition: global_class.f90:41
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
global_class::net_names
character *5, dimension(:), allocatable, public net_names
list of isotopes contained in the network
Definition: global_class.f90:95
global_class::reactionrate_type
reaction rate type
Definition: global_class.f90:44
ls_timmes_eos_module
Definition: ls_timmes_eos_module.f:2
global_class::rrate
type(reactionrate_type), dimension(:), allocatable, public rrate
array containing all reaction rates used in the network
Definition: global_class.f90:65
nuclear_heating
Takes care of the temperature and entropy updates due to the nuclear energy release.
Definition: nuclear_heating.f90:11
nuclear_heating::nuclear_heating_energy
subroutine, private nuclear_heating_energy(rho, Ye, pf, Y_p, Y, entropy_p, entropy, T9_p, T9, T9_tr_p, T9_tr, eos_status)
Modifies the temperature to account for nuclear heating.
Definition: nuclear_heating.f90:461
nuclear_heating::nuclear_heating_init
subroutine, public nuclear_heating_init(T9, rho, Ye, Y, entropy)
Nuclear heating initialization routine.
Definition: nuclear_heating.f90:51
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
expansion_module
Subroutines to handle parametric evolution of hydrodynamic quantities after the final timestep of the...
Definition: expansion_module.f90:16
single_zone_vars::t9h_p
real(r_kind) t9h_p
Temperature [GK] storage for heating mode 2.
Definition: single_zone_vars.f90:16
error_msg_class::int_to_str
character(:) function, allocatable, public int_to_str(num)
Converts a given integer to a string.
Definition: error_msg_class.f90:224
ls_timmes_eos_module::timmes_eos
subroutine timmes_eos(var, vin, d, Ye, state, status)
Definition: ls_timmes_eos_module.f:49
thermal_neutrino_module::thermal_neutrinos
subroutine, public thermal_neutrinos(abar, Ye, temp, den, timestep, neutrino_loss)
Calculates the neutrino emissivity.
Definition: thermal_neutrino_module.f90:109
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::top_engen_every
integer top_engen_every
frequency of energy generators toplist
Definition: parameter_class.f90:75
nuclear_heating::qdot_nu
real(r_kind), save, public qdot_nu
Total energy added to the system by neutrino.
Definition: nuclear_heating.f90:22
nuclear_heating::engen_nuc
real(r_kind), private engen_nuc
Total energy, generated by nuclear reactions.
Definition: nuclear_heating.f90:16
nuclear_heating::debug_ffn_qd
real(r_kind), private debug_ffn_qd
debug variable for the qdot caused by ffn rates
Definition: nuclear_heating.f90:26
global_class::isotope
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
Definition: global_class.f90:34
nucstuff_class
Module with helper functions such as rate tabulation, partition functions, and theoretical weak rates...
Definition: nucstuff_class.f90:11
nuclear_heating::qdot_th
real(r_kind), save, public qdot_th
Total energy lost by thermal neutrinos.
Definition: nuclear_heating.f90:23
nuclear_heating::debug_bet_qd
real(r_kind), private debug_bet_qd
debug variable for the qdot caused by beta decay rates
Definition: nuclear_heating.f90:28
nuclear_heating::start_heating
subroutine, private start_heating(T9, rho, Ye, Y, entropy)
Initialize the entrop and temperature for the heating.
Definition: nuclear_heating.f90:119
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
nuclear_heating::debug_heatfrac
integer, private debug_heatfrac
Debug file for the heating fraction.
Definition: nuclear_heating.f90:19
nuclear_heating::debug_nu_qd
real(r_kind), private debug_nu_qd
debug variable for the qdot caused by nu rates
Definition: nuclear_heating.f90:27
nuclear_heating::debug_temp
integer, private debug_temp
Debug file for temperature integration.
Definition: nuclear_heating.f90:18
parameter_class::h_nu_loss_every
integer h_nu_loss_every
Output neutrino loss and gain in hdf5 format.
Definition: parameter_class.f90:101
thermal_neutrino_module
The thermal_neutrino_module serves as interface to the neutrino emission routines from the sneut5....
Definition: thermal_neutrino_module.f90:19
rrs_twr
#define rrs_twr
Definition: macros.h:52
global_class::net_size
integer, public net_size
total number of isotopes (network size)
Definition: global_class.f90:93
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
rrs_nu
#define rrs_nu
Definition: macros.h:51
nuclear_heating::nuclear_heating_update
subroutine, public nuclear_heating_update(nr_count, rho, Ye, pf, Y_p, Y, entropy_p, entropy, T9_p, T9, T9_tr_p, T9_tr, timestep, T9conv)
Modifies the temperature and entropy to account for nuclear heating.
Definition: nuclear_heating.f90:320
nuclear_heating::output_nuclear_heating
subroutine, public output_nuclear_heating(cnt, ctime)
Output data related to nuclear heating.
Definition: nuclear_heating.f90:757
file_handling_class
Provide some basic file-handling routines.
Definition: file_handling_class.f90:18
error_msg_class::num_to_str
character(:) function, allocatable, public num_to_str(num)
Converts a given real to a string with format "(1pE10.2)".
Definition: error_msg_class.f90:205
nuclear_heating::reset_qdot
subroutine reset_qdot(time)
Reset the qdot variable.
Definition: nuclear_heating.f90:155
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
single_zone_vars::stepsize
real(r_kind) stepsize
Stepsize.
Definition: single_zone_vars.f90:14
r_kind
#define r_kind
Definition: macros.h:46
nuclear_heating::engen_unit
integer, private engen_unit
Engen output file.
Definition: nuclear_heating.f90:17
parameter_class::engen
real(r_kind) engen
total energy generation [MeV/s]
Definition: parameter_class.f90:109
chempot
subroutine chempot(temp, den, ye, etaele, etapos)
Given a temperature temp [K], density den [g/cm**3], and a composition characterized by y_e,...
Definition: chem_pot.f90:25
nuclear_heating::calculate_qdot
subroutine calculate_qdot(rrate, Y, h)
Definition: nuclear_heating.f90:201
parameter_class::use_thermal_nu_loss
logical use_thermal_nu_loss
Whether to include thermal neutrino loss or not.
Definition: parameter_class.f90:99
ls_timmes_eos_module::ins
integer, parameter ins
Definition: ls_timmes_eos_module.f:16
parameter_class::nu_loss_every
integer nu_loss_every
Output neutrino loss and gain.
Definition: parameter_class.f90:100
nuclear_heating::output_debug_nufrac
subroutine output_debug_nufrac(rrate_array, length)
Output the heating fractions to a debug file.
Definition: nuclear_heating.f90:267
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
nucstuff_class::inter_partf
subroutine, public inter_partf(temp, interpol)
Calculates partition function.
Definition: nucstuff_class.f90:132
global_class
Contains types and objects shared between multiple modules.
Definition: global_class.f90:19
global_class::nreac
integer, public nreac
total number of reactions
Definition: global_class.f90:98
ls_timmes_eos_module::timmes_eos_state
Definition: ls_timmes_eos_module.f:23
nuclear_heating::nuclear_heating_entropy
subroutine, private nuclear_heating_entropy(rho, Ye, pf, Y_p, Y, entropy_p, entropy, T9, eos_status)
Modifies the temperature and ent_p to account for nuclear heating.
Definition: nuclear_heating.f90:602
single_zone_vars
Simulation variables for a single zone model.
Definition: single_zone_vars.f90:11
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
single_zone_vars::t9h
real(r_kind) t9h
Definition: single_zone_vars.f90:16