Line data Source code
1 : ! ***********************************************************************
2 : !
3 : ! Copyright (C) 2010 The MESA Team
4 : !
5 : ! This program is free software: you can redistribute it and/or modify
6 : ! it under the terms of the GNU Lesser General Public License
7 : ! as published by the Free Software Foundation,
8 : ! either version 3 of the License, or (at your option) any later version.
9 : !
10 : ! This program is distributed in the hope that it will be useful,
11 : ! but WITHOUT ANY WARRANTY; without even the implied warranty of
12 : ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
13 : ! See the GNU Lesser General Public License for more details.
14 : !
15 : ! You should have received a copy of the GNU Lesser General Public License
16 : ! along with this program. If not, see <https://www.gnu.org/licenses/>.
17 : !
18 : ! ***********************************************************************
19 :
20 : module init
21 :
22 : use star_private_def
23 : use const_def, only: dp, msun, secyer
24 :
25 : implicit none
26 :
27 : private
28 : public :: alloc_star_data
29 : public :: set_starting_star_data
30 : public :: do_star_init
31 : public :: do_starlib_shutdown
32 : public :: set_kap_and_eos_handles
33 : public :: set_colors_handles
34 : public :: load_zams_model
35 : public :: create_pre_ms_model
36 : public :: create_initial_model
37 : public :: create_RSP_model
38 : public :: create_RSP2_model
39 : public :: doing_restart
40 : public :: load_restart_photo
41 : public :: load_saved_model
42 : public :: do_garbage_collection
43 :
44 : integer, parameter :: do_create_pre_ms_model = 0
45 : integer, parameter :: do_load_zams_model = 1
46 : integer, parameter :: do_load_saved_model = 2
47 : integer, parameter :: do_create_initial_model = 3
48 : integer, parameter :: do_create_RSP_model = 4
49 : integer, parameter :: do_create_RSP2_model = 5
50 :
51 : logical :: have_done_starlib_init = .false.
52 :
53 : contains
54 :
55 1 : subroutine set_kap_and_eos_handles(id, ierr)
56 : use kap_lib, only: alloc_kap_handle_using_inlist, kap_ptr
57 : use eos_lib, only: alloc_eos_handle_using_inlist, eos_ptr
58 : integer, intent(in) :: id
59 : integer, intent(out) :: ierr ! 0 means AOK.
60 : type (star_info), pointer :: s
61 1 : call get_star_ptr(id, s, ierr)
62 1 : if (ierr /= 0) then
63 0 : write(*,*) 'get_star_ptr failed in alloc_eos_handle'
64 0 : return
65 : end if
66 1 : if (s% eos_handle == 0) then
67 1 : s% eos_handle = alloc_eos_handle_using_inlist(s% inlist_fname, ierr)
68 1 : if (ierr /= 0) then
69 0 : write(*,*) 'set_kap_and_eos_handles failed in alloc_eos_handle_using_inlist'
70 0 : return
71 : end if
72 1 : call eos_ptr(s% eos_handle, s% eos_rq, ierr)
73 1 : if (ierr /= 0) then
74 0 : write(*,*) 'eos_ptr failed in alloc_eos_handle'
75 0 : return
76 : end if
77 : end if
78 1 : if (s% kap_handle == 0) then
79 1 : s% kap_handle = alloc_kap_handle_using_inlist(s% inlist_fname, ierr)
80 1 : if (ierr /= 0) then
81 0 : write(*,*) 'set_kap_and_eos_handles failed in alloc_kap_handle_using_inlist'
82 0 : return
83 : end if
84 1 : call kap_ptr(s% kap_handle,s% kap_rq,ierr)
85 1 : if (ierr /= 0) then
86 0 : write(*,*) 'kap_ptr failed in alloc_kap_handle'
87 0 : return
88 : end if
89 : end if
90 1 : end subroutine set_kap_and_eos_handles
91 :
92 :
93 1 : subroutine set_colors_handles(id, ierr)
94 1 : use colors_lib, only: alloc_colors_handle_using_inlist, colors_ptr
95 : use colors_def, only: Colors_General_Info
96 : integer, intent(in) :: id
97 : integer, intent(out) :: ierr ! 0 means AOK.
98 : type (star_info), pointer :: s
99 : type(Colors_General_Info), pointer :: colors_settings
100 1 : call get_star_ptr(id, s, ierr)
101 1 : if (ierr /= 0) then
102 0 : write(*,*) 'get_star_ptr failed in alloc_colors_handle'
103 0 : return
104 : end if
105 1 : if (s% colors_handle == 0) then
106 1 : s% colors_handle = alloc_colors_handle_using_inlist(s% inlist_fname, ierr)
107 1 : if (ierr /= 0) then
108 0 : write(*,*) 'set_colors_handles failed in alloc_colors_handle'
109 0 : return
110 : end if
111 1 : call colors_ptr(s% colors_handle, colors_settings, ierr)
112 1 : if (ierr /= 0) then
113 0 : write(*,*) 'colors_ptr failed in alloc_colors_handle'
114 0 : return
115 : end if
116 : end if
117 : end subroutine set_colors_handles
118 :
119 1 : subroutine do_star_init( &
120 : my_mesa_dir, chem_isotopes_filename, &
121 : net_reaction_filename, jina_reaclib_filename, &
122 : use_suzuki_weak_rates, &
123 : use_special_weak_rates, special_weak_states_file, special_weak_transitions_file, &
124 : reaclib_min_T9, &
125 : rate_tables_dir, rates_cache_suffix, &
126 : ionization_file_prefix, ionization_Z1_suffix, &
127 : eosDT_cache_dir, &
128 : ionization_cache_dir, kap_cache_dir, rates_cache_dir, &
129 : ierr)
130 : use paquette_coeffs, only: initialise_collision_integrals
131 : use alloc, only: init_alloc
132 : character (len=*), intent(in) :: &
133 : my_mesa_dir, chem_isotopes_filename, net_reaction_filename, &
134 : jina_reaclib_filename, rate_tables_dir, &
135 : special_weak_states_file, special_weak_transitions_file, &
136 : rates_cache_suffix, &
137 : ionization_file_prefix, ionization_Z1_suffix, &
138 : eosDT_cache_dir, &
139 : ionization_cache_dir, kap_cache_dir, rates_cache_dir
140 : logical, intent(in) :: use_suzuki_weak_rates, use_special_weak_rates
141 : real(dp), intent(in) :: reaclib_min_T9
142 : integer, intent(out) :: ierr
143 : include 'formats'
144 1 : ierr = 0
145 1 : if (have_done_starlib_init) return
146 1 : call initialise_collision_integrals
147 1 : call init_alloc
148 : call stardata_init( &
149 : my_mesa_dir, chem_isotopes_filename, &
150 : net_reaction_filename, jina_reaclib_filename, &
151 : use_suzuki_weak_rates, &
152 : use_special_weak_rates, special_weak_states_file, special_weak_transitions_file, &
153 : reaclib_min_T9, &
154 : rate_tables_dir, rates_cache_suffix, &
155 : ionization_file_prefix, ionization_Z1_suffix, &
156 : eosDT_cache_dir, &
157 : ionization_cache_dir, kap_cache_dir, rates_cache_dir, &
158 1 : ierr)
159 1 : if (ierr /= 0) then
160 0 : write(*,*) 'failed in stardata_init'
161 0 : return
162 : end if
163 :
164 1 : have_done_starlib_init = .true.
165 :
166 1 : end subroutine do_star_init
167 :
168 :
169 1 : subroutine do_starlib_shutdown
170 :
171 1 : use alloc, only: shutdown_alloc
172 : use micro, only: shutdown_microphys
173 : use atm_lib, only: atm_shutdown
174 : use colors_lib, only: colors_shutdown
175 : use chem_lib, only: chem_shutdown
176 : use rates_lib, only: rates_shutdown
177 : use star_profile_def, only: profile_column_names_shutdown
178 : use star_history_def, only: history_column_names_shutdown
179 : use paquette_coeffs, only: free_collision_integrals
180 :
181 1 : call rates_shutdown()
182 1 : call atm_shutdown()
183 1 : call shutdown_microphys()
184 1 : call colors_shutdown()
185 1 : call chem_shutdown()
186 1 : call profile_column_names_shutdown()
187 1 : call history_column_names_shutdown()
188 :
189 1 : call free_collision_integrals()
190 :
191 1 : call shutdown_alloc()
192 :
193 1 : have_done_starlib_init = .false.
194 :
195 1 : end subroutine do_starlib_shutdown
196 :
197 :
198 2 : subroutine alloc_star_data(id, ierr)
199 1 : use chem_def, only: num_categories
200 : use net, only: default_set_rate_factors, &
201 : default_set_op_mono_factors
202 :
203 :
204 : integer, intent(out) :: id, ierr
205 :
206 : type (star_info), pointer :: s
207 : integer, parameter :: init_alloc_nvar = 20
208 : character (len=32) :: extra_name
209 : integer :: i
210 :
211 : ierr = 0
212 :
213 2 : call alloc_star(id, ierr)
214 2 : if (ierr /= 0) then
215 0 : write(*,*) 'alloc_star_data failed in alloc_star'
216 0 : return
217 : end if
218 :
219 2 : call get_star_ptr(id, s, ierr)
220 2 : if (ierr /= 0) then
221 0 : write(*,*) 'alloc_star_data failed in get_star_ptr'
222 0 : return
223 : end if
224 :
225 2 : nullify(s% dq)
226 2 : nullify(s% xa)
227 2 : nullify(s% xh)
228 :
229 : nullify( &
230 2 : s% op_mono_umesh1, s% op_mono_semesh1, s% op_mono_ff1, &
231 2 : s% op_mono_rs1)
232 :
233 2 : nullify(s% atm_structure)
234 2 : s% atm_structure_num_pts = 0
235 :
236 2 : nullify(s% chem_id)
237 2 : nullify(s% xa_removed)
238 :
239 2 : nullify(s% rate_factors)
240 2 : s% set_rate_factors => default_set_rate_factors
241 :
242 2 : nullify(s% op_mono_factors)
243 2 : s% set_op_mono_factors => default_set_op_mono_factors
244 :
245 2 : allocate(s% nameofvar(init_alloc_nvar),stat=ierr)
246 2 : if (ierr /= 0) return
247 :
248 2 : allocate(s% nameofequ(init_alloc_nvar),stat=ierr)
249 2 : if (ierr /= 0) return
250 :
251 2 : nullify(s% history_values)
252 2 : nullify(s% history_value_is_integer)
253 2 : nullify(s% history_names)
254 2 : nullify(s% history_names_dict)
255 :
256 2 : nullify(s% prev_mesh_xh)
257 2 : nullify(s% prev_mesh_xa)
258 2 : nullify(s% prev_mesh_j_rot)
259 2 : nullify(s% prev_mesh_omega)
260 2 : nullify(s% prev_mesh_dq)
261 :
262 2 : nullify(s% D_ST_start)
263 2 : nullify(s% prev_mesh_D_ST_start)
264 :
265 2 : nullify(s% other_star_info)
266 :
267 2 : nullify(s% bcyclic_odd_storage)
268 2 : nullify(s% bcyclic_odd_storage_qp)
269 :
270 2 : nullify(s% solver_iwork)
271 2 : nullify(s% solver_work)
272 2 : nullify(s% AF1)
273 :
274 2 : s% net_name = ''
275 2 : s% species = 0
276 2 : s% num_reactions = 0
277 :
278 2 : s% M_center = 0
279 2 : s% R_center = 0
280 2 : s% v_center = 0
281 2 : s% L_center = 0
282 :
283 2 : nullify(s% profile_column_spec)
284 2 : nullify(s% history_column_spec)
285 :
286 2 : s% num_conv_boundaries = 0
287 2 : nullify(s% conv_bdy_q)
288 2 : nullify(s% conv_bdy_loc)
289 2 : nullify(s% top_conv_bdy)
290 :
291 2 : s% num_mix_boundaries = 0
292 2 : nullify(s% mix_bdy_q)
293 2 : nullify(s% mix_bdy_loc)
294 2 : nullify(s% top_mix_bdy)
295 :
296 2 : nullify(s% burn_h_conv_region)
297 2 : nullify(s% burn_he_conv_region)
298 2 : nullify(s% burn_z_conv_region)
299 :
300 2 : s% have_burner_storage = .false.
301 2 : s% burner_num_threads = 0
302 2 : nullify(s% burner_storage)
303 :
304 2 : s% doing_timing = .false.
305 2 : s% time_evolve_step = 0
306 2 : s% time_remesh = 0
307 2 : s% time_adjust_mass = 0
308 2 : s% time_conv_premix = 0
309 2 : s% time_element_diffusion = 0
310 2 : s% time_struct_burn_mix = 0
311 2 : s% time_solver_matrix = 0
312 2 : s% time_solve_mix = 0
313 2 : s% time_solve_burn = 0
314 2 : s% time_solve_omega_mix = 0
315 2 : s% time_eos = 0
316 2 : s% time_neu_kap = 0
317 2 : s% time_nonburn_net = 0
318 2 : s% time_mlt = 0
319 2 : s% time_set_hydro_vars = 0
320 2 : s% time_set_mixing_info = 0
321 2 : s% time_total = 0
322 :
323 2 : s% timing_num_get_eos_calls = 0
324 2 : s% timing_num_solve_eos_calls = 0
325 2 : s% timing_num_get_kap_calls = 0
326 :
327 2 : s% model_profile_filename = ''
328 2 : s% most_recent_profile_filename = ''
329 :
330 2 : s% model_controls_filename = ''
331 2 : s% most_recent_controls_filename = ''
332 :
333 2 : s% most_recent_photo_name = ''
334 :
335 2 : s% doing_flash_wind = .false.
336 2 : s% doing_rlo_wind = .false.
337 :
338 2 : s% phase_of_evolution = phase_starting
339 2 : s% recent_log_header = -1000
340 :
341 2 : s% tau_base = 2d0/3d0
342 2 : s% tau_factor = 1
343 :
344 2 : s% solver_iter = 0
345 :
346 2 : s% using_gold_tolerances = .false.
347 2 : s% using_velocity_time_centering = .false.
348 :
349 2 : s% using_revised_net_name = .false.
350 2 : s% revised_net_name = ''
351 :
352 2 : s% using_revised_max_yr_dt = .false.
353 2 : s% revised_max_yr_dt = 0
354 :
355 2 : s% astero_using_revised_max_yr_dt = .false.
356 2 : s% astero_revised_max_yr_dt = 0
357 :
358 2 : s% cumulative_energy_error = 0
359 2 : s% cumulative_extra_heating = 0
360 :
361 2 : s% have_initial_energy_integrals = .false.
362 :
363 2 : s% num_solver_iterations = 0
364 2 : s% mesh_call_number = 0
365 2 : s% solver_call_number = 0
366 2 : s% diffusion_call_number = 0
367 2 : s% model_number = 0
368 2 : s% RSP_have_set_velocities = .false.
369 2 : s% RSP_just_set_velocities = .false.
370 2 : s% rsp_period = 0d0
371 :
372 2 : s% dt = 0d0
373 2 : s% mstar_dot = 0d0
374 :
375 2 : s% power_nuc_burn = -1
376 2 : s% power_h_burn = -1
377 2 : s% power_he_burn = -1
378 2 : s% power_z_burn = -1
379 2 : s% power_photo = -1
380 :
381 2 : s% k_const_mass = 1
382 2 : s% k_below_just_added = 1
383 2 : s% k_below_const_q = 1
384 :
385 2 : s% why_Tlim = Tlim_struc
386 118 : s% dt_why_count(:) = 0
387 118 : s% dt_why_retry_count(:) = 0
388 :
389 2 : s% len_extra_iwork = 0
390 2 : s% len_extra_work = 0
391 :
392 2 : s% eos_handle = 0
393 2 : s% kap_handle = 0
394 2 : s% colors_handle = 0
395 :
396 202 : do i = 1, max_num_profile_extras
397 200 : if (i < 10) then
398 18 : write(extra_name,'(a,i1)') 'profile_extra_', i
399 182 : else if (i < 100) then
400 180 : write(extra_name,'(a,i2)') 'profile_extra_', i
401 : else
402 2 : write(extra_name,'(a,i3)') 'profile_extra_', i
403 : end if
404 202 : s% profile_extra_name(i) = trim(extra_name)
405 : end do
406 :
407 2 : call set_starting_star_data(s, ierr)
408 2 : if (ierr /= 0) then
409 0 : write(*,*) 'alloc_star_data failed in set_starting_star_data'
410 0 : return
411 : end if
412 :
413 8 : end subroutine alloc_star_data
414 :
415 :
416 11 : subroutine null_other_new_generation(id, ierr)
417 : integer, intent(in) :: id
418 : integer, intent(out) :: ierr
419 11 : ierr = 0
420 2 : end subroutine null_other_new_generation
421 :
422 :
423 11 : subroutine null_other_set_current_to_old(id)
424 : integer, intent(in) :: id
425 11 : end subroutine null_other_set_current_to_old
426 :
427 :
428 2 : subroutine set_starting_star_data(s, ierr)
429 : use other_wind, only: null_other_wind
430 : use other_accreting_state, only: null_other_accreting_state
431 : use other_adjust_mdot, only: null_other_adjust_mdot
432 : use other_j_for_adjust_J_lost, only: null_other_j_for_adjust_J_lost
433 : use other_eval_fp_ft, only: null_other_eval_fp_ft
434 : use other_eval_i_rot, only: null_other_eval_i_rot
435 : use other_torque, only: default_other_torque
436 : use other_torque_implicit, only: default_other_torque_implicit
437 : use other_remove_surface, only: default_other_remove_surface
438 : use other_momentum, only: default_other_momentum
439 : use other_momentum_implicit, only: default_other_momentum_implicit
440 : use other_pressure, only: default_other_pressure
441 : use other_energy, only: default_other_energy
442 : use other_energy_implicit, only: default_other_energy_implicit
443 : use other_D_mix, only: null_other_D_mix
444 : use other_am_mixing, only: null_other_am_mixing
445 : use other_brunt, only: default_other_brunt
446 : use other_brunt_smoothing, only: null_other_brunt_smoothing
447 : use other_adjust_mlt_gradT_fraction, only: &
448 : default_other_adjust_mlt_gradT_fraction
449 : use other_after_set_mixing_info, only: &
450 : default_other_after_set_mixing_info
451 : use other_after_solver_setmatrix, only: &
452 : default_other_after_solver_setmatrix
453 : use other_diffusion, only: null_other_diffusion
454 : use other_diffusion_factor, only: default_other_diffusion_factor
455 : use other_neu, only: null_other_neu
456 : use other_net_get, only: null_other_net_get
457 : use other_cgrav, only: default_other_cgrav
458 : use other_mesh_delta_coeff_factor, only: default_other_mesh_delta_coeff_factor
459 : use other_alpha_mlt, only: default_other_alpha_mlt
460 : use other_mlt_results, only: null_other_mlt_results
461 : use other_opacity_factor, only: default_other_opacity_factor
462 : use other_pgstar_plots, only: null_other_pgstar_plots_info
463 : use other_mesh_functions
464 : use other_eps_grav, only: null_other_eps_grav
465 : use other_rsp_build_model, only: null_other_rsp_build_model
466 : use other_rsp_linear_analysis, only: null_other_rsp_linear_analysis
467 : use other_gradr_factor, only: null_other_gradr_factor
468 : use other_surface_PT, only: null_other_surface_PT
469 : use other_timestep_limit, only: null_other_timestep_limit
470 : use other_overshooting_scheme, only: null_other_overshooting_scheme
471 : use other_photo_write, only: default_other_photo_write
472 : use other_photo_read, only: default_other_photo_read
473 : use other_set_pgstar_controls, only: default_other_set_pgstar_controls
474 : use other_kap
475 : use pgstar_decorator
476 : use star_utils, only: init_random
477 :
478 : type (star_info), pointer :: s
479 : integer, intent(out) :: ierr
480 :
481 : ! note: keep the handles for eos, kap, and net
482 :
483 2 : ierr = 0
484 :
485 2 : s% model_number = 0
486 2 : s% time = 0
487 2 : s% dt = 0
488 :
489 2 : s% total_num_solver_iterations = 0
490 2 : s% total_num_solver_relax_iterations = 0
491 2 : s% total_num_solver_calls_made = 0
492 2 : s% total_num_solver_relax_calls_made = 0
493 2 : s% total_num_solver_calls_converged = 0
494 2 : s% total_num_solver_relax_calls_converged = 0
495 :
496 2 : s% num_solver_iterations = 0
497 2 : s% num_skipped_setvars = 0
498 2 : s% num_setvars = 0
499 2 : s% num_solver_setvars = 0
500 2 : s% num_retries = 0
501 2 : s% num_hydro_merges = 0
502 2 : s% num_hydro_splits = 0
503 2 : s% timestep_hold = -1
504 :
505 2 : s% mesh_call_number = 0
506 2 : s% solver_call_number = 0
507 2 : s% diffusion_call_number = 0
508 2 : s% model_number_for_last_retry = 0
509 2 : s% dt_limit_ratio = 0
510 2 : s% force_tau_factor = 0
511 2 : s% force_Tsurf_factor = 0
512 2 : s% force_opacity_factor = 0
513 :
514 2 : s% generations = 0
515 :
516 2 : s% nvar_hydro = 0
517 2 : s% nvar_chem = 0
518 2 : s% nvar_total = 0
519 :
520 2 : s% nz = 0
521 2 : s% prev_mesh_nz = 0
522 2 : s% net_name = ''
523 2 : s% species = 0
524 2 : s% num_reactions = 0
525 :
526 2 : s% fix_Pgas = .false.
527 2 : s% v_flag = .false.
528 2 : s% u_flag = .false.
529 2 : s% rotation_flag = .false.
530 2 : s% RTI_flag = .false.
531 2 : s% w_div_wc_flag = .false.
532 2 : s% D_omega_flag = .false.
533 2 : s% am_nu_rot_flag = .false.
534 2 : s% RSP_flag = .false.
535 2 : s% RSP2_flag = .false.
536 :
537 2 : s% have_mixing_info = .false.
538 2 : s% doing_solver_iterations = .false.
539 2 : s% need_to_setvars = .true.
540 2 : s% okay_to_set_mixing_info = .true.
541 2 : s% okay_to_set_mlt_vc = .false. ! not until have set mlt_cv_old
542 2 : s% have_mlt_vc = .false.
543 :
544 2 : s% have_ST_start_info = .false.
545 2 : s% prev_mesh_have_ST_start_info = .false.
546 :
547 2 : s% just_wrote_terminal_header = .false.
548 2 : s% doing_relax = .false.
549 2 : s% mstar_dot = 0
550 2 : s% surf_lnS = 0
551 :
552 2 : s% termination_code = -1
553 :
554 2 : s% screening_mode_value = -1
555 :
556 2 : s% dt = -1
557 2 : s% dt_next = -1
558 2 : s% dt_next_unclipped = -1
559 :
560 2 : s% i_lnd = 0
561 2 : s% i_lnT = 0
562 2 : s% i_lnR = 0
563 2 : s% i_lum = 0
564 2 : s% i_v = 0
565 2 : s% i_u = 0
566 2 : s% i_alpha_RTI = 0
567 :
568 2 : s% i_dv_dt = 0
569 2 : s% i_du_dt = 0
570 2 : s% i_equL = 0
571 2 : s% i_dlnd_dt = 0
572 2 : s% i_dlnE_dt = 0
573 2 : s% i_dlnR_dt = 0
574 2 : s% i_dalpha_RTI_dt = 0
575 :
576 2 : s% op_mono_nptot = 0
577 2 : s% op_mono_ipe = 0
578 2 : s% op_mono_nrad = 0
579 2 : s% op_mono_n = 0
580 :
581 2 : s% number_of_history_columns = -1
582 2 : s% model_number_of_history_values = -1
583 2 : s% need_to_set_history_names_etc = .true.
584 2 : s% doing_finish_load_model = .false.
585 :
586 2 : nullify(s% finish_relax_step)
587 2 : nullify(s% finished_relax)
588 :
589 : s% how_many_extra_profile_header_items => &
590 2 : null_how_many_extra_header_items
591 : s% data_for_extra_profile_header_items => &
592 2 : null_data_for_extra_header_items
593 :
594 : s% how_many_extra_history_header_items => &
595 2 : null_how_many_extra_header_items
596 : s% data_for_extra_history_header_items => &
597 2 : null_data_for_extra_header_items
598 :
599 2 : s% other_wind => null_other_wind
600 2 : s% other_accreting_state => null_other_accreting_state
601 2 : s% other_adjust_mdot => null_other_adjust_mdot
602 2 : s% other_j_for_adjust_J_lost => null_other_j_for_adjust_J_lost
603 2 : s% other_D_mix => null_other_D_mix
604 2 : s% other_am_mixing => null_other_am_mixing
605 2 : s% other_eval_fp_ft => null_other_eval_fp_ft
606 2 : s% other_eval_i_rot => null_other_eval_i_rot
607 2 : s% other_torque => default_other_torque
608 2 : s% other_torque_implicit => default_other_torque_implicit
609 2 : s% other_remove_surface => default_other_remove_surface
610 2 : s% other_momentum => default_other_momentum
611 2 : s% other_momentum_implicit => default_other_momentum_implicit
612 2 : s% other_pressure => default_other_pressure
613 2 : s% other_energy => default_other_energy
614 2 : s% other_energy_implicit => default_other_energy_implicit
615 2 : s% other_cgrav => default_other_cgrav
616 2 : s% other_mesh_delta_coeff_factor => default_other_mesh_delta_coeff_factor
617 2 : s% other_alpha_mlt => default_other_alpha_mlt
618 2 : s% other_opacity_factor => default_other_opacity_factor
619 2 : s% other_brunt => default_other_brunt
620 2 : s% other_brunt_smoothing => null_other_brunt_smoothing
621 2 : s% other_adjust_mlt_gradT_fraction => default_other_adjust_mlt_gradT_fraction
622 2 : s% other_after_set_mixing_info => default_other_after_set_mixing_info
623 2 : s% other_after_solver_setmatrix => default_other_after_solver_setmatrix
624 2 : s% other_diffusion => null_other_diffusion
625 2 : s% other_diffusion_factor => default_other_diffusion_factor
626 2 : s% other_mlt_results => null_other_mlt_results
627 2 : s% other_neu => null_other_neu
628 2 : s% other_net_get => null_other_net_get
629 2 : s% other_eps_grav => null_other_eps_grav
630 2 : s% other_rsp_build_model => null_other_rsp_build_model
631 2 : s% other_rsp_linear_analysis => null_other_rsp_linear_analysis
632 2 : s% other_gradr_factor => null_other_gradr_factor
633 :
634 2 : s% other_kap_get => null_other_kap_get
635 2 : s% other_kap_get_op_mono => null_other_kap_get_op_mono
636 :
637 2 : s% other_surface_PT => null_other_surface_PT
638 :
639 2 : s% other_timestep_limit => null_other_timestep_limit
640 2 : s% other_overshooting_scheme => null_other_overshooting_scheme
641 :
642 2 : s% other_pgstar_plots_info => null_other_pgstar_plots_info
643 2 : s% how_many_other_mesh_fcns => null_how_many_other_mesh_fcns
644 2 : s% other_mesh_fcn_data => null_other_mesh_fcn_data
645 :
646 2 : s% other_photo_write => default_other_photo_write
647 2 : s% other_photo_read => default_other_photo_read
648 :
649 2 : s% other_set_pgstar_controls => default_other_set_pgstar_controls
650 :
651 2 : s% other_new_generation => null_other_new_generation
652 2 : s% other_set_current_to_old => null_other_set_current_to_old
653 :
654 2 : nullify(s% extra_profile_col_names)
655 2 : nullify(s% extra_profile_col_vals)
656 2 : s% num_extra_profile_cols = 0
657 :
658 2 : s% binary_id = 0
659 2 : s% include_binary_history_in_log_file = .false.
660 2 : s% how_many_binary_history_columns => null_how_many_binary_history_columns
661 2 : s% data_for_binary_history_columns => null_data_for_binary_history_columns
662 2 : s% how_many_extra_binary_history_columns => null_how_many_extra_binary_history_columns
663 2 : s% data_for_extra_binary_history_columns => null_data_for_extra_binary_history_columns
664 :
665 2 : s% generations = 0
666 :
667 2 : s% nz = 0
668 :
669 2 : s% nvar_hydro = 0
670 2 : s% nvar_chem = 0
671 2 : s% nvar_total = 0
672 :
673 2 : s% species = 0
674 2 : s% num_reactions = 0
675 :
676 2 : s% model_number = 0
677 2 : s% mstar = 0
678 2 : s% xmstar = 0
679 2 : s% M_center = 0
680 2 : s% v_center = 0
681 2 : s% R_center = 0
682 2 : s% L_center = 0
683 2 : s% time = 0
684 2 : s% total_angular_momentum = 0
685 :
686 2 : s% dt = 0
687 :
688 2 : s% have_previous_conv_vel = .false.
689 :
690 2 : s% net_name = ''
691 :
692 2 : s% mstar_dot = 0
693 2 : s% v_surf = 0
694 2 : s% L_nuc_burn_total = 0
695 50 : s% L_by_category = 0
696 2 : s% dt_limit_ratio = 0
697 2 : s% L_phot = 0
698 2 : s% T_surf = 0
699 2 : s% P_surf = 0
700 :
701 2 : s% gradT_excess_alpha = 0
702 2 : s% gradT_excess_alpha_old = 0
703 :
704 2 : s% h1_czb_mass = 0
705 :
706 2 : s% he_core_mass = 0
707 2 : s% co_core_mass = 0
708 2 : s% Teff = -1 ! need to calculate it
709 2 : s% center_eps_nuc = 0
710 2 : s% Lrad_div_Ledd_avg_surf = 0
711 2 : s% w_div_w_crit_avg_surf = 0
712 2 : s% total_internal_energy = 0d0
713 2 : s% total_gravitational_energy = 0d0
714 2 : s% total_radial_kinetic_energy = 0d0
715 2 : s% total_turbulent_energy = 0d0
716 2 : s% total_rotational_kinetic_energy = 0d0
717 2 : s% total_energy = 0d0
718 :
719 2 : s% n_conv_regions = 0
720 202 : s% cz_bot_mass(:) = 0
721 202 : s% cz_top_mass(:) = 0
722 2 : s% dt_next = 0
723 :
724 2 : s% model_profile_filename = ''
725 2 : s% model_controls_filename = ''
726 2 : s% model_data_filename = ''
727 :
728 2 : s% most_recent_profile_filename = ''
729 2 : s% most_recent_controls_filename = ''
730 :
731 2 : s% most_recent_model_data_filename = ''
732 :
733 2 : s% recent_log_header = -1000
734 2 : s% phase_of_evolution = 0
735 :
736 2 : s% num_solver_iterations = 0
737 2 : s% num_skipped_setvars = 0
738 2 : s% num_setvars = 0
739 2 : s% num_retries = 0
740 :
741 2 : s% num_hydro_merges = 0
742 2 : s% num_hydro_splits = 0
743 :
744 2 : s% timestep_hold = 0
745 2 : s% model_number_for_last_retry = 0
746 :
747 2 : s% mesh_call_number = 0
748 2 : s% solver_call_number = 0
749 2 : s% diffusion_call_number = 0
750 :
751 2 : s% num_rotation_solver_steps = 0
752 2 : s% num_diffusion_solver_steps = 0
753 2 : s% initial_timestep = 0
754 2 : s% why_Tlim = 0
755 2 : s% result_reason = 0
756 :
757 2 : s% have_new_generation = .false.
758 2 : s% have_new_cz_bdy_info = .false.
759 2 : s% need_to_update_history_now = .false.
760 2 : s% need_to_save_profiles_now = .false.
761 2 : s% save_profiles_model_priority = 0
762 :
763 2 : s% doing_flash_wind = .false.
764 2 : s% doing_rlo_wind = .false.
765 2 : s% most_recent_photo_name = ''
766 :
767 2 : s% len_extra_iwork = 0
768 2 : s% len_extra_work = 0
769 :
770 2 : s% crystal_core_boundary_mass = -1
771 2 : s% phase_sep_mixing_mass = -1
772 :
773 2 : call init_random(s)
774 :
775 2 : end subroutine set_starting_star_data
776 :
777 :
778 0 : subroutine create_pre_ms_model(id, ierr)
779 : integer, intent(in) :: id
780 : integer, intent(out) :: ierr
781 : character (len=0) :: model_dir
782 : call model_builder( &
783 : id, model_dir, do_create_pre_ms_model, &
784 0 : .false., 'restart_photo', ierr)
785 2 : end subroutine create_pre_ms_model
786 :
787 :
788 0 : subroutine create_initial_model(id, ierr)
789 : integer, intent(in) :: id
790 : integer, intent(out) :: ierr
791 : character (len=0) :: model_dir
792 : call model_builder( &
793 : id, model_dir, do_create_initial_model, &
794 0 : .false., 'restart_photo', ierr)
795 0 : end subroutine create_initial_model
796 :
797 :
798 0 : subroutine create_RSP_model(id, ierr)
799 : integer, intent(in) :: id
800 : integer, intent(out) :: ierr
801 : character (len=0) :: model_dir
802 : call model_builder( &
803 : id, model_dir, do_create_RSP_model, &
804 0 : .false., 'restart_photo', ierr)
805 0 : end subroutine create_RSP_model
806 :
807 :
808 0 : subroutine create_RSP2_model(id, ierr)
809 : integer, intent(in) :: id
810 : integer, intent(out) :: ierr
811 : character (len=0) :: model_dir
812 : call model_builder( &
813 : id, model_dir, do_create_RSP2_model, &
814 0 : .false., 'restart_photo', ierr)
815 0 : end subroutine create_RSP2_model
816 :
817 :
818 1 : subroutine load_zams_model(id, ierr)
819 : integer, intent(in) :: id
820 : integer, intent(out) :: ierr
821 : call model_builder( &
822 : id, '', do_load_zams_model, &
823 1 : .false., 'restart_photo', ierr)
824 1 : end subroutine load_zams_model
825 :
826 :
827 0 : subroutine load_saved_model(id, model_fname, ierr)
828 : integer, intent(in) :: id
829 : character (len=*), intent(in) :: model_fname
830 : integer, intent(out) :: ierr
831 : integer :: l
832 : l = len_trim(model_fname)
833 : call model_builder( &
834 : id, model_fname, do_load_saved_model, &
835 0 : .false., 'restart_photo', ierr)
836 0 : end subroutine load_saved_model
837 :
838 :
839 0 : subroutine load_restart_photo(id, restart_filename, ierr)
840 : integer, intent(in) :: id
841 : character (len=*), intent(in) :: restart_filename
842 : integer, intent(out) :: ierr
843 : call model_builder( &
844 0 : id, '', do_load_zams_model, .true., restart_filename, ierr)
845 0 : end subroutine load_restart_photo
846 :
847 :
848 : ! for both zams and pre-main-sequence
849 1 : subroutine model_builder( &
850 : id, model_info, do_which, restart, restart_filename, ierr)
851 : use net, only: set_net, do_micro_change_net
852 : use alloc, only: set_var_info
853 : use photo_in, only: read_star_photo
854 : use init_model, only: get_zams_model
855 : use star_utils, only: set_phase_of_evolution, yrs_for_init_timestep, &
856 : eval_deltaM_total_energy_integrals
857 : use adjust_xyz, only: set_z, set_y
858 : use pre_ms_model, only: build_pre_ms_model
859 : use create_initial_model, only: build_initial_model
860 : use rsp, only: build_rsp_model, rsp_total_energy_integrals
861 : use rsp_def, only: init_def
862 : use read_model, only: do_read_saved_model, &
863 : finish_load_model
864 : use relax, only: do_relax_to_limit, do_relax_mass, &
865 : do_relax_mass_scale, do_relax_num_steps, do_relax_to_radiative_core
866 : use auto_diff_support
867 : integer, intent(in) :: id, do_which
868 : character (len=*), intent(in) :: model_info, restart_filename
869 : logical, intent(in) :: restart
870 : integer, intent(out) :: ierr
871 :
872 : type (star_info), pointer :: s
873 1 : real(dp) :: initial_mass, initial_z
874 : real(dp), parameter :: lg_max_abs_mdot = -1000 ! use default
875 : real(dp), parameter :: change_mass_years_for_dt = 1
876 : real(dp), parameter :: min_mass_for_create_pre_ms = 0.03d0
877 1 : real(dp) :: total_radiation, warning_limit_for_max_residual
878 : integer :: k, num_trace_history_values
879 1 : real(dp) :: save_Pextra_factor
880 : character (len=256):: save_atm_option, &
881 : save_atm_T_tau_relation, save_atm_T_tau_opacity
882 1 : real(dp), allocatable, dimension(:) :: total_energy_profile
883 :
884 : include 'formats'
885 :
886 : ierr = 0
887 :
888 1 : call get_star_ptr(id, s, ierr)
889 1 : if (ierr /= 0) return
890 :
891 1 : initial_mass = s% initial_mass
892 1 : initial_z = s% initial_z
893 :
894 1 : if (s% initial_y < 0) s% initial_y = max(0d0, min(1d0, 0.24d0 + 2*initial_z))
895 :
896 1 : s% dt = 0
897 1 : s% termination_code = -1
898 :
899 1 : if (restart) then
900 0 : s% doing_first_model_of_run = .false.
901 0 : s% doing_first_model_after_restart = .true.
902 0 : call read_star_photo(s, restart_filename, ierr)
903 0 : if (ierr /= 0) return
904 0 : call check_initials
905 0 : call set_net(s, s% net_name, ierr)
906 0 : if (ierr /= 0) return
907 0 : if (s% rotation_flag) s% have_j_rot = .true.
908 0 : call init_def(s) ! RSP
909 0 : call finish_load_model(s, restart, ierr)
910 0 : if (s% max_years_for_timestep > 0) &
911 0 : s% dt_next = min(s% dt_next, secyer*s% max_years_for_timestep)
912 0 : return
913 : end if
914 :
915 1 : num_trace_history_values = s% num_trace_history_values
916 1 : s% num_trace_history_values = 0
917 :
918 1 : warning_limit_for_max_residual = s% warning_limit_for_max_residual
919 1 : s% warning_limit_for_max_residual = 1d0
920 :
921 1 : s% doing_first_model_of_run = .true.
922 1 : s% doing_first_model_after_restart = .false.
923 :
924 1 : if (do_which == do_load_saved_model) then
925 0 : s% dt_next = -1
926 0 : call do_read_saved_model(s, model_info, ierr)
927 0 : if (ierr /= 0) then
928 0 : write(*,*) 'load failed in do_read_saved_model'
929 0 : return
930 : end if
931 0 : call check_initials
932 0 : if (s% dt_next < 0) s% dt_next = yrs_for_init_timestep(s)*secyer
933 : else
934 1 : s% net_name = s% default_net_name
935 1 : s% species = 0
936 1 : s% v_flag = .false.
937 1 : s% u_flag = .false.
938 1 : s% rotation_flag = .false.
939 1 : s% D_omega_flag = .false.
940 1 : s% am_nu_rot_flag = .false.
941 1 : s% star_mass = s% initial_mass
942 1 : s% mstar = s% initial_mass*Msun
943 1 : s% M_center = s% mstar - s% xmstar
944 1 : call set_var_info(s, ierr)
945 1 : if (ierr /= 0) then
946 0 : write(*,*) 'failed in set_var_info'
947 0 : return
948 : end if
949 0 : select case (do_which)
950 : case (do_create_initial_model)
951 0 : if (s% initial_model_change_net) then
952 0 : call do_micro_change_net(s, s% initial_model_new_net_name, ierr)
953 : else
954 0 : call set_net(s, s% net_name, ierr)
955 : end if
956 0 : if (ierr /= 0) then
957 0 : write(*,*) 'failed in set_net'
958 0 : return
959 : end if
960 0 : call build_initial_model(s, ierr)
961 0 : if (ierr /= 0) then
962 0 : write(*,*) 'failed in build_initial_model'
963 0 : return
964 : end if
965 0 : s% generations = 1
966 0 : s% dt_next = 1d-5*secyer
967 : case (do_create_pre_ms_model)
968 0 : if (s% initial_mass < min_mass_for_create_pre_ms) then
969 0 : write(*,'(A)')
970 0 : write(*,'(A)')
971 0 : write(*,'(A)')
972 0 : write(*,'(a,1x,f5.2)') 'sorry: cannot create pre-ms smaller than', &
973 0 : min_mass_for_create_pre_ms
974 : write(*,'(a)') &
975 0 : 'please create pre-ms and then relax to lower mass as a separate operation'
976 0 : write(*,'(A)')
977 0 : write(*,'(a)') 'here is an example:'
978 0 : write(*,'(a)') 'in your inlist &controls section, set initial_mass = 0.03'
979 0 : write(*,'(a)') 'in the &star_job section, add something like these lines'
980 0 : write(*,'(a)') ' relax_mass_scale = .true.'
981 0 : write(*,'(a)') ' dlgm_per_step = 1d-3 ! log10(delta M/Msun/step)'
982 0 : write(*,'(a)') ' new_mass = 2.863362d-3 ! 3 Mjupiter in Msun units'
983 0 : write(*,'(a)') ' change_mass_years_for_dt = 1'
984 0 : write(*,'(A)')
985 0 : write(*,'(A)')
986 0 : write(*,'(A)')
987 0 : ierr = -1
988 0 : return
989 : end if
990 0 : if (s% pre_ms_change_net) then
991 0 : call do_micro_change_net(s, s% pre_ms_new_net_name, ierr)
992 : else
993 0 : call set_net(s, s% net_name, ierr)
994 : end if
995 0 : if (ierr /= 0) then
996 0 : write(*,*) 'failed in set_net'
997 0 : return
998 : end if
999 0 : write(*,2) 'species mass', s% species, s% mstar/Msun
1000 :
1001 0 : call build_pre_ms_model(id, s, s% nvar_hydro, s% species, ierr)
1002 0 : if (ierr /= 0) then
1003 0 : write(*,*) 'failed in build_pre_ms_model'
1004 0 : return
1005 : end if
1006 0 : s% generations = 1
1007 0 : s% dt_next = 1d-5*secyer
1008 : case (do_load_zams_model)
1009 1 : s% generations = 1
1010 1 : call get_zams_model(s, s% zams_filename, ierr)
1011 1 : if (ierr /= 0) then
1012 0 : write(*,*) 'failed in get_zams_model'
1013 0 : return
1014 : end if
1015 1 : if (s% dt_next <= 0d0) then
1016 1 : s% dt_next = yrs_for_init_timestep(s)*secyer
1017 : end if
1018 : case (do_create_RSP_model)
1019 0 : call build_rsp_model(s, ierr) ! like build_pre_ms_model
1020 0 : if (ierr /= 0) then
1021 0 : write(*,*) 'failed in build_rsp_model'
1022 0 : return
1023 : end if
1024 0 : s% generations = 1
1025 0 : s% dt_next = 1d-2*secyer
1026 : case (do_create_RSP2_model)
1027 : !call build_rsp2_model(s, ierr) ! like build_pre_ms_model
1028 0 : call mesa_error(__FILE__,__LINE__,'need to add build_rsp2_model')
1029 0 : if (ierr /= 0) then
1030 0 : write(*,*) 'failed in build_rsp2_model'
1031 0 : return
1032 : end if
1033 0 : s% generations = 1
1034 0 : s% dt_next = 1d-2*secyer
1035 : case default
1036 0 : write(*,*) 'bad value for do_which in build_model'
1037 0 : ierr = -1
1038 1 : return
1039 : end select
1040 : end if
1041 :
1042 2465 : do k=1,s% nz
1043 2465 : s% extra_heat(k) = 0
1044 : end do
1045 :
1046 1 : call finish_load_model(s, restart, ierr)
1047 1 : if (ierr /= 0) then
1048 0 : write(*,*) 'failed in finish_load_model'
1049 0 : return
1050 : end if
1051 :
1052 1 : if (s% max_years_for_timestep > 0) &
1053 0 : s% dt_next = min(s% dt_next, secyer*s% max_years_for_timestep)
1054 1 : call set_phase_of_evolution(s)
1055 :
1056 1 : if (s% RSP_flag) then
1057 : call rsp_total_energy_integrals(s, &
1058 : s% total_internal_energy, &
1059 : s% total_gravitational_energy, &
1060 : s% total_radial_kinetic_energy, &
1061 : s% total_rotational_kinetic_energy, &
1062 : s% total_turbulent_energy, &
1063 0 : s% total_energy, total_radiation)
1064 : else
1065 1 : allocate(total_energy_profile(1:s% nz))
1066 : call eval_deltaM_total_energy_integrals( &
1067 : s, 1, s% nz, s% mstar, .false., &
1068 : total_energy_profile, &
1069 : s% total_internal_energy, &
1070 : s% total_gravitational_energy, &
1071 : s% total_radial_kinetic_energy, &
1072 : s% total_rotational_kinetic_energy, &
1073 : s% total_turbulent_energy, &
1074 1 : s% total_energy)
1075 : end if
1076 :
1077 1 : if (do_which == do_create_pre_ms_model) then
1078 0 : call setup_for_relax_after_create_pre_ms_model
1079 0 : if (s% mstar > s% initial_mass*Msun) then ! need to reduce mass
1080 0 : write(*,1) 'reduce mass to', s% initial_mass
1081 0 : call do_relax_mass(s% id, s% initial_mass, lg_max_abs_mdot, ierr)
1082 0 : if (ierr /= 0) then
1083 0 : write(*,*) 'failed in do_relax_mass'
1084 0 : return
1085 : end if
1086 0 : else if (s% mstar < s% initial_mass*Msun) then ! need to increase mass
1087 0 : write(*,1) 'increase mass to', s% initial_mass
1088 : call do_relax_mass_scale( &
1089 0 : s% id, s% initial_mass, s% job% dlgm_per_step, s% job% change_mass_years_for_dt, ierr)
1090 0 : if (ierr /= 0) then
1091 0 : write(*,*) 'failed in do_relax_mass'
1092 0 : return
1093 : end if
1094 : end if
1095 : call do_relax_num_steps( &
1096 0 : s% id, s% pre_ms_relax_num_steps, s% dt_next, ierr)
1097 0 : if (ierr /= 0) then
1098 0 : write(*,*) 'failed in do_relax_num_steps'
1099 0 : return
1100 : end if
1101 :
1102 0 : if (s% job% pre_ms_relax_to_start_radiative_core) then
1103 0 : call do_relax_to_radiative_core(s% id, ierr)
1104 0 : if (ierr /= 0) then
1105 0 : write(*,*) 'failed in do_relax_to_radiative_core'
1106 0 : return
1107 : end if
1108 : end if
1109 0 : call done_relax_after_create_pre_ms_model
1110 1 : else if (do_which == do_create_initial_model .and. &
1111 : s% initial_model_relax_num_steps > 0) then
1112 : call do_relax_num_steps( &
1113 0 : s% id, s% initial_model_relax_num_steps, s% dt_next, ierr)
1114 0 : if (ierr /= 0) then
1115 0 : write(*,*) 'failed in do_relax_num_steps'
1116 0 : return
1117 : end if
1118 : end if
1119 :
1120 1 : s% doing_first_model_of_run = .true.
1121 1 : s% num_trace_history_values = num_trace_history_values
1122 1 : s% warning_limit_for_max_residual = warning_limit_for_max_residual
1123 :
1124 : contains
1125 :
1126 0 : subroutine setup_for_relax_after_create_pre_ms_model
1127 0 : save_atm_option = s% atm_option
1128 0 : save_atm_T_tau_relation = s% atm_T_tau_relation
1129 0 : save_atm_T_tau_opacity = s% atm_T_tau_opacity
1130 0 : save_Pextra_factor = s% Pextra_factor
1131 0 : s% atm_option = 'T_tau'
1132 0 : s% atm_T_tau_relation = 'Eddington'
1133 0 : s% atm_T_tau_opacity = 'fixed'
1134 0 : s% Pextra_factor = 2
1135 1 : end subroutine setup_for_relax_after_create_pre_ms_model
1136 :
1137 0 : subroutine done_relax_after_create_pre_ms_model
1138 0 : s% atm_option = save_atm_option
1139 0 : s% atm_T_tau_relation = save_atm_T_tau_relation
1140 0 : s% atm_T_tau_opacity = save_atm_T_tau_opacity
1141 0 : s% Pextra_factor = save_Pextra_factor
1142 0 : end subroutine done_relax_after_create_pre_ms_model
1143 :
1144 0 : subroutine check_initials
1145 : include 'formats'
1146 : if (abs(initial_mass - s% initial_mass) > &
1147 0 : 1d-3*initial_mass .and. initial_mass > 0) then
1148 0 : write(*,1) "WARNING -- inlist initial_mass ignored", initial_mass
1149 0 : write(*,1) "using saved initial_mass instead", s% initial_mass
1150 0 : write(*,'(A)')
1151 : end if
1152 : if (abs(initial_z - s% initial_z) > &
1153 0 : 1d-3*initial_z .and. initial_z > 0) then
1154 0 : write(*,1) "WARNING -- inlist initial_z ignored", initial_z
1155 0 : write(*,1) "using saved initial_z instead", s% initial_z
1156 0 : write(*,'(A)')
1157 : end if
1158 0 : end subroutine check_initials
1159 :
1160 : end subroutine model_builder
1161 :
1162 :
1163 1 : logical function doing_restart(restart_filename)
1164 : character (len=*) :: restart_filename
1165 1 : inquire(file=restart_filename, exist=doing_restart)
1166 1 : end function doing_restart
1167 :
1168 :
1169 0 : integer function null_how_many_extra_header_items(id)
1170 : integer, intent(in) :: id
1171 0 : null_how_many_extra_header_items = 0
1172 0 : end function null_how_many_extra_header_items
1173 :
1174 :
1175 0 : subroutine null_data_for_extra_header_items(id, n, names, vals, ierr)
1176 : integer, intent(in) :: id, n
1177 : character (len=80) :: names(n)
1178 : real(dp) :: vals(n)
1179 : integer, intent(out) :: ierr
1180 0 : ierr = 0
1181 0 : end subroutine null_data_for_extra_header_items
1182 :
1183 :
1184 0 : integer function null_how_many_binary_history_columns(binary_id)
1185 : integer, intent(in) :: binary_id
1186 0 : null_how_many_binary_history_columns = 0
1187 0 : end function null_how_many_binary_history_columns
1188 :
1189 :
1190 0 : subroutine null_data_for_binary_history_columns( &
1191 : binary_id, n, names, vals, ierr)
1192 : use const_def, only: dp
1193 : integer, intent(in) :: binary_id, n
1194 : character (len=80) :: names(n)
1195 : real(dp) :: vals(n)
1196 : integer, intent(out) :: ierr
1197 0 : ierr = 0
1198 0 : end subroutine null_data_for_binary_history_columns
1199 :
1200 :
1201 0 : integer function null_how_many_extra_binary_history_columns(binary_id)
1202 : integer, intent(in) :: binary_id
1203 0 : null_how_many_extra_binary_history_columns = 0
1204 0 : end function null_how_many_extra_binary_history_columns
1205 :
1206 :
1207 0 : subroutine null_data_for_extra_binary_history_columns( &
1208 : binary_id, n, names, vals, ierr)
1209 : use const_def, only: dp
1210 : integer, intent(in) :: binary_id, n
1211 : character (len=80) :: names(n)
1212 : real(dp) :: vals(n)
1213 : integer, intent(out) :: ierr
1214 0 : ierr = 0
1215 0 : end subroutine null_data_for_extra_binary_history_columns
1216 :
1217 :
1218 0 : subroutine do_garbage_collection(eosDT_cache_dir, ierr)
1219 : use eos_lib, only: eos_init, eos_shutdown
1220 : use eos_def, only: use_cache_for_eos
1221 : integer, intent(inout) :: ierr
1222 : character (len=*), intent(in) :: eosDT_cache_dir
1223 : ! Remove existing eos data
1224 0 : call eos_shutdown()
1225 : ! Re-initialize eos
1226 : call eos_init(eosDT_cache_dir,&
1227 : ! After first init this is set in eos_def
1228 : use_cache_for_eos,&
1229 0 : ierr)
1230 0 : end subroutine do_garbage_collection
1231 :
1232 : end module init
|