expansion_module.f90
Go to the documentation of this file.
1 !> @file expansion_module.f90
2 !!
3 !! The error file code for this file is ***W17***.
4 !! @brief Module \ref expansion_module for parametric expansions
5 !!
6 
7 !>
8 !! Subroutines to handle parametric evolution of hydrodynamic quantities after the
9 !! final timestep of the trajectory
10 !!
11 !! \b Edited:
12 !! - 01.11.16
13 !! - M.R. 26.12.20 - Got rid of expansion parameter
14 !! .
15 #include "macros.h"
21  implicit none
22 
23 save
24  real(r_kind) :: mdot !< 1/4pi*dM/dr = rho*r^2 = const
25  real(r_kind) :: rho_0 !< Density [g/ccm] at the end of the trajectory
26  real(r_kind) :: rad_0 !< Radius [km] at the end of the trajectory
27  real(r_kind) :: t9_0 !< Temperature [GK] at the end of the trajectory
28  real(r_kind) :: t_0 !< Time at the end of the trajectory
29  real(r_kind) :: tau
30  real(r_kind) :: s_0 !< Entropy at the end of the trajectory (deprecated)
31  type(timmes_eos_state) :: state !< EOS state
32  real(r_kind) :: vel !< velocity [km/s]
33  real(r_kind) :: rad !< radial distance [km]
34  logical :: expand !< flag if expansion will be present
35  integer :: expand_count !< 1 for the first timestep 2 for following steps, 0 for no expansion yet
36  !-- Debugging
37  integer, private :: debug_exp !< file ID for debugging expansion
38 
39 
40 
41 contains
42 
43 
44 
45 !>
46 !! Initialize the expansion module and open files for debugging.
47 !!
48 !! This subroutine also determines if the simulation
49 !! has to use the expansion routine or not (depending
50 !! on parameter_class::termination_criterion).
51 !!
52 !! @author: Moritz Reichert
53 !!
54 !! \b Edited:
55 !! - 28.02.17
56 !! - MR 22.12.20
57 !! - MR 22.01.21
58 !! .
59  subroutine expansion_init()
64  implicit none
65 
66 
67  expand = .false.
68 
69  if ((trim(adjustl(trajectory_mode)) .eq. 'from_file')) then
70  ! Check if it has to expand
71  if (((termination_criterion .eq. 1) .and. (ztime(zsteps) .lt. final_time)) &
72  & .or. ((termination_criterion .eq. 2) .and. (minval(dexp(ztemp(init_index:))) .gt. final_temp)) &
73  & .or. ((termination_criterion .eq. 3) .and. (minval(dexp(zdens(init_index:))) .gt. final_dens)) &
74  & .or. ((termination_criterion .eq. 4) )) then
75  expand = .true.
76  end if
77 
78  if (expand) then
79  if (verbose_level .gt. 2) then
80  debug_exp = open_outfile('debug_expansion.dat')
81  write(debug_exp,'(A)') '# File for debugging subroutine expansion in expansion_module.f90'
82  write(debug_exp,'(*(A,4x))') '# Time [s]','Density [g/ccm]','Radius [km]','Old Radius [km]', &
83  'Velocity [km/s]', 'Temperature [GK]'
84  end if
85 
86  ! Consistency check
87  if ((expansiontype .lt. 1) .or. (expansiontype .gt. 8)) then
88  call raise_exception("Expansiontype ("//trim(adjustl(int_to_str(expansiontype)))&
89  //") not implemented yet. "//&
90  "Set it to a supported value!",&
91  "expansion_init",&
92  170003)
93  end if
94 
95  ! Get velocity, final density and final radius
97  expand_count = 0
98  end if
99  end if
100  end subroutine expansion_init
101 
102 
103 
104 !>
105 !! Calculates the velocity for trajectory extrapolation by linear regression
106 !! on a few last points; the number of points is controlled by the parameter
107 !! parameter_class::extrapolation_width.
108 !!
109 !! @remark At verbose Level >2 this creates a file called "debug_vel.dat"
110 !! which lists extrapolated points and the computed value of velocity.
111 !!
112 !! \b Edited:
113 !! - 09.03.17
114 !! - OK 13.01.2014
115 !! - OK 17.06.2017 - cleanup, renamed: variance -> residual_expansion
116 !! - MR 22.01.2021 - Changed entropy calculation
117 !! .
121  use hydro_trajectory
122  implicit none
123  ! integer :: eos_status
124 
125  real(r_kind) :: v ! velocity
126  !
127  integer :: i, debug_vel
128  real(r_kind) :: er,ert,et,ets,det
129 
130  ! sanity check
131  if (extrapolation_width.gt.zsteps) then
132  call raise_exception('The parameter "extrapolation_width" ('//trim(adjustl(int_to_str(extrapolation_width)))//&
133  ') should be smaller'//new_line("A")//&
134  'than the amount of trajectory points (zsteps = '//trim(adjustl(int_to_str(zsteps)))//").",&
135  'residual_expansion',&
136  170004)
137  endif
138  if (extrapolation_width.lt.2) then
139  call raise_exception('The parameter "extrapolation_width" ('//trim(adjustl(int_to_str(extrapolation_width)))//&
140  ') should be larger than 1.',&
141  'residual_expansion',&
142  170005)
143  endif
144 
145  if (extrapolation_width.eq.2) then
146  ! handle case of two endpoints
147  v= (exp(zrad(zsteps)) - exp(zrad(zsteps-1))) &
148  / (ztime(zsteps) - ztime(zsteps-1))
149  else
150  ! more than two points
151  et = 0.0
152  ets = 0.0
153  er = 0.0
154  ert = 0.0
156  et = et + ztime(i)
157  ets = ets + ztime(i)**2
158  er = er + exp(zrad(i))
159  ert = ert + ztime(i)*exp(zrad(i))
160  enddo
161  det = et*et - extrapolation_width*ets
162  v= 0.0
163  if (abs(det).gt.1e-20) then
164  v = (er*et - extrapolation_width*ert)/det
165  endif
166  endif
167 
168  if (verbose_level.ge.1) then
169  call write_data_to_std_out("Expansion velocity:",num_to_str(v),"[km/s]")
170  ! print '(A,ES12.5,A)', &
171  ! " Using expansion with residual velocity: ", v," [km/s]"
172  endif
173 
174  ! initialize module parameters
175  vel = v
176  rad_0 = exp(zrad(zsteps))
177  rho_0 = exp(zdens(zsteps))
178  t9_0 = exp(ztemp(zsteps))
179  t_0 = ztime(zsteps)
180  mdot = rho_0 * rad_0**2
181 
182  ! MR: The difference between the EOS entropy and
183  ! T9^3/rho (taking some dummy ye and abar)
184  ! differs by 5 magnitudes. This seems wrong.
185  ! In my understanding the entropy is only proportional
186  ! to T9^3/rho and not equal
187  ! (see Python script of expansion test).
188  ! The entropy S_0 is, however, also not used so far.
189  ! Therefore, I commented it out.
190 
191  ! calculate entropy
192  ! if (.not. include_nuclear_heating) then
193  ! state%abar =20
194  ! call timmes_eos(ink,T9_0*1.d9,rho_0,0.5,state,eos_status) ! Careful, dummy abar and ye used!
195  ! if(eos_status.ne.0) stop 'error in EOS'
196  ! S_0 = state%s
197  ! write(*,*) "EOS: S=",S_0
198  ! S_0 = T9_0**3/rho_0
199  ! write(*,*) "T9**3/rho",S_0
200  ! endif
201 
202  ! Debugging
203  if (verbose_level .gt. 2) then
204  ! open a file 'debug_vel.dat' and record extrapolated value
205  debug_vel = open_outfile('debug_vel.dat')
206  write(debug_vel,'(A)') '# Velocity extrapolation info'
207  write(debug_vel,'(A)') '# 1:step 2:time[s] 3:R[km]'
209  write (debug_vel,'(i4,2(1x,es15.7))') i, ztime(i), exp(zrad(i))
210  enddo
211  write (debug_vel,'("vel = ",es15.7, " km/s")') v
212  close(debug_vel)
213  end if
214 
215  if (vel .lt. 0.) call raise_exception("Expansion velocity was negative!",&
216  'residual_expansion',&
217  170006)
218 
219 end subroutine residual_expansion
220 
221 !>
222 !! Returns temperature, radius, density, and entropy after the trajectory has ended.
223 !!
224 !! This depends on the \ref parameter_class::expansiontype parameter.
225 !! Possible values are:
226 !! <table>
227 !! <caption id="multi_row">Expansiontype parameter</caption>
228 !! <tr><th> Value <th> Expansion <th> Literature
229 !! <tr><td> 1 <td> Adiabatic expansion <td> [Korobkin et al. 2012](https://ui.adsabs.harvard.edu/abs/2012MNRAS.426.1940K/abstract)
230 !! <tr><td> 2 <td> Exponential expansion <td> -
231 !! <tr><td> 3 <td> Expansion with const. velocity <td> -
232 !! <tr><td> 4 <td> Expansion with const. velocity <td> [Fujimoto et al. 2008](https://ui.adsabs.harvard.edu/abs/2008ApJ...680.1350F/abstract)
233 !! </table>
234 !!
235 !! \b Edited:
236 !! - 26.01.21 - MR
237 !! - 17.02.21 - MR: Cleaned up the routine and removed some expansion types
238 !! .
239 subroutine expansion(t,dt,ye,dens,rad_in,temp,entropy,vel_in,abar)
242  use hydro_trajectory, only: ztemp,zsteps
243  implicit none
244 
245  real(r_kind),intent(in) :: t
246  real(r_kind),intent(in) :: dt
247  real(r_kind),intent(in) :: abar ! Average mass number (TODO: add this as an use statement after restructure of the code)
248  real(r_kind),intent(inout) :: dens
249  real(r_kind),intent(inout) :: rad_in
250  real(r_kind),intent(inout) :: temp
251  real(r_kind),intent(in) :: entropy
252  real(r_kind),intent(inout) :: vel_in
253  real(r_kind),intent(in) :: ye
254  real(r_kind) :: time
255  real(r_kind) :: rold,dold
256  logical :: calc_temperature
257  integer :: eos_status
258 
259  ! It can happen that the function is called even when there should be
260  ! no expansion (e.g., because the timestep is restricted after the
261  ! hydro update call). Therefore return without doing something.
262  if (.not. expand) return
263 
264  rold = rad_in
265  dold = dens
266  time = t+dt-t_0 ! time that has passed since the last step in the trajectory
267 
268  calc_temperature = ((heating_mode .eq. 0) .and. (temp .gt. freeze_rate_temp))
269 
270  ! calc_temperature = (((heating_mode .eq. 2) .and. (temp .gt. freeze_rate_temp)) &
271  ! .or. (temp .gt. min(max(dexp(ztemp(zsteps)),1d-6),freeze_rate_temp) &
272  ! .and. (.not. (heating_mode .eq. 1))))
273 
274  select case (expansiontype)
275  case(1) !adiabatic expansion (from Korobkin et al. (2012))
276  rad_in = rad_0 + time*vel_in
277  dens = rho_0*(t_0/(time+t_0))**3
278  ! Ensure to call the EOS only at valid points, i.e., above some temperature
279  if (calc_temperature) then
280  state%abar = abar
281  call timmes_eos(ins,entropy,dens,ye,state,eos_status)
282  if(eos_status.ne.0) call raise_exception('Error when calling the EOS.','expansion',&
283  170007)
284  temp = 1.d-9*state%t
285  end if
286  case(2) !exponential expansion
287  rad_in = rad_0 + time*vel_in
288  tau = t_0 ! TODO: move to parameter_class
289  dens = rho_0*dexp(-time/tau)
290  ! Prevent underflows
291  dens = max(dens,1d-99)
292  ! Ensure to call the EOS only at valid points, i.e., above some temperature
293  if (calc_temperature) then
294  state%abar = abar
295  call timmes_eos(ins,entropy,dens,ye,state,eos_status)
296  if(eos_status.ne.0) call raise_exception('Error when calling the EOS.','expansion',&
297  170007)
298  temp = 1.d-9*state%t
299  end if
300  case(3) !expansion with constant velocity
301  rad_in = rad_0 + time*vel_in
302  dens = mdot/(rad_in**2)! rho_0 *(r_0/r)**2
303  ! Ensure to call the EOS only at valid points, i.e., above some temperature
304  if (calc_temperature) then
305  state%abar = abar
306  call timmes_eos(ins,entropy,dens,ye,state,eos_status)
307  if(eos_status.ne.0) call raise_exception('Error when calling the EOS.','expansion',&
308  170007)
309  temp = 1.d-9*state%t
310  end if
311  case(4) !expansion with constant velocity as in fujimoto apj 680
312  rad_in = rad_0 + time*vel_in
313  ! Free spherical symmetric expansion
314  dens = rho_0*(rad_0/rad_in)**3
315  ! Ensure to call the EOS only at valid points, i.e., above some temperature
316  if (calc_temperature) then
317  state%abar = abar
318  call timmes_eos(ins,entropy,dens,ye,state,eos_status)
319  if(eos_status.ne.0) call raise_exception('Error when calling the EOS.','expansion',&
320  170007)
321  temp = 1.d-9*state%t
322  end if
323  ! Alternatively:
324  ! The temperature refers to an adiabatic expansion as S \propto T^3/rho = const
325  ! temp = t9_0*rad_0/rad
326  case default
327  call raise_exception('Expansion type not (yet) supported.',&
328  'expansion',170008)
329  end select
330 
331  ! Set the temperature above some threshold value,
332  ! that is either the minimum of the trajectory,
333  ! 1d-2GK or 1d-6GK.
334  ! The rates are frozen in any case at 1d-2GK in the Jacobian class
335  if (calc_temperature) then
336  temp = max(temp,freeze_rate_temp)
337  end if
338 
339  ! Debug file
340  if (verbose_level .gt. 2) then
341  write(debug_exp,'(*(10es23.14,4x))')time,dens,rad_in,rold,vel_in,temp
342  end if
343 
344  ! Check which expansion step this was
345  if (expand_count .lt. 2) expand_count = expand_count+1
346 
347  return
348 
349 end subroutine expansion
350 
351 
352 !>
353 !! Close debug files of the module
354 !!
355 !! @author: Moritz Reichert
356 !!
357 !! \b Edited:
358 !! - 28.02.17
359 !! .
360 subroutine expansion_finalize()
362  implicit none
363 
364  if ((verbose_level .gt. 2) .and. (expand)) then
365  call close_io_file(debug_exp,'debug_expansion.dat')
366  end if
367 
368 end subroutine expansion_finalize
369 
370 end module expansion_module
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
expansion_module::s_0
real(r_kind) s_0
Entropy at the end of the trajectory (deprecated)
Definition: expansion_module.f90:30
expand
Definition: expand.py:1
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
expansion_module::expansion
subroutine expansion(t, dt, ye, dens, rad_in, temp, entropy, vel_in, abar)
Returns temperature, radius, density, and entropy after the trajectory has ended.
Definition: expansion_module.f90:240
ls_timmes_eos_module
Definition: ls_timmes_eos_module.f:2
expansion_module::expansion_finalize
subroutine expansion_finalize()
Close debug files of the module.
Definition: expansion_module.f90:361
expansion_module::state
type(timmes_eos_state) state
EOS state.
Definition: expansion_module.f90:31
expansion_module::expansion_init
subroutine expansion_init()
Initialize the expansion module and open files for debugging.
Definition: expansion_module.f90:60
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
expansion_module
Subroutines to handle parametric evolution of hydrodynamic quantities after the final timestep of the...
Definition: expansion_module.f90:16
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
expansion_module::rad
real(r_kind) rad
radial distance [km]
Definition: expansion_module.f90:33
expansion_module::debug_exp
integer, private debug_exp
file ID for debugging expansion
Definition: expansion_module.f90:37
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
parameter_class::final_dens
real(r_kind) final_dens
termination density [g/cm3]
Definition: parameter_class.f90:131
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
expansion_module::rho_0
real(r_kind) rho_0
Density [g/ccm] at the end of the trajectory.
Definition: expansion_module.f90:25
expansion_module::t9_0
real(r_kind) t9_0
Temperature [GK] at the end of the trajectory.
Definition: expansion_module.f90:27
error_msg_class::write_data_to_std_out
subroutine, public write_data_to_std_out(str_msg, value_str, unit)
Write data to the standard output (usually OUT)
Definition: error_msg_class.f90:122
hydro_trajectory::ztime
real(r_kind), dimension(:), allocatable, public ztime
time information from trajectory
Definition: hydro_trajectory.f90:19
expansion_module::t_0
real(r_kind) t_0
Time at the end of the trajectory.
Definition: expansion_module.f90:28
hydro_trajectory::zrad
real(r_kind), dimension(:), allocatable, public zrad
radii from trajectory
Definition: hydro_trajectory.f90:23
expansion_module::vel
real(r_kind) vel
velocity [km/s]
Definition: expansion_module.f90:32
file_handling_class
Provide some basic file-handling routines.
Definition: file_handling_class.f90:18
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::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
hydro_trajectory::init_index
integer init_index
Initial index in the trajectory.
Definition: hydro_trajectory.f90:18
r_kind
#define r_kind
Definition: macros.h:46
expansion_module::mdot
real(r_kind) mdot
1/4pi*dM/dr = rho*r^2 = const
Definition: expansion_module.f90:24
expansion_module::tau
real(r_kind) tau
Definition: expansion_module.f90:29
hydro_trajectory::zsteps
integer zsteps
number of timesteps in the hydro trajectory
Definition: hydro_trajectory.f90:17
hydro_trajectory
Contains arrays representing thermodynamic conditions from hydro trajectory file.
Definition: hydro_trajectory.f90:14
hydro_trajectory::zdens
real(r_kind), dimension(:), allocatable, public zdens
density information from trajectory
Definition: hydro_trajectory.f90:21
ls_timmes_eos_module::ins
integer, parameter ins
Definition: ls_timmes_eos_module.f:16
expansion_module::rad_0
real(r_kind) rad_0
Radius [km] at the end of the trajectory.
Definition: expansion_module.f90:26
parameter_class::final_time
real(r_kind) final_time
termination time in seconds
Definition: parameter_class.f90:129
parameter_class::final_temp
real(r_kind) final_temp
termination temperature [GK]
Definition: parameter_class.f90:130
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
expansion_module::residual_expansion
subroutine residual_expansion
Calculates the velocity for trajectory extrapolation by linear regression on a few last points; the n...
Definition: expansion_module.f90:119
file_handling_class::close_io_file
subroutine, public close_io_file(unit_no, file_name)
Close an external file.
Definition: file_handling_class.f90:144
ls_timmes_eos_module::timmes_eos_state
Definition: ls_timmes_eos_module.f:23
hydro_trajectory::ztemp
real(r_kind), dimension(:), allocatable, public ztemp
temperature information from trajectory
Definition: hydro_trajectory.f90:20
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
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24