hdf5_module.f90
Go to the documentation of this file.
1 !> @file hdf5_module.f90
2 !! The error file code for this file is ***W24***.
3 !! Contains the module \ref hdf5_module.
4 
5 !> @brief Module that contains necessary subroutines to write
6 !! abundances to an hdf5 file.
7 !!
8 !! It is only included when the compilerflag "USE_HDF5" is set.
9 !! For more information about the hdf5 format
10 !! see [What is HDF5?](https://support.hdfgroup.org/HDF5/doc/H5.intro.html).
11 !! There is a tradeoff between having the data in the memory
12 !! and making an IO operation. Therefore, each output is first stored in a
13 !! temporary array of a specific size (or chunksize)
14 !! to prevent too much IO going on.
15 !!
16 !! @remark It is recommended, that the chunk sizes should
17 !! be around the size of 1MB, however, here are written many 1d real(double)
18 !! arrays and 1MB would be way more than storing the whole simulation temporary.
19 !! Therefore the chunk sizes are smaller (in the order of a couple of hundreds).
20 !!
21 !! @author Moritz Reichert
22 !! @date 28.01.21
23 #include "macros.h"
25 ! Only include the module with correct compiler
26 ! Note that this is bad practice as it makes the tests
27 ! more difficult, but it has the advantage that the code can still
28 ! work even when no hdf5 is installed and used.
29 #ifdef USE_HDF5
30 
31  use hdf5
32  use error_msg_class
33  use global_class, only: net_size
34  implicit none
35 
36  ! File related variables
37  integer(HID_T),private :: file_id !< File identifier
38  character(len=20),private :: hdf5_filename="WinNet_data.h5" !< Name of the hdf5 file
39 
40  ! Flag that indicates if there will be an hdf5 output
41  logical,private :: hdf5_output=.false.
42 
43  character(LEN=*), parameter,private :: dsetname_u = "Units" !< Name of the units dataset
44 
45  ! General helper variables
46  integer(HSIZE_T), dimension(1),private :: dims_1d=(/1/) !< Helper variable to specify 1 dimension
47  integer(HID_T),private :: dataspace !< Dataspace identifier
48  integer(HID_T),private :: crp_list !< Dataset creation property identifier
49  integer(HSIZE_T), dimension(1:2),private :: maxdims !< Maximum dimensions (later set to unlimited)
50 
51 
52  !-------- Snapshots variables -------------!
53  INTEGER(HID_T),private :: snaps_group_id !< The ID of the group
54  integer,private :: iter_snaps = 0 !< Iteration count,
55  !< how often was already
56  !< extended to the datasets?
57  integer,private :: chunk_counter_snaps = 0 !< How full is the chunk already?
58  integer,parameter,private :: chunk_size_snaps=200 !< Chunk size
59  real(r_kind),private,dimension(chunk_size_snaps) :: chunk_store_snaps_time !< Storage for the
60  !< chunk which is later
61  !< written to the file.
62  real(r_kind),private,dimension(:,:),allocatable :: chunk_store_snaps_y !< Storage for the
63  !< chunk which is later
64  !< written to the file.
65 
66  ! Abundances
67  integer(HID_T),private :: dset_id_y !< Dataset identifier
68  character(len=*), parameter,private :: dsetname_y = "Y" !< Name of the dataset
69  integer(HSIZE_T), dimension(1:2),private :: dims_y !< Array dimensions (net_size)
70  ! Time
71  character(len=*), parameter,private :: snaps_dsetname_t = "time" !< Name of the dataset
72  integer(HID_T),private :: snaps_dset_id_t !< Dataset identifier
73 
74 
75  !---------- Mainout variables -------------!
76  INTEGER(HID_T),private :: mainout_group_id !< The ID of the group
77  integer,private :: iter_mainout = 0 !< Iteration count,
78  !< how often was already
79  !< extended to the datasets?
80  integer,private :: chunk_counter_mainout = 0 !< How full is the chunk already?
81  integer,parameter,private :: chunk_size_mainout=500 !< Chunk size
82  real(r_kind),private,dimension(chunk_size_mainout,13) :: chunk_store_mainout !< Storage for the
83  !< chunk which is later
84  !< written to the file.
85  integer,private,dimension(chunk_size_mainout) :: chunk_store_int_mainout !< Storage for integers in chunk
86  !< which is later
87  !< written to the file.
88  ! Iteration
89  character(len=*), parameter,private :: mainout_dsetname_iter = "iteration" !< Name of the dataset
90  integer(HID_T),private :: mainout_dset_id_iter !< Dataset identifier
91  ! Time
92  character(len=*), parameter,private :: mainout_dsetname_t = "time" !< Name of the dataset
93  integer(HID_T),private :: mainout_dset_id_t !< Dataset identifier
94  ! Temperature
95  character(len=*), parameter,private :: mainout_dsetname_temp = "temp" !< Name of the dataset
96  integer(HID_T),private :: mainout_dset_id_temp !< Dataset identifier
97  ! Density
98  character(len=*), parameter,private :: mainout_dsetname_dens = "dens" !< Name of the dataset
99  integer(HID_T),private :: mainout_dset_id_dens !< Dataset identifier
100  ! Entropy
101  character(len=*), parameter,private :: mainout_dsetname_entr = "entr" !< Name of the dataset
102  integer(HID_T),private :: mainout_dset_id_entr !< Dataset identifier
103  ! Radius
104  character(len=*), parameter,private :: mainout_dsetname_rad = "rad" !< Name of the dataset
105  integer(HID_T),private :: mainout_dset_id_rad !< Dataset identifier
106  ! Electron fraction
107  character(len=*), parameter,private :: mainout_dsetname_ye = "ye" !< Name of the dataset
108  integer(HID_T),private :: mainout_dset_id_ye !< Dataset identifier
109  ! Neutron abundance
110  character(len=*), parameter,private :: mainout_dsetname_yn = "yn" !< Name of the dataset
111  integer(HID_T),private :: mainout_dset_id_yn !< Dataset identifier
112  ! Proton abundance
113  character(len=*), parameter,private :: mainout_dsetname_yp = "yp" !< Name of the dataset
114  integer(HID_T),private :: mainout_dset_id_yp !< Dataset identifier
115  ! Alpha abundance
116  character(len=*), parameter,private :: mainout_dsetname_ya = "ya" !< Name of the dataset
117  integer(HID_T),private :: mainout_dset_id_ya !< Dataset identifier
118  ! Ylight
119  character(len=*), parameter,private :: mainout_dsetname_ylight = "ylight" !< Name of the dataset
120  integer(HID_T),private :: mainout_dset_id_ylight !< Dataset identifier
121  ! Yheavy
122  character(len=*), parameter,private :: mainout_dsetname_yheavy = "yheavy" !< Name of the dataset
123  integer(HID_T),private :: mainout_dset_id_yheavy !< Dataset identifier
124  ! abar
125  character(len=*), parameter,private :: mainout_dsetname_abar = "abar" !< Name of the dataset
126  integer(HID_T),private :: mainout_dset_id_abar !< Dataset identifier
127  ! zbar
128  character(len=*), parameter,private :: mainout_dsetname_zbar = "zbar" !< Name of the dataset
129  integer(HID_T),private :: mainout_dset_id_zbar !< Dataset identifier
130 
131 
132  !---------- Track nuclei variables -------------!
133  INTEGER(HID_T),private :: track_group_id !< The ID of the group
134  integer,private :: iter_tracked = 0 !< Iteration count,
135  !< how often was already
136  !< extended to the datasets?
137  integer,private :: chunk_counter_track = 0 !< How full is the chunk already?
138  integer,parameter,private :: chunk_size_track=500 !< Chunk size
139  real(r_kind),private,dimension(:,:),allocatable :: chunk_store_track !< Temporary storage for
140  !< tracked nuclei
141 
142  ! Time
143  character(len=*), parameter,private :: tracked_dsetname_t = "time" !< Name of the dataset
144  integer(HID_T),private :: tracked_dset_id_t !< Dataset identifier
145  ! Other
146  integer(HSIZE_T), dimension(1:2),private :: dims_track !< Array dimensions
147  character(len=5),dimension(:),allocatable, private :: tracked_names !< Names of the tracked nuclei
148  integer(HID_T), private :: tracked_abu_id !< Dataset identifier
149  character(len=*), parameter,private :: tracked_dsetname_y = "Y" !< Name of the dataset
150 
151  !---------- Timescale variables -------------!
152  integer(HID_T),private :: ts_group_id !< The ID of the group
153  integer,private :: iter_ts = 0 !< Iteration count,
154  !< how often was already
155  !< extended to the datasets?
156  integer,private :: chunk_counter_ts = 0 !< How full is the chunk already?
157  integer,parameter,private :: chunk_size_ts=500 !< Chunk size
158  real(r_kind),private,dimension(chunk_size_ts,18) :: chunk_store_ts !< Temporary storage for
159  !< average timescales
160 
161  ! Time
162  character(len=*), parameter,private :: ts_dsetname_t = "time" !< Name of the dataset
163  integer(HID_T),private :: ts_dset_id_t !< Dataset identifier
164  ! Other
165  character(len=9),dimension(17), private :: ts_names = &
166  (/"tau_ga ","tau_ag ","tau_ng ","tau_gn ","tau_pg ","tau_gp ","tau_np ",&
167  "tau_pn ","tau_an ","tau_na ","tau_ap ","tau_pa ","tau_beta ","tau_alpha", &
168  "tau_nfiss","tau_sfiss","tau_bfiss"/)
169  !< Names of the timescales
170  integer(HID_T),dimension(17), private :: ts_reac_ids !< Dataset identifier
171 
172 
173  !---------- Energy variables -------------!
174  integer(HID_T),private :: en_group_id !< The ID of the group
175  integer,private :: iter_en = 0 !< Iteration count,
176  !< how often was already
177  !< extended to the datasets?
178  integer,private :: chunk_counter_en = 0 !< How full is the chunk already?
179  integer,parameter,private :: chunk_size_en=500 !< Chunk size
180  real(r_kind),private,dimension(chunk_size_en,11) :: chunk_store_en !< Temporary storage for
181  !< energy generation
182  real(r_kind),private,dimension(:,:),allocatable :: & !< Storage for the chunk which is later written to the file.
187 
188  ! Time
189  character(len=*), parameter,private :: en_dsetname_t = "time" !< Name of the dataset
190  integer(HID_T),private :: en_dset_id_t !< Dataset identifier
191  ! Other
192  character(len=11),dimension(10), private :: en_names = &
193  (/"engen_tot ","S_src ","engen_ng_gn","engen_pg_gp","engen_ag_ga",&
194  "engen_np_pn","engen_an_na","engen_ap_pa","engen_beta ", &
195  "engen_fiss "/)
196  !< Name of the energy generations
197  integer(HID_T),dimension(10), private :: en_reac_ids !< Dataset identifier
198 
199  character(len=14), private :: & !< Name of the decay energy splitted by parent
200  en_det_bet_name="detailed decay", en_det_ag_name ="detailed (a,g)", en_det_pg_name="detailed (p,g)", &
201  en_det_ng_name ="detailed (n,g)", en_det_pn_name ="detailed (p,n)", en_det_ap_name="detailed (a,p)", &
202  en_det_an_name ="detailed (a,n)", en_det_other_name="detailed other", en_det_fiss_name="detailed fiss ", &
203  en_det_tot_name="detailed total"
204 
205  integer(HID_T), private :: & !< Dataset identifier
210 
211  !----------- Flow variables --------------!
212  integer(HID_T),private :: flow_group_id !< The ID of the group
213  integer,private :: iter_flow = 0 !< Iteration count,
214  !< how often was already
215  !< extended to the datasets?
216  ! Time
217  character(len=*), parameter,private :: flow_dsetname_t = "time" !< Name of the dataset
218  integer(HID_T),private :: flow_dset_id_t !< Dataset identifier
219 
220 
221  !----------- Nu gain/loss variables --------------!
222  integer(HID_T),private :: nuloss_group_id !< The ID of the group
223  integer,private :: iter_nuloss = 0 !< Iteration count,
224  !< how often was already
225  !< extended to the datasets?
226  integer,private :: chunk_counter_nuloss = 0 !< How full is the chunk already?
227  integer,parameter,private :: chunk_size_nuloss=500 !< Chunk size
228  real(r_kind),private,dimension(chunk_size_nuloss) :: chunk_store_nuloss_t, &
236 
237  ! Time
238  character(len=*), parameter,private :: nuloss_dsetname_t = "time" !< Name of the dataset
239  integer(HID_T),private :: nuloss_dset_id_t !< Dataset identifier
240  ! Temperature
241  character(len=*), parameter,private :: nuloss_dsetname_temp = "temp" !< Name of the dataset
242  integer(HID_T),private :: nuloss_dset_id_temp !< Dataset identifier
243  ! Density
244  character(len=*), parameter,private :: nuloss_dsetname_dens = "dens" !< Name of the dataset
245  integer(HID_T),private :: nuloss_dset_id_dens !< Dataset identifier
246  ! Radius
247  character(len=*), parameter,private :: nuloss_dsetname_rad = "rad" !< Name of the dataset
248  integer(HID_T),private :: nuloss_dset_id_rad !< Dataset identifier
249  ! nu loss total
250  character(len=*), parameter,private :: nuloss_dsetname_nut = "nu_total" !< Name of the dataset
251  integer(HID_T),private :: nuloss_dset_id_nut !< Dataset identifier
252  ! nu loss beta
253  character(len=*), parameter,private :: nuloss_dsetname_bet = "nu_beta" !< Name of the dataset
254  integer(HID_T),private :: nuloss_dset_id_bet !< Dataset identifier
255  ! nu loss thermal
256  character(len=*), parameter,private :: nuloss_dsetname_the = "nu_thermal" !< Name of the dataset
257  integer(HID_T),private :: nuloss_dset_id_the !< Dataset identifier
258  ! nu gain neutrino heating
259  character(len=*), parameter,private :: nuloss_dsetname_heat = "nu_heat" !< Name of the dataset
260  integer(HID_T),private :: nuloss_dset_id_heat !< Dataset identifier
261 
262 
263  !----------- Finab variables --------------!
264  integer(HID_T),private :: finab_group_id !< The ID of the group
265 
266 
267 
268  !
269  ! Public and private fields and methods of the module
270  !
271  public:: &
275  private:: &
282 
283 
284 contains
285 
286  !> @brief Initialize the hdf5 module
287  !!
288  !! Create the file and the datasets. Furthermore, initialize arrays.
289  !!
290  !! @author Moritz Reichert
291  !! @date 28.01.21
292  subroutine init_hdf5_module()
296 
297  implicit none
298  integer :: i_stat !< status variable
299 
300 
301  ! Check if a file has to get created
302  if ((h_snapshot_every .gt. 0) .or. (h_custom_snapshots) .or. &
303  (h_mainout_every .gt. 0) .or. (h_track_nuclei_every .gt. 0) .or. &
304  (h_timescales_every .gt. 0) .or. (h_flow_every .gt. 0) .or.&
305  (h_finab) .or. (h_engen_every .gt. 0) .or. &
306  ((h_nu_loss_every .gt. 0))) then
307  hdf5_output = .true.
308  end if
309  if (.not. hdf5_output) return
310 
311  !--- Create and initialize the file
312  !
313  ! Initialize FORTRAN predefined datatypes
314  call h5open_f(i_stat)
315 
316  if (i_stat .ne. 0) call raise_exception("Could not initialize fortran predefined datatypes",&
317  "init_hdf5_module",240003)
318 
319  ! Create a new file
320  call h5fcreate_f(hdf5_filename, h5f_acc_trunc_f, file_id, i_stat)
321  if (i_stat .ne. 0) then
322  call raise_exception("Could not open HDF5 file."//new_line("A")//&
323  "Close the file if you have opened it.",&
324  "init_hdf5_module",240004)
325  end if
326 
327  ! Snapshot things:
328  if ((h_snapshot_every .gt. 0) .or. (h_custom_snapshots)) then
329  call init_snaps
330  end if
331 
332  ! Mainout things:
333  if (h_mainout_every .gt. 0) then
334  call init_mainout
335  end if
336 
337  ! Open the track_nuclei file and write a header
338  if (h_track_nuclei_every .gt. 0) then
339  call init_track_nuclei
340  end if
341 
342  ! Store average timescales
343  if (h_timescales_every .gt. 0) then
344  call init_av_timescales
345  end if
346 
347  ! Initialize flow output
348  if (h_flow_every .gt. 0) then
349  call init_flow
350  end if
351 
352  if ((h_nu_loss_every .gt. 0)) then
353  call init_nu_loss_gain
354  end if
355 
356  ! Initialize flow output
357  if (h_engen_every .gt. 0) then
359  end if
360 
361  end subroutine init_hdf5_module
362 
363 
364 
365  !> Initialize the flow output
366  subroutine init_flow
367  implicit none
368  integer :: i_stat !< status variable
369 
370  ! Abundance dataset
371  ! Create a group for the snapshots
372  call h5gcreate_f(file_id, "/flows", flow_group_id, i_stat)
373  if (i_stat .ne. 0) then
374  call raise_exception("Unable to create flows group.",&
375  "init_flow",240005)
376  end if
377 
378  end subroutine init_flow
379 
380 
381  !> Initialize neutrino loss/gain output
382  subroutine init_nu_loss_gain
383  implicit none
384  ! Helper variables
385  integer :: i_stat !< status variable
386 
387  ! Create group
388  call h5gcreate_f(file_id, "/nu_loss_gain", nuloss_group_id, i_stat)
389  if (i_stat .ne. 0) then
390  call raise_exception("Unable to create nu_loss_gain group.",&
391  "init_nu_loss_gain",240005)
392  end if
393 
394  ! Also make space for the time and all other outputs
403 
404  end subroutine init_nu_loss_gain
405 
406  !>
407  !! Write neutrino gain and loss
408  !!
409  !! These values are stored in a separate group (called snapshots) that is initialized
410  !! in \ref init_hdf5_module.
411  !!
412  !! @author Moritz Reichert
413  !! @date 12.04.23
414  subroutine extend_nu_loss_gain(time,temp,dens,rad,the,heat,bet)
415  use global_class, only: net_size
416  implicit none
417  real(r_kind),intent(in) :: time !< Time [s]
418  real(r_kind),intent(in) :: temp !< Temperature [GK]
419  real(r_kind),intent(in) :: dens !< Density [g/cm^3]
420  real(r_kind),intent(in) :: rad !< Radius [km]
421  real(r_kind),intent(in) :: the !< Neutrino gain/loss thermal [MeV/baryon/s]
422  real(r_kind),intent(in) :: heat !< Neutrino gain/loss heating [MeV/baryon/s]
423  real(r_kind),intent(in) :: bet !< Neutrino gain/loss beta decay [MeV/baryon/s]
424  real(r_kind) :: nut !< Neutrino gain/loss total [MeV/baryon/s]
425  ! Total energy
426  nut = the + heat + bet
427  ! Store the time
437 
438  ! Write to the file
440  call write_nu_loss_gain()
441  end if
442  end subroutine extend_nu_loss_gain
443 
444 
445  !>
446  !! @brief Write the neutrino loss/gain into the hdf5 file
447  !!
448  !! These values are stored in a separate group (called nu_loss_gain) that is initialized
449  !! in \ref init_hdf5_module.
450  !!
451  !! @author Moritz Reichert
452  !! @date 12.04.23
454  implicit none
455  ! Helper variables
456 
457  if (chunk_counter_nuloss .lt. 1) return
458  ! Save the data
467 
470  end subroutine write_nu_loss_gain
471 
472 
473 
474 
475 
476  !> Initialize energy generation output
477  subroutine init_engen(include_decay)
478  use global_class, only: net_size,isotope
479  implicit none
480  logical,intent(in) :: include_decay !< Flag that determines if decay energy per parent is written
481  ! Helper variables
482  integer :: i_stat !< status variable
483  integer :: i !< Loop variable
484  logical :: avail
485  integer :: filter_info,filter_info_both
486  integer,dimension(net_size) :: helper !< Helper array to store A,Z,N
487 
488 
489  ! Create group
490  call h5gcreate_f(file_id, "/energy", en_group_id, i_stat)
491  if (i_stat .ne. 0) then
492  call raise_exception("Unable to create energies group.",&
493  "init_engen",240005)
494  end if
495  ! Store dataset Ids
496  do i=1, 10
497  en_reac_ids(i) = create_1d_dataset(trim(adjustl(en_names(i))),en_group_id)
498  end do
499 
500  ! Also make space for the time
502 
503  if (include_decay .eqv. .true.) then
504  ! Set the initial dimensions
505  dims_y(1:2) = (/net_size,1/)
506  ! Create the data space with unlimited dimensions.
507  maxdims = (/h5s_unlimited_f, h5s_unlimited_f/)
508  call h5screate_simple_f(2, dims_y, dataspace, i_stat, maxdims)
509  if (i_stat .ne. 0) then
510  call raise_exception("Unable to create necessary dataspace.",&
511  "init_engen",240006)
512  end if
513 
514 
515  ! Check if gzip compression is available and can be used for both
516  ! compression and decompression.
517  ! The compression can greatly reduce the used space as
518  ! The energy generation has many zeros included. In a small
519  ! test, the filesize got reduced by a factor of 10.
520  ! However, it consumes some time to compress whenever data is written...
521  CALL h5zfilter_avail_f(h5z_filter_deflate_f, avail, i_stat)
522 
523  if (.not. avail) then
524  call raise_exception("gzip filter not available.","init_engen",240008)
525  end if
526  call h5zget_filter_info_f(h5z_filter_deflate_f, filter_info, i_stat)
527 
528  filter_info_both=ior(h5z_filter_encode_enabled_f,h5z_filter_decode_enabled_f)
529  if (filter_info .ne. filter_info_both) then
530  call raise_exception("gzip filter not available for encoding and decoding.",&
531  "init_engen",240009)
532  endif
533 
534  ! Modify dataset properties
535  call h5pcreate_f(h5p_dataset_create_f, crp_list, i_stat)
536  if (i_stat .ne. 0) then
537  call raise_exception("Unable to modify dataset properties.",&
538  "init_engen",240010)
539  end if
540  ! Apply the gzip filter
541  call h5pset_deflate_f(crp_list, 9, i_stat)
542  if (i_stat .ne. 0) then
543  call raise_exception("Unable to deflate and apply gzip filter.",&
544  "init_engen",240011)
545  end if
546  ! Enable chunking
547  call h5pset_chunk_f(crp_list, 2, dims_y, i_stat)
548  if (i_stat .ne. 0) then
549  call raise_exception("Unable to enable chunking.",&
550  "init_engen",240012)
551  end if
552 
553  ! Create a dataset using cparms creation property
554  call h5dcreate_f(en_group_id, en_det_bet_name, h5t_native_double, dataspace, &
555  en_det_bet_id, i_stat, crp_list )
556  if (i_stat .ne. 0) then
557  call raise_exception("Unable to create dataspace (en_det_bet_id).",&
558  "init_engen",240006)
559  end if
560  call h5dcreate_f(en_group_id, en_det_ag_name, h5t_native_double, dataspace, &
561  en_det_ag_id, i_stat, crp_list )
562  if (i_stat .ne. 0) then
563  call raise_exception("Unable to create dataspace (en_det_ag_id).",&
564  "init_engen",240006)
565  end if
566  call h5dcreate_f(en_group_id, en_det_pg_name, h5t_native_double, dataspace, &
567  en_det_pg_id, i_stat, crp_list )
568  if (i_stat .ne. 0) then
569  call raise_exception("Unable to create dataspace (en_det_pg_id).",&
570  "init_engen",240006)
571  end if
572  call h5dcreate_f(en_group_id, en_det_ng_name, h5t_native_double, dataspace, &
573  en_det_ng_id, i_stat, crp_list )
574  if (i_stat .ne. 0) then
575  call raise_exception("Unable to create dataspace (en_det_ng_id).",&
576  "init_engen",240006)
577  end if
578  call h5dcreate_f(en_group_id, en_det_pn_name, h5t_native_double, dataspace, &
579  en_det_pn_id, i_stat, crp_list )
580  if (i_stat .ne. 0) then
581  call raise_exception("Unable to create dataspace (en_det_pn_id).",&
582  "init_engen",240006)
583  end if
584  call h5dcreate_f(en_group_id, en_det_ap_name, h5t_native_double, dataspace, &
585  en_det_ap_id, i_stat, crp_list )
586  if (i_stat .ne. 0) then
587  call raise_exception("Unable to create dataspace (en_det_ap_id).",&
588  "init_engen",240006)
589  end if
590  call h5dcreate_f(en_group_id, en_det_an_name, h5t_native_double, dataspace, &
591  en_det_an_id, i_stat, crp_list )
592  if (i_stat .ne. 0) then
593  call raise_exception("Unable to create dataspace (en_det_an_id).",&
594  "init_engen",240006)
595  end if
596  call h5dcreate_f(en_group_id, en_det_other_name, h5t_native_double, dataspace, &
597  en_det_other_id, i_stat, crp_list )
598  if (i_stat .ne. 0) then
599  call raise_exception("Unable to create dataspace (en_det_other_id).",&
600  "init_engen",240006)
601  end if
602  call h5dcreate_f(en_group_id, en_det_fiss_name, h5t_native_double, dataspace, &
603  en_det_fiss_id, i_stat, crp_list )
604  if (i_stat .ne. 0) then
605  call raise_exception("Unable to create dataspace (en_det_fiss_id).",&
606  "init_engen",240006)
607  end if
608  call h5dcreate_f(en_group_id, en_det_tot_name, h5t_native_double, dataspace, &
609  en_det_tot_id, i_stat, crp_list )
610  if (i_stat .ne. 0) then
611  call raise_exception("Unable to create dataspace (en_det_tot_id).",&
612  "init_engen",240006)
613  end if
614  call h5sclose_f(dataspace, i_stat) ! close the dataspace again
615  if (i_stat .ne. 0) then
616  call raise_exception("Unable to close the dataspace.",&
617  "init_engen",240007)
618  end if
619 
620  !--- Write constant information into the hdf5
621  ! Write A, Z, N into the hdf5
622  ! Necessary to identify nuclei in detailed output
623  do i=1,net_size
624  helper(i) = isotope(i)%mass
625  end do
627  ! Write Z into hdf5
628  do i=1,net_size
629  helper(i) = isotope(i)%p_nr
630  end do
632  ! Write N into hdf5
633  do i=1,net_size
634  helper(i) = isotope(i)%n_nr
635  end do
637 
638  ! Allocate the array to store the chunks in
644 
645  if (i_stat /= 0) call raise_exception('Allocation failed.',"init_engen",&
646  240001)
647  end if
648 
649  end subroutine init_engen
650 
651 
652  !>
653  !! @brief Subroutine to write the energy generation per reaction type
654  !!
655  !! @author Moritz Reichert
656  !! @date 22.03.21
657  subroutine extend_engen(time,engen_tot, heat,engen_ng_gn, engen_pg_gp, &
658  engen_ag_ga, engen_np_pn, engen_an_na, &
659  engen_ap_pa, engen_beta, engen_fiss, &
660  det_bet_engen, det_ag_engen, det_pg_engen, &
661  det_ng_engen, det_pn_engen, det_ap_engen, &
662  det_an_engen, det_other_engen, det_fiss_engen, &
663  det_tot_engen, &
664  include_decay)
665  use global_class, only: net_size
666  implicit none
667  real(r_kind),intent(in) :: time !< Time [s]
668  real(r_kind),intent(in) :: engen_tot, heat, engen_ng_gn, engen_pg_gp !< Energy generation [erg/g/s]
669  real(r_kind),intent(in) :: engen_ag_ga, engen_np_pn, engen_an_na !< Energy generation [erg/g/s]
670  real(r_kind),intent(in) :: engen_ap_pa, engen_beta, engen_fiss !< Energy generation [erg/g/s]
671  real(r_kind),dimension(net_size),intent(in) :: det_bet_engen
672  real(r_kind),dimension(net_size),intent(in) :: det_ag_engen
673  real(r_kind),dimension(net_size),intent(in) :: det_pg_engen
674  real(r_kind),dimension(net_size),intent(in) :: det_ng_engen
675  real(r_kind),dimension(net_size),intent(in) :: det_pn_engen
676  real(r_kind),dimension(net_size),intent(in) :: det_ap_engen
677  real(r_kind),dimension(net_size),intent(in) :: det_an_engen
678  real(r_kind),dimension(net_size),intent(in) :: det_other_engen
679  real(r_kind),dimension(net_size),intent(in) :: det_fiss_engen !< Energy generation [erg/g/s]
680  real(r_kind),dimension(net_size),intent(in) :: det_tot_engen !< Energy generation [erg/g/s]
681  logical,intent(in) :: include_decay !< Write engen_decay_parents?
682  !
683  integer :: i !< Loop variable
684 
685  ! Count how large the space has to be
687  !< Save the data temporary in an array
688  chunk_store_en(chunk_counter_en,:) = (/time,engen_tot, heat,engen_ng_gn, engen_pg_gp, &
689  engen_ag_ga, engen_np_pn, engen_an_na, &
690  engen_ap_pa, engen_beta, engen_fiss/)
691 
692  if (include_decay .eqv. .true.) then
693  ! Extend the decay energy generation splitted in parent nuclei
694  chunk_store_en_bet(:,chunk_counter_en) = det_bet_engen
695  chunk_store_en_ag(:,chunk_counter_en) = det_ag_engen
696  chunk_store_en_pg(:,chunk_counter_en) = det_pg_engen
697  chunk_store_en_ng(:,chunk_counter_en) = det_ng_engen
698  chunk_store_en_pn(:,chunk_counter_en) = det_pn_engen
699  chunk_store_en_ap(:,chunk_counter_en) = det_ap_engen
700  chunk_store_en_an(:,chunk_counter_en) = det_an_engen
701  chunk_store_en_other(:,chunk_counter_en)= det_other_engen
702  chunk_store_en_fiss(:,chunk_counter_en) = det_fiss_engen
703  chunk_store_en_tot(:,chunk_counter_en) = det_tot_engen
704  end if
705 
706  ! Write the chunk to the file
707  if (chunk_counter_en .eq. chunk_size_en) then
708  call write_engen(include_decay)
709  end if
710 
711  end subroutine extend_engen
712 
713  !>
714  !! @brief Write energy generations and time into the hdf5 file
715  !!
716  !! These values are stored in a separate group (called energy) that is initialized
717  !! in \ref init_hdf5_module.
718  !!
719  !! @author Moritz Reichert
720  !! @date 22.03.21
721  subroutine write_engen(include_decay)
722  use global_class, only: net_size
723  implicit none
724  logical, intent(in) :: include_decay !< Write engen_decay?
725  ! Helper variables
726  integer :: i !< Loop variable
727 
728  if (chunk_counter_en .lt. 1) return
729  ! Save the time
731  ! Save timescales
732  do i=1, 10
734  end do
735 
736  if (include_decay .eqv. .true.) then
737  ! Decay energy splitted into parent nuclei
748  end if
749 
751  chunk_counter_en = 0
752  end subroutine write_engen
753 
754 
755 
756 
757  !> Extend the flow in the file
758  !! With every call a new group is created and the flows are written in this
759  !! group. The group is named after the calls (the third call is then located
760  !! in flows/3)
761  subroutine extend_flow(time,temp,dens,flow,n_flows,Y)
763  implicit none
764  real(r_kind),intent(in) :: time !< Value of the time
765  real(r_kind),intent(in) :: temp !< Value of the time
766  real(r_kind),intent(in) :: dens !< Value of the time
767  integer, intent(in) :: n_flows !< Maximum number of flows
768  type(flow_vector),dimension(n_flows), intent(in) :: flow !< Array with already calculated flows
769  real(r_kind),dimension(net_size), intent(in) :: y !< Array with abundances
770  integer :: i !< Loop variable
771  integer :: count !< Amount of non zero flows
772  integer :: i_stat !< IO status variable
773  integer :: alloc_stat !< Allocation status variable
774  real(r_kind) :: flow_diff !< Value of the flow
775  integer,dimension(:),allocatable :: n_in_nr,p_in_nr !< Amount of ingoing neutrons and protons
776  integer,dimension(:),allocatable :: n_out_nr,p_out_nr!< Amount of outgoing neutrons and protons
777  real(r_kind),dimension(:),allocatable :: flow_in,flow_out !< In/Out-going flow
778  real(r_kind),dimension(:),allocatable :: y_in,y_out !< In/Out-going abundances
779  integer(HID_T) :: tmp_group_id !< Temporary group id of the flows
780  real(r_kind),dimension(1) :: helper_time !< Helper array to store the time
781  real(r_kind),dimension(1) :: helper_temp !< Helper array to store the temp
782  real(r_kind),dimension(1) :: helper_dens !< Helper array to store the dens
783 
784  iter_flow = iter_flow + 1 ! Count the amount of calls
785 
786  ! Initialize count variable
787  count = 0
788 
789  ! Loop over the flows and count non zero ones
790  do i=1,n_flows
791  flow_diff = flow(i)%fwd - flow(i)%bwd
792  ! Count non zero flows
793  if (flow_diff .ne. 0) count = count + 1
794  end do
795 
796  ! Allocate the arrays
797  allocate(n_out_nr(count),stat=alloc_stat)
798  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'n_out_nr' failed!","extend_flow",240001)
799  allocate(p_out_nr(count),stat=alloc_stat)
800  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'p_out_nr' failed!","extend_flow",240001)
801  allocate(flow_out(count),stat=alloc_stat)
802  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'flow_out' failed!","extend_flow",240001)
803  allocate( n_in_nr(count),stat=alloc_stat)
804  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'n_in_nr' failed!","extend_flow",240001)
805  allocate( p_in_nr(count),stat=alloc_stat)
806  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'p_in_nr' failed!","extend_flow",240001)
807  allocate( flow_in(count),stat=alloc_stat)
808  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'flow_in' failed!","extend_flow",240001)
809  allocate( y_in(count) ,stat=alloc_stat)
810  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'Y_in' failed!","extend_flow",240001)
811  allocate( y_out(count) ,stat=alloc_stat)
812  if (alloc_stat .ne. 0) call raise_exception("Allocation of 'Y_out' failed!","extend_flow",240001)
813 
814  ! Loop over the flows and fill the arrays with non zero flows
815  count = 0
816  do i=1,n_flows
817  flow_diff = flow(i)%fwd - flow(i)%bwd
818  ! Count non zero flows
819  if (flow_diff .eq. 0) cycle
820  count = count + 1
821  ! Store ingoing and outgoing quantities
822  n_in_nr(count) = isotope(flow(i)%iin)%n_nr
823  p_in_nr(count) = isotope(flow(i)%iin)%p_nr
824  n_out_nr(count) = isotope(flow(i)%iout)%n_nr
825  p_out_nr(count) = isotope(flow(i)%iout)%p_nr
826  flow_out(count) = flow(i)%bwd
827  flow_in(count) = flow(i)%fwd
828  y_in(count) = y(flow(i)%iin)
829  y_out(count) = y(flow(i)%iout)
830  end do
831  ! Store the time in form of an array with length 1
832  helper_time(1) = time
833  helper_temp(1) = temp
834  helper_dens(1) = dens
835 
836  ! Abundance dataset
837  ! Calculate net flow here and not in the argument of create_constant_1d_arrays
838  ! in order to avoid annoying warning message
839  flow_in(:) = flow_in(:) - flow_out(:)
840  ! Create a group for the snapshots
841  call h5gcreate_f(file_id, "/flows/"//int_to_str(iter_flow), tmp_group_id, i_stat)
842  call create_constant_1d_int_arrays(count,n_in_nr ,"n_in",tmp_group_id)
843  call create_constant_1d_int_arrays(count,p_in_nr ,"p_in",tmp_group_id)
844  call create_constant_1d_int_arrays(count,n_out_nr,"n_out",tmp_group_id)
845  call create_constant_1d_int_arrays(count,p_out_nr,"p_out",tmp_group_id)
846  call create_constant_1d_arrays(count,flow_in,"flow",tmp_group_id)
847  call create_constant_1d_arrays(1,helper_time,"time",tmp_group_id)
848  call create_constant_1d_arrays(1,helper_temp,"temp",tmp_group_id)
849  call create_constant_1d_arrays(1,helper_dens,"dens",tmp_group_id)
850  call create_constant_1d_arrays(count,y_in,"y_in",tmp_group_id)
851  call create_constant_1d_arrays(count,y_out,"y_out",tmp_group_id)
852  call h5gclose_f(tmp_group_id , i_stat)
853 
854 
855  ! Deallocate the arrays
856  deallocate(n_out_nr,stat=alloc_stat)
857  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'n_out_nr' failed!","extend_flow",240002)
858  deallocate(p_out_nr,stat=alloc_stat)
859  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'p_out_nr' failed!","extend_flow",240002)
860  deallocate(flow_out,stat=alloc_stat)
861  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'flow_out' failed!","extend_flow",240002)
862  deallocate( n_in_nr,stat=alloc_stat)
863  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'n_in_nr' failed!","extend_flow",240002)
864  deallocate( p_in_nr,stat=alloc_stat)
865  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'p_in_nr' failed!","extend_flow",240002)
866  deallocate( flow_in,stat=alloc_stat)
867  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'flow_in' failed!","extend_flow",240002)
868  deallocate(y_in ,stat=alloc_stat)
869  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'Y_in' failed!","extend_flow",240002)
870  deallocate(y_out,stat=alloc_stat)
871  if (alloc_stat .ne. 0) call raise_exception("Deallocation of 'Y_out' failed!","extend_flow",240002)
872 
873  end subroutine extend_flow
874 
875 
876  !> Initialize the snapshot hdf5 group.
877  !!
878  !! This subroutine creates a snapshot group and writes mass number
879  !! proton number and neutron number into it. Furthermore, it creates a dataspace
880  !! for the abundances and the time. In addition a array that stores
881  !! the abundances is initialized. This array is used to create larger chunks
882  !! and reduce the IO when writing to the file on the cost of memory usage.
883  subroutine init_snaps
884  use global_class, only: net_size,isotope
885  implicit none
886  integer :: i_stat !< status variable
887  integer :: i !< Loop variable
888  integer,dimension(net_size) :: helper !< Helper array to store A,Z,N
889  logical :: avail !< For gzip compression
890  integer :: filter_info,filter_info_both
891  ! Abundance dataset
892  ! Create a group for the snapshots
893  call h5gcreate_f(file_id, "/snapshots", snaps_group_id, i_stat)
894  if (i_stat .ne. 0) then
895  call raise_exception("Unable to create snapshot group.",&
896  "init_snaps",240005)
897  end if
898 
899  ! Set the initial dimensions
900  dims_y(1:2) = (/net_size,1/)
901  ! Create the data space with unlimited dimensions.
902  maxdims = (/h5s_unlimited_f, h5s_unlimited_f/)
903  call h5screate_simple_f(2, dims_y, dataspace, i_stat, maxdims)
904  if (i_stat .ne. 0) then
905  call raise_exception("Unable to create necessary dataspace.",&
906  "init_snaps",240006)
907  end if
908 
909  ! Check if gzip compression is available and can be used for both
910  ! compression and decompression.
911  call h5zfilter_avail_f(h5z_filter_deflate_f, avail, i_stat)
912 
913  if (.not. avail) then
914  call raise_exception("gzip filter not available.","init_snaps",240008)
915  end if
916  call h5zget_filter_info_f(h5z_filter_deflate_f, filter_info, i_stat)
917 
918  filter_info_both=ior(h5z_filter_encode_enabled_f,h5z_filter_decode_enabled_f)
919  if (filter_info .ne. filter_info_both) then
920  call raise_exception("gzip filter not available for encoding and decoding.","init_snaps",240009)
921  endif
922 
923  ! Modify dataset properties
924  call h5pcreate_f(h5p_dataset_create_f, crp_list, i_stat)
925  if (i_stat .ne. 0) then
926  call raise_exception("Unable to modify dataset properties.",&
927  "init_snaps",240010)
928  end if
929 
930  ! Apply the gzip filter
931  call h5pset_deflate_f(crp_list, 9, i_stat)
932  if (i_stat .ne. 0) then
933  call raise_exception("Unable to deflate and apply gzip filter.",&
934  "init_snaps",240011)
935  end if
936 
937  call h5pset_chunk_f(crp_list, 2, dims_y, i_stat)
938  if (i_stat .ne. 0) then
939  call raise_exception("Unable to enable chunking.",&
940  "init_snaps",240012)
941  end if
942 
943  ! Create a dataset using cparms creation property
944  call h5dcreate_f(snaps_group_id, dsetname_y, h5t_native_double, dataspace, &
945  dset_id_y, i_stat, crp_list )
946  if (i_stat .ne. 0) then
947  call raise_exception("Unable to create dataspace.",&
948  "init_snaps",240006)
949  end if
950  call h5sclose_f(dataspace, i_stat) ! close the dataspace again
951  if (i_stat .ne. 0) then
952  call raise_exception("Unable to close the dataspace.",&
953  "init_snaps",240007)
954  end if
955 
956  !--- Initialize 1D datasets
957  ! Time dataset
959 
960  !--- Write constant information into the hdf5
961  ! Write A into the hdf5
962  do i=1,net_size
963  helper(i) = isotope(i)%mass
964  end do
966  ! Write Z into hdf5
967  do i=1,net_size
968  helper(i) = isotope(i)%p_nr
969  end do
971  ! Write N into hdf5
972  do i=1,net_size
973  helper(i) = isotope(i)%n_nr
974  end do
976 
977  ! Allocate the array to store the chunks in
979 
980  end subroutine init_snaps
981 
982 
983  !> Initialize the mainout hdf5 group.
984  !!
985  !! This subroutine creates a mainout group and creates the dataspaces for
986  !! all included quantities.
987  subroutine init_mainout
988  implicit none
989  integer :: i_stat !< status variable
990 
991  ! Create a group for the mainout
992  call h5gcreate_f(file_id, "/mainout", mainout_group_id, i_stat)
993  if (i_stat .ne. 0) then
994  call raise_exception("Unable to create mainout group.",&
995  "init_mainout",240005)
996  end if
997  !--- Initialize 1D datasets
998  ! Iteration (integer)dataset
1000  ! Time dataset
1002  ! Temp. dataset
1004  ! Density dataset
1006  ! Entropy dataset
1008  ! Radius dataset
1010  ! Electron fraction dataset
1012  ! neutron abundance dataset
1014  ! proton abundance dataset
1016  ! alpha abundance dataset
1018  ! ylight abundance dataset
1020  ! yheavy abundance dataset
1022  ! abar abundance dataset
1024  ! zbar abundance dataset
1026  end subroutine init_mainout
1027 
1028 
1029  !> Initialize the tracked_nuclei hdf5 group.
1030  !!
1031  !! This subroutine creates a tracked_nuclei group and creates the dataspaces for
1032  !! all included abundances and the time. Furthermore, it allocates a
1033  !! array to store the abundances over several iterations.
1037  implicit none
1038  integer :: i_stat !< status variable
1039  integer :: i !< Loop variable
1040  integer,dimension(track_nuclei_nr) :: helper !< Helper array to store A,Z,N
1041 
1042 
1043  ! Create a group for the tracked nuclei
1044  call h5gcreate_f(file_id, "/tracked_nuclei", track_group_id, i_stat)
1045  if (i_stat .ne. 0) then
1046  call raise_exception("Unable to create tracked_nuclei group.",&
1047  "init_track_nuclei",240005)
1048  end if
1049 
1050 
1051  ! Set the initial dimensions
1052  dims_track(1:2) = (/track_nuclei_nr,1/)
1053  ! Create the data space with unlimited dimensions.
1054  maxdims = (/h5s_unlimited_f, h5s_unlimited_f/)
1055  call h5screate_simple_f(2, dims_track, dataspace, i_stat, maxdims)
1056  if (i_stat .ne. 0) then
1057  call raise_exception("Unable to create necessary dataspace.",&
1058  "init_track_nuclei",240006)
1059  end if
1060 
1061  ! Modify dataset properties
1062  call h5pcreate_f(h5p_dataset_create_f, crp_list, i_stat)
1063  if (i_stat .ne. 0) then
1064  call raise_exception("Unable to modify dataset properties.",&
1065  "init_track_nuclei",240010)
1066  end if
1067 
1068  call h5pset_chunk_f(crp_list, 2, dims_track, i_stat)
1069  if (i_stat .ne. 0) then
1070  call raise_exception("Unable to enable chunking.",&
1071  "init_track_nuclei",240012)
1072  end if
1073 
1074  ! Create a dataset using cparms creation property
1075  call h5dcreate_f(track_group_id, tracked_dsetname_y, h5t_native_double, dataspace, &
1076  tracked_abu_id, i_stat, crp_list )
1077  if (i_stat .ne. 0) then
1078  call raise_exception("Unable to create dataspace.",&
1079  "init_track_nuclei",240006)
1080  end if
1081  call h5sclose_f(dataspace, i_stat) ! close the dataspace again
1082  if (i_stat .ne. 0) then
1083  call raise_exception("Unable to close the dataspace.",&
1084  "init_track_nuclei",240007)
1085  end if
1086 
1087  ! Store the names
1088  allocate(tracked_names(track_nuclei_nr),stat=i_stat) ! Allocate the name array
1089  if (i_stat .ne. 0) then
1090  call raise_exception('Allocation of "tracked_names" failed.',&
1091  "init_track_nuclei",240001)
1092  end if
1093 
1094  ! Convert indices to names
1095  do i=1, track_nuclei_nr
1097  end do
1098 
1099  !--- Write constant information into the hdf5
1100  ! Write A into the hdf5
1101  do i=1,track_nuclei_nr
1102  helper(i) = isotope(track_nuclei_indices(i))%mass
1103  end do
1105  ! Write Z into hdf5
1106  do i=1,track_nuclei_nr
1107  helper(i) = isotope(track_nuclei_indices(i))%p_nr
1108  end do
1110  ! Write N into hdf5
1111  do i=1,track_nuclei_nr
1112  helper(i) = isotope(track_nuclei_indices(i))%n_nr
1113  end do
1115 
1116  ! Also make space for the time
1118  allocate(chunk_store_track(track_nuclei_nr+1,chunk_size_track),stat=i_stat) ! +1 for the time
1119  if (i_stat .ne. 0) then
1120  call raise_exception('Allocation of "chunk_store_track" failed.',&
1121  "init_track_nuclei",240001)
1122  end if
1123  end subroutine init_track_nuclei
1124 
1125 
1126  !> Initialize the timescales hdf5 group.
1127  !!
1128  !! This subroutine creates a timescales group and creates the dataspaces for
1129  !! all included timescales and the time.
1131  implicit none
1132  integer :: i_stat !< status variable
1133  integer :: i !< Loop variable
1134 
1135  ! Create a group for the tracked nuclei
1136  call h5gcreate_f(file_id, "/timescales", ts_group_id, i_stat)
1137  if (i_stat .ne. 0) then
1138  call raise_exception("Unable to create timescales group.",&
1139  "init_av_timescales",240005)
1140  end if
1141  ! Store dataset Ids
1142  do i=1, 17
1143  ts_reac_ids(i) = create_1d_dataset(trim(adjustl(ts_names(i))),ts_group_id)
1144  end do
1145  ! Also make space for the time
1147 
1148  end subroutine init_av_timescales
1149 
1150 
1151 
1152  !> @brief Write the units of the individual entries into the hdf5 file
1153  !!
1154  !! For example: \n
1155  !! Temperature - GK\n
1156  !! Entropy - kB/nuc
1157  !!
1158  !! @note This subroutine is never used
1159  !!
1160  !! @author Moritz Reichert
1161  !! @date 28.01.21
1162  subroutine write_units()
1163  implicit none
1164  integer,parameter :: length=10 !< length of entries
1165  character(len=20),dimension(length,2) :: quantity !< Storage of the text to write
1166  integer(HID_T) :: dset_id !< ID of the dataset
1167  integer(HSIZE_T), dimension(2) :: dims_static = (/length,2/) !< Dimensions (length,2)
1168  integer :: i_stat !< status variable
1169  INTEGER(HID_T) :: strtype
1170  integer(SIZE_T) :: typesize
1171  ! Write the units of every quantity into the hdf5 file
1172  quantity(1 ,1) = "Abundances" ; quantity(1 ,2) = "-"
1173  quantity(2 ,1) = "Atomic number" ; quantity(2 ,2) = "-"
1174  quantity(3 ,1) = "Density" ; quantity(3 ,2) = "g/ccm"
1175  quantity(4 ,1) = "Electron fraction" ; quantity(4 ,2) = "-"
1176  quantity(5 ,1) = "Entropy" ; quantity(5 ,2) = "kB/nuc"
1177  quantity(6 ,1) = "Mass number" ; quantity(6 ,2) = "-"
1178  quantity(7 ,1) = "Neutron number" ; quantity(7 ,2) = "-"
1179  quantity(8 ,1) = "Radius" ; quantity(8 ,2) = "Km"
1180  quantity(9 ,1) = "Temperature" ; quantity(9 ,2) = "GK"
1181  quantity(10,1) = "Time" ; quantity(10,2) = "s"
1182 
1183 
1184  ! Generate a datatype that is a character with length of 20
1185  call h5tcopy_f(h5t_native_character, strtype, i_stat)
1186  typesize = 20
1187  call h5tset_size_f(strtype, typesize, i_stat)
1188 
1189  ! Create an appropriate dataspace
1190  call h5screate_simple_f(2, dims_static, dataspace, i_stat)
1191 
1192  ! Create a dataset using cparms creation property
1193  call h5dcreate_f(file_id, dsetname_u, strtype, dataspace, &
1194  dset_id, i_stat )
1195  call h5sclose_f(dataspace, i_stat)
1196 
1197  ! Write initial value to the dataset
1198  call h5dwrite_f(dset_id, strtype, quantity, dims_static, i_stat)
1199 
1200  ! Close the dataset
1201  call h5dclose_f(dset_id, i_stat)
1202 
1203  end subroutine write_units
1204 
1205 
1206 
1207  !> Write final abundances into hdf5 file
1208  !!
1209  !! This routine writes the final abundances of all nuclei (group:finab/finab),
1210  !! the final abundances summed over mass number (group:finab/finabsum),
1211  !! and the final abundances summed over equal proton numbers (group:finab/finabelem).
1212  !! These entries are similar to the ascii version the output (finabelem.dat,..)
1213  !!
1214  !! @author M. Reichert
1215  !! @date 05.03.21
1216  subroutine write_finab(Y)
1217  use global_class, only: isotope, net_size
1218  implicit none
1219 
1220  real(r_kind),dimension(net_size),intent(in) :: y !< Abundances
1221  real(r_kind),dimension(:),allocatable :: y_tmpa,x_tmpa !< Temporary helper variables
1222  real(r_kind),dimension(:),allocatable :: y_tmp,x_tmp !< Temporary helper variables
1223  integer,dimension(:),allocatable :: a_tmp,z_tmp !< Temporary helper variables
1224  integer :: i !< Loop variable
1225  integer :: count !< Helper variable
1226  integer :: i_stat !< Status variable
1227  integer :: mval !< helper variable
1228 
1229  ! Create a group for the finab
1230  call h5gcreate_f(file_id, "/finab/", finab_group_id, i_stat)
1231  if (i_stat .ne. 0) then
1232  call raise_exception("Unable to create finab group.",&
1233  "write_finab",240005)
1234  end if
1235  call h5gclose_f(finab_group_id , i_stat)
1236  call h5gcreate_f(file_id, "/finab/finab", finab_group_id, i_stat)
1237  if (i_stat .ne. 0) then
1238  call raise_exception("Unable to create finab group.",&
1239  "write_finab",240005)
1240  end if
1241 
1242 
1243  ! Write analog entry to the ascii file finab.dat
1244  ! Count the amount of abundances above 1d-25 for the output
1245  count = 0
1246  do i=1,net_size
1247  if (y(i) .gt. 1d-25) then
1248  count = count+1
1249  end if
1250  end do
1251 
1252  ! Allocate arrays
1253  allocate(y_tmp(count))
1254  allocate(x_tmp(count))
1255  allocate(a_tmp(count))
1256  allocate(z_tmp(count))
1257 
1258  ! Fill the temporary arrays
1259  count = 0
1260  do i=1,net_size
1261  if (y(i) .gt. 1d-25) then
1262  count = count+1
1263  y_tmp(count) = y(i)
1264  a_tmp(count) = isotope(i)%mass
1265  z_tmp(count) = isotope(i)%p_nr
1266  x_tmp(count) = y_tmp(count)*a_tmp(count)
1267  end if
1268  end do
1269 
1270  ! Write to the hdf5 file
1271  call create_constant_1d_int_arrays(count,a_tmp,"A",finab_group_id)
1272  call create_constant_1d_int_arrays(count,z_tmp,"Z",finab_group_id)
1273  call create_constant_1d_arrays(count,y_tmp,"Y",finab_group_id)
1274  call create_constant_1d_arrays(count,x_tmp,"X",finab_group_id)
1275 
1276  ! Deallocate arrays
1277  deallocate(y_tmp)
1278  deallocate(a_tmp)
1279  deallocate(z_tmp)
1280  deallocate(x_tmp)
1281 
1282  ! Close the group
1283  call h5gclose_f(finab_group_id , i_stat)
1284 
1285  ! Create group for finabsum
1286  call h5gcreate_f(file_id, "/finab/finabsum", finab_group_id, i_stat)
1287  if (i_stat .ne. 0) then
1288  call raise_exception("Unable to create finabsum group.",&
1289  "write_finab",240005)
1290  end if
1291 
1292  mval = maxval(isotope%mass)
1293  allocate(y_tmpa(mval))
1294 
1295  ! Sum up abundances
1296  y_tmpa(:) = 0
1297  do i=1,net_size
1298  y_tmpa(isotope(i)%mass)=y_tmpa(isotope(i)%mass)+y(i)
1299  end do
1300 
1301  count = 0
1302  do i=1,mval
1303  if (y_tmpa(i) .gt. 1d-20) then
1304  count = count+1
1305  end if
1306  end do
1307 
1308  ! Allocate arrays once more
1309  allocate(y_tmp(count))
1310  allocate(a_tmp(count))
1311  allocate(x_tmp(count))
1312 
1313  ! Prepare helper arrays for the output
1314  count = 0
1315  do i=1,mval
1316  if (y_tmpa(i) .gt. 1d-20) then
1317  count = count+1
1318  a_tmp(count) = i
1319  y_tmp(count) = y_tmpa(i)
1320  x_tmp(count) = y_tmp(count)*a_tmp(count)
1321  end if
1322  end do
1323 
1324  ! Write the arrays
1325  call create_constant_1d_int_arrays(count,a_tmp,"A",finab_group_id)
1326  call create_constant_1d_arrays(count,y_tmp,"Y",finab_group_id)
1327  call create_constant_1d_arrays(count,x_tmp,"X",finab_group_id)
1328 
1329  ! Deallocate again
1330  deallocate(y_tmp)
1331  deallocate(a_tmp)
1332  deallocate(x_tmp)
1333  deallocate(y_tmpa)
1334 
1335  ! Close the group
1336  call h5gclose_f(finab_group_id , i_stat)
1337 
1338  ! Create group for finabsum
1339  call h5gcreate_f(file_id, "/finab/finabelem", finab_group_id, i_stat)
1340  if (i_stat .ne. 0) then
1341  call raise_exception("Unable to create finabelem group.",&
1342  "write_finab",240005)
1343  end if
1344 
1345  ! Prepare arrays to sum over Z
1346  mval = maxval(isotope%p_nr)+1 ! To also write neutrons add 1
1347  allocate(y_tmpa(mval))
1348  allocate(x_tmpa(mval))
1349 
1350  ! Sum up abundances
1351  y_tmpa(:) = 0
1352  x_tmpa(:) = 0
1353  do i=1,net_size
1354  y_tmpa(isotope(i)%p_nr+1)=y_tmpa(isotope(i)%p_nr+1)+y(i)
1355  x_tmpa(isotope(i)%p_nr+1)=x_tmpa(isotope(i)%p_nr+1)+y(i)*isotope(i)%mass
1356  end do
1357 
1358  count = 0
1359  do i=1,mval
1360  if (y_tmpa(i) .gt. 1d-20) then
1361  count = count+1
1362  end if
1363  end do
1364 
1365  ! Allocate
1366  allocate(y_tmp(count))
1367  allocate(x_tmp(count))
1368  allocate(z_tmp(count))
1369 
1370  ! Write everything to helper variables
1371  y_tmp(:) = 0
1372  x_tmp(:) = 0
1373  z_tmp(:) = 0
1374  count = 0
1375  do i=1,mval
1376  if (y_tmpa(i) .gt. 1d-20) then
1377  count = count+1
1378  y_tmp(count) = y_tmpa(i)
1379  x_tmp(count) = x_tmpa(i)
1380  z_tmp(count) = i-1
1381  end if
1382  end do
1383 
1384  ! Write the arrays
1385  call create_constant_1d_int_arrays(count,z_tmp,"Z",finab_group_id)
1386  call create_constant_1d_arrays(count,y_tmp,"Y",finab_group_id)
1387  call create_constant_1d_arrays(count,x_tmp,"X",finab_group_id)
1388 
1389  ! Close the group
1390  call h5gclose_f(finab_group_id , i_stat)
1391 
1392  end subroutine
1393 
1394 
1395 
1396  !> @brief Gets a dataset name and creates it
1397  !!
1398  !! Creates a 1d dataset in the hdf5 and returns its
1399  !! dataset ID.
1400  !!
1401  !! @author Moritz Reichert
1402  !! @date 28.01.21
1403  function create_1d_dataset(dsetname,group_id)
1404  implicit none
1405  character(len=*),intent(in) :: dsetname !< Name of the dataset
1406  integer(HID_T),intent(in) :: group_id !< Group identifier
1407  integer(HSIZE_T) :: create_1d_dataset !< Dataset ID of the entry
1408  integer(HID_T) :: dset_id !< ID of the dataset
1409  integer(HSIZE_T), dimension(1) :: maxdims_1d !< Maximum (1d) dimensions
1410  integer :: i_stat !< Reading status
1411 
1412  ! Set the dimension to unlimited to be able to extend to it
1413  maxdims_1d = h5s_unlimited_f
1414 
1415  ! Create an appropriate dataspace
1416  call h5screate_simple_f(1, dims_1d, dataspace, i_stat, maxdims_1d)
1417  if (i_stat .ne. 0) then
1418  call raise_exception("Unable to create the dataspace.",&
1419  "create_1d_dataset",240006)
1420  end if
1421 
1422  ! Modify dataset properties
1423  call h5pcreate_f(h5p_dataset_create_f, crp_list, i_stat)
1424  if (i_stat .ne. 0) then
1425  call raise_exception("Unable to modify dataspace properties.",&
1426  "create_1d_dataset",240010)
1427  end if
1428 
1429  call h5pset_chunk_f(crp_list, 1, dims_1d, i_stat)
1430  if (i_stat .ne. 0) then
1431  call raise_exception("Unable to enable chunking.",&
1432  "create_1d_dataset",240012)
1433  end if
1434 
1435  ! Create a dataset using cparms creation property
1436  call h5dcreate_f(group_id, dsetname, h5t_native_double, dataspace, &
1437  dset_id, i_stat, crp_list )
1438  if (i_stat .ne. 0) then
1439  call raise_exception("Unable to create the dataspace.",&
1440  "create_1d_dataset",240006)
1441  end if
1442  ! Close the dataspace
1443  call h5sclose_f(dataspace, i_stat)
1444  if (i_stat .ne. 0) then
1445  call raise_exception("Unable to close the dataspace again.",&
1446  "create_1d_dataset",240023)
1447  end if
1448 
1449  ! ! Write initial value to the dataset
1450  ! call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE, init_val, dims_1d, i_stat)
1451 
1452  ! Dset ID return value
1453  create_1d_dataset = dset_id
1454 
1455  end function create_1d_dataset
1456 
1457 
1458  !> @brief Gets a dataset name and creates an integer dataset
1459  !!
1460  !! Creates a 1d dataset in the hdf5 and returns its
1461  !! dataset ID.
1462  !!
1463  !! @author Moritz Reichert
1464  !! @date 28.01.21
1465  function create_1d_int_dataset(dsetname,group_id)
1466  implicit none
1467  character(len=*),intent(in) :: dsetname !< Name of the dataset
1468  integer(HID_T),intent(in) :: group_id !< Group identifier
1469  integer(HSIZE_T) :: create_1d_int_dataset !< Dataset ID of the entry
1470  integer(HID_T) :: dset_id !< ID of the dataset
1471  integer(HSIZE_T), dimension(1) :: maxdims_1d !< Maximum (1d) dimensions
1472  integer :: i_stat !< Reading status
1473 
1474  ! Set the dimension to unlimited to be able to extend to it
1475  maxdims_1d = h5s_unlimited_f
1476 
1477  ! Create an appropriate dataspace
1478  call h5screate_simple_f(1, dims_1d, dataspace, i_stat, maxdims_1d)
1479  if (i_stat .ne. 0) then
1480  call raise_exception("Unable to create the dataspace.",&
1481  "create_1d_int_dataset",240006)
1482  end if
1483 
1484  ! Modify dataset properties
1485  call h5pcreate_f(h5p_dataset_create_f, crp_list, i_stat)
1486  if (i_stat .ne. 0) then
1487  call raise_exception("Unable to modify dataspace properties.",&
1488  "create_1d_int_dataset",240010)
1489  end if
1490 
1491  call h5pset_chunk_f(crp_list, 1, dims_1d, i_stat)
1492  if (i_stat .ne. 0) then
1493  call raise_exception("Unable to enable chunking.",&
1494  "create_1d_int_dataset",240012)
1495  end if
1496 
1497 
1498  ! Create a dataset using cparms creation property
1499  call h5dcreate_f(group_id, dsetname, h5t_native_integer, dataspace, &
1500  dset_id, i_stat, crp_list )
1501  if (i_stat .ne. 0) then
1502  call raise_exception("Unable to create the dataspace.",&
1503  "create_1d_int_dataset",240006)
1504  end if
1505 
1506  call h5sclose_f(dataspace, i_stat)
1507  if (i_stat .ne. 0) then
1508  call raise_exception("Unable to close the dataspace again.",&
1509  "create_1d_int_dataset",240007)
1510  end if
1511 
1512  ! Dset ID return value
1513  create_1d_int_dataset = dset_id
1514 
1515  end function create_1d_int_dataset
1516 
1517 
1518  !> @brief Create a hdf5 entry with constant values
1519  !!
1520  !! This is used for mass number, proton number, and
1521  !! neutron number.
1522  !!
1523  !! @author Moritz Reichert
1524  !! @date 28.01.21
1525  subroutine create_constant_1d_int_arrays(length,data,dsetname,group_id)
1526  implicit none
1527  integer,intent(in) :: length !< ID of the dataset
1528  integer,dimension(length),intent(in) :: data !< Data values
1529  character(len=*),intent(in) :: dsetname !< Name of the dataset
1530  integer(HID_T) :: dset_id !< ID of the dataset
1531  integer(HID_T) :: group_id !< ID of the group
1532  integer(HSIZE_T), dimension(1) :: maxdims_1d !< Maximum (1d) dimensions
1533  integer(HSIZE_T), dimension(1) :: dims_static !< Maximum (1d) dimensions
1534  integer :: i_stat !< Reading status
1535 
1536  ! Set the dimension to unlimited to be able to extend to it
1537  dims_static = length
1538 
1539  ! Create an appropriate dataspace
1540  call h5screate_simple_f(1, dims_static, dataspace, i_stat)
1541  if (i_stat .ne. 0) then
1542  call raise_exception("Unable to create the dataspace.",&
1543  "create_constant_1d_int_arrays",240006)
1544  end if
1545 
1546  ! Create a dataset using cparms creation property
1547  call h5dcreate_f(group_id, dsetname, h5t_native_integer, dataspace, &
1548  dset_id, i_stat )
1549  if (i_stat .ne. 0) then
1550  call raise_exception("Unable to modify dataspace properties.",&
1551  "create_constant_1d_int_arrays",240010)
1552  end if
1553 
1554  call h5sclose_f(dataspace, i_stat)
1555  if (i_stat .ne. 0) then
1556  call raise_exception("Unable to close the dataspace again.",&
1557  "create_constant_1d_int_arrays",240007)
1558  end if
1559  ! Write initial value to the dataset
1560  call h5dwrite_f(dset_id, h5t_native_integer, data, dims_static, i_stat)
1561  if (i_stat .ne. 0) then
1562  call raise_exception("Unable to write to the dataset.",&
1563  "create_constant_1d_int_arrays",240013)
1564  end if
1565 
1566  ! Close the dataset
1567  call h5dclose_f(dset_id, i_stat)
1568  if (i_stat .ne. 0) then
1569  call raise_exception("Unable to close the dataset.",&
1570  "create_constant_1d_int_arrays",240007)
1571  end if
1572 
1573  end subroutine create_constant_1d_int_arrays
1574 
1575 
1576  !> @brief Create a hdf5 entry with constant values
1577  !!
1578  !! This is used for e.g., the flows
1579  !!
1580  !! @author Moritz Reichert
1581  !! @date 28.01.21
1582  subroutine create_constant_1d_arrays(length,data,dsetname,group_id)
1583  implicit none
1584  integer,intent(in) :: length !< ID of the dataset
1585  real(r_kind),dimension(length),intent(in) :: data !< Data values
1586  character(len=*),intent(in) :: dsetname !< Name of the dataset
1587  integer(HID_T) :: dset_id !< ID of the dataset
1588  integer(HID_T) :: group_id !< ID of the group
1589  integer(HSIZE_T), dimension(1) :: maxdims_1d !< Maximum (1d) dimensions
1590  integer(HSIZE_T), dimension(1) :: dims_static !< Maximum (1d) dimensions
1591  integer :: i_stat !< Reading status
1592 
1593  ! Set the dimension to unlimited to be able to extend to it
1594  dims_static = length
1595 
1596  ! Create an appropriate dataspace
1597  call h5screate_simple_f(1, dims_static, dataspace, i_stat)
1598  if (i_stat .ne. 0) then
1599  call raise_exception("Unable to create the dataspace.",&
1600  "create_constant_1d_int_arrays",240006)
1601  end if
1602 
1603  ! Create a dataset using cparms creation property
1604  call h5dcreate_f(group_id, dsetname, h5t_native_double, dataspace, &
1605  dset_id, i_stat )
1606  if (i_stat .ne. 0) then
1607  call raise_exception("Unable to modify dataspace properties.",&
1608  "create_constant_1d_int_arrays",240010)
1609  end if
1610 
1611  call h5sclose_f(dataspace, i_stat)
1612  if (i_stat .ne. 0) then
1613  call raise_exception("Unable to close the dataspace again.",&
1614  "create_constant_1d_int_arrays",240007)
1615  end if
1616  ! Write initial value to the dataset
1617  call h5dwrite_f(dset_id, h5t_native_double, data, dims_static, i_stat)
1618  if (i_stat .ne. 0) then
1619  call raise_exception("Unable to write to the dataset.",&
1620  "create_constant_1d_int_arrays",240013)
1621  end if
1622 
1623  ! Close the dataset
1624  call h5dclose_f(dset_id, i_stat)
1625  if (i_stat .ne. 0) then
1626  call raise_exception("Unable to close the dataset.",&
1627  "create_constant_1d_int_arrays",240007)
1628  end if
1629 
1630  end subroutine create_constant_1d_arrays
1631 
1632 
1633  !> @brief Extend a previously created 1D - dataset
1634  !!
1635  !! The necessary input is the value and the
1636  !! id of the dataset only.
1637  !!
1638  !! @author Moritz Reichert
1639  !! @date 28.01.21
1640  subroutine extend_1d_dataset(dset_id,value,in_size,chunksize)
1641  use global_class, only: net_size
1642  implicit none
1643  integer,intent(in) :: chunksize!< Size of the amount of variables written
1644  real(r_kind),dimension(chunksize),intent(in) :: value !< New value that will get appended
1645  integer(HID_T),intent(in) :: dset_id !< ID of the dataset
1646  integer,intent(in) :: in_size !< New size of the array
1647  integer(HID_T) :: memspace !< Memory dataspace identifier
1648  integer :: i_stat !< Reading status
1649  integer(HSIZE_T), dimension(1) :: offset !< Offset, dont overwrite the old data
1650  integer(HSIZE_T), dimension(1) :: count !< New line
1651  integer(HSIZE_T), dimension(1) :: new_size !< New total size of the dataset
1652 
1653  !Extend the dataset (new dimensions)
1654  new_size(1) = in_size+chunksize
1655  dims_1d = (/chunksize/)
1656  call h5dset_extent_f(dset_id, new_size, i_stat)
1657  if (i_stat .ne. 0) then
1658  call raise_exception("Unable to extend the dataset.",&
1659  "extend_1d_dataset",240014)
1660  end if
1661 
1662  call h5screate_simple_f (1, dims_1d, memspace, i_stat)
1663  if (i_stat .ne. 0) then
1664  call raise_exception("Unable to create new memspace.",&
1665  "extend_1d_dataset",240015)
1666  end if
1667 
1668  ! Offset by previous size
1669  offset(1) = in_size
1670  ! write a new row
1671  count(1) = chunksize
1672 
1673  ! Create space, select hyperslab
1674  call h5dget_space_f(dset_id, dataspace, i_stat)
1675  call h5sselect_hyperslab_f(dataspace, h5s_select_set_f, &
1676  offset, count, i_stat)
1677  if (i_stat .ne. 0) then
1678  call raise_exception("Unable to select hyperslab.",&
1679  "extend_1d_dataset",240016)
1680  end if
1681  ! Write to the new row
1682  call h5dwrite_f(dset_id, h5t_native_double, value, dims_1d, i_stat, &
1683  memspace, dataspace)
1684  if (i_stat .ne. 0) then
1685  call raise_exception("Unable to write to the file.",&
1686  "extend_1d_dataset",240013)
1687  end if
1688  end subroutine extend_1d_dataset
1689 
1690 
1691  !> @brief Extend a previously created 1D integer - dataset
1692  !!
1693  !! The necessary input is the value and the
1694  !! id of the dataset only.
1695  !!
1696  !! @author Moritz Reichert
1697  !! @date 28.01.21
1698  subroutine extend_1d_int_dataset(dset_id,value,in_size,chunksize)
1699  use global_class, only: net_size
1700  implicit none
1701  integer,intent(in) :: chunksize!< Size of the amount of variables written
1702  integer,dimension(chunksize),intent(in) :: value !< New value that will get appended
1703  integer(HID_T),intent(in) :: dset_id !< ID of the dataset
1704  integer,intent(in) :: in_size !< New size of the array
1705  integer(HID_T) :: memspace !< Memory dataspace identifier
1706  integer :: i_stat !< Reading status
1707  integer(HSIZE_T), dimension(1) :: offset !< Offset, dont overwrite the old data
1708  integer(HSIZE_T), dimension(1) :: count !< New line
1709  integer(HSIZE_T), dimension(1) :: new_size !< New total size of the dataset
1710 
1711  !Extend the dataset (new dimensions)
1712  new_size(1) = in_size+chunksize
1713  dims_1d = (/chunksize/)
1714  call h5dset_extent_f(dset_id, new_size, i_stat)
1715  if (i_stat .ne. 0) then
1716  call raise_exception("Unable to extend the dataset.",&
1717  "extend_1d_int_dataset",240014)
1718  end if
1719 
1720  call h5screate_simple_f (1, dims_1d, memspace, i_stat)
1721  if (i_stat .ne. 0) then
1722  call raise_exception("Unable to create new memspace.",&
1723  "extend_1d_int_dataset",240015)
1724  end if
1725 
1726  ! Offset one row
1727  offset(1) = in_size
1728  ! write a new row
1729  count(1) = chunksize
1730 
1731  ! Create space, select hyperslab
1732  call h5dget_space_f(dset_id, dataspace, i_stat)
1733  call h5sselect_hyperslab_f(dataspace, h5s_select_set_f, &
1734  offset, count, i_stat)
1735  if (i_stat .ne. 0) then
1736  call raise_exception("Unable to select hyperslab.",&
1737  "extend_1d_int_dataset",240016)
1738  end if
1739 
1740  ! Write to the new row
1741  call h5dwrite_f(dset_id, h5t_native_integer, value, dims_1d, i_stat, &
1742  memspace, dataspace)
1743  if (i_stat .ne. 0) then
1744  call raise_exception("Unable to write to the file.",&
1745  "extend_1d_int_dataset",240013)
1746  end if
1747  end subroutine extend_1d_int_dataset
1748 
1749 
1750 
1751  !>
1752  !! @brief Subroutine to write the average timescales (1/s) into the hdf5
1753  !!
1754  !! @author Moritz Reichert
1755  !! @date 5.02.21
1756  subroutine extend_av_timescales(time,tau_ga, tau_ag,tau_ng, tau_gn, tau_pg, tau_gp, tau_np, &
1757  tau_pn, tau_an, tau_na, tau_ap, tau_pa, tau_beta, tau_alpha, &
1758  tau_nfiss, tau_sfiss, tau_bfiss)
1759  implicit none
1760  real(r_kind),intent(in) :: time !< Time [s]
1761  real(r_kind),intent(in) :: tau_ng, tau_gn, tau_pg, tau_gp, tau_np !< Timescales [1/s]
1762  real(r_kind),intent(in) :: tau_ga, tau_ag, tau_ap, tau_pa !< Timescales [1/s]
1763  real(r_kind),intent(in) :: tau_pn, tau_an, tau_na, tau_beta, tau_alpha !< Timescales [1/s]
1764  real(r_kind),intent(in) :: tau_nfiss, tau_sfiss, tau_bfiss !< Timescales [1/s]
1765  !
1766  integer :: i !< Loop variable
1767 
1768  ! Count how large the space has to be
1770  !< Save the data temporary in an array
1771  chunk_store_ts(chunk_counter_ts,:) = (/time, tau_ga, tau_ag, tau_ng, tau_gn, tau_pg, tau_gp, tau_np, &
1772  tau_pn, tau_an, tau_na, tau_ap, tau_pa, tau_beta, tau_alpha, &
1773  tau_nfiss, tau_sfiss, tau_bfiss/)
1774  ! Write the chunk to the file
1775  if (chunk_counter_ts .eq. chunk_size_ts) then
1776  call write_av_timescales()
1777  end if
1778 
1779  end subroutine extend_av_timescales
1780 
1781  !>
1782  !! @brief Write average timescales and time into the hdf5 file
1783  !!
1784  !! These values are stored in a separate group (called timescales) that is initialized
1785  !! in \ref init_hdf5_module.
1786  !!
1787  !! @author Moritz Reichert
1788  !! @date 5.02.21
1789  subroutine write_av_timescales()
1790  implicit none
1791  integer :: i !< Loop variable
1792 
1793  if (chunk_counter_ts .lt. 1) return
1794  ! Save the time
1796  ! Save timescales
1797  do i=1, 17
1799  end do
1801  chunk_counter_ts = 0
1802  end subroutine write_av_timescales
1803 
1804  !>
1805  !! @brief Write tracked abundances and time into the hdf5 file
1806  !!
1807  !! These values are stored in a separate group (called tracked_nuclei) that is initialized
1808  !! in \ref init_hdf5_module.
1809  !!
1810  !! @author Moritz Reichert
1811  !! @date 5.02.21
1812  subroutine extend_track_nuclei(time,Y_array)
1814  implicit none
1815  real(r_kind),dimension(net_size),intent(in) :: y_array !< Abundance to store
1816  real(r_kind),intent(in) :: time !< Time [s]
1817  integer :: i !< Loop variable
1818 
1819  ! Count the amount of entries in an intermediate array
1821 
1822  ! Store the time
1824  ! Store abundances
1825  do i=1, track_nuclei_nr
1827  end do
1828 
1829  if (chunk_counter_track .eq. chunk_size_track) then
1830  ! Extend the datasets
1831  call write_track_data()
1832  end if
1833 
1834  end subroutine extend_track_nuclei
1835 
1836 
1837 
1838  !> Write the abundances of track nuclei into a file
1839  !!
1840  !! When this subroutine is called depends on the chunk size.
1841  !!
1842  !! @author Moritz Reichert
1843  !! @date 09.02.21
1844  subroutine write_track_data()
1845  use global_class, only:track_nuclei_nr
1846  implicit none
1847  integer :: i !< Loop variable
1848 
1849  ! Do nothing if it recently got written already
1850  if (chunk_counter_track .lt. 1) return
1851 
1852  ! write time array by "chunk" timesteps
1854  ! Write abundances
1858  end subroutine write_track_data
1859 
1860 
1861 
1862 
1863  !>
1864  !! Write abundances and time into the hdf5 file
1865  !!
1866  !! These values are stored in a separate group (called snapshots) that is initialized
1867  !! in \ref init_hdf5_module.
1868  !!
1869  !! @author Moritz Reichert
1870  !! @date 5.02.21
1871  subroutine extend_snaps(time,Y_array)
1872  use global_class, only: net_size
1873  implicit none
1874  real(r_kind),dimension(net_size),intent(in) :: y_array !< Abundance to store
1875  real(r_kind),intent(in) :: time !< Time [s]
1876 
1877  ! Store the time
1880  ! Save the abundances in intermediate arrays
1882 
1883  ! Write to the file
1884  if (chunk_counter_snaps .eq. chunk_size_snaps) then
1885  call write_snaps()
1886  end if
1887  end subroutine extend_snaps
1888 
1889 
1890  !> Write the abundances of all nuclei into a file
1891  !!
1892  !! When this subroutine is called depends on the chunk size.
1893  !!
1894  !! @author Moritz Reichert
1895  !! @date 09.02.21
1896  subroutine write_snaps()
1897  use global_class, only: net_size
1898  implicit none
1899 
1900  ! Do nothing if it was recently called already
1901  if (chunk_size_snaps .lt. 1) return
1902 
1903  ! extend time array by one timestep
1907  chunk_counter_snaps = 0 !< reset the chunk counter
1908 
1909  end subroutine write_snaps
1910 
1911 
1912 
1913  !> Write the mainout data to the hdf5
1914  !!
1915  !! This will write the iteration, time (s),
1916  !! temperature (GK), density (g/ccm), entropy(kB/nuc),
1917  !! radius (km), Ye, Yn, Yp, Ya, Ylight, Yheavy,
1918  !! abar, and zbar.
1919  !!
1920  !! @author Moritz Reichert
1921  !! @date 5.02.21
1922  subroutine extend_mainout(cnt,time,temp,dens,entr,rad,Y)
1924  implicit none
1925  integer,intent(in) :: cnt !< Iteration count
1926  real(r_kind),intent(in) :: time !< Time [s]
1927  real(r_kind),intent(in) :: temp !< Temperature [GK]
1928  real(r_kind),intent(in) :: dens !< Density [g/ccm]
1929  real(r_kind),intent(in) :: entr !< Entropy [kB/nuc]
1930  real(r_kind),intent(in) :: rad !< Radius [km]
1931  real(r_kind),dimension(net_size),intent(in) :: y !< Abundances
1932  ! Helper variables
1933  real(r_kind) :: ye,yneu,ypro,yhe4,ylight,yheavies,ysum,yasum,yzsum,abar,zbar
1934 
1935  ! Count the amount of entries in an intermediate array
1937 
1938  ! output diagnostics
1939  ye = sum(isotope(1:net_size)%p_nr*y(1:net_size))
1940  ylight= max(1.0d-99,sum(y(ipro+1:ihe4-1)))
1941  yheavies= 0.0
1942  if (ihe4.ge.1) yheavies= max(1.0d-99,sum(y(ihe4+1:net_size)))
1943  ! Calculate abar and zbar
1944  ysum = sum(y(1:net_size))
1945  yasum = sum(y(1:net_size)*isotope(1:net_size)%mass)
1946  yzsum = sum(y(1:net_size)*isotope(1:net_size)%p_nr)
1947  abar = yasum/ysum
1948  zbar = yzsum/ysum
1949  ! Get abundance of neutrons, protons, and alphas if they exist in the network
1950  yneu= 0.0
1951  if (ineu.ge.1) yneu= max(1.0d-99,y(ineu))
1952 
1953  ypro= 0.0
1954  if (ipro.ge.1) ypro= max(1.0d-99,y(ipro))
1955 
1956  yhe4= 0.0
1957  if (ihe4.ge.1) yhe4= max(1.0d-99,y(ihe4))
1958 
1959  ! Store data in intermediate arrays to prevent to much IO going on
1973  ! Same for iterations
1975 
1977  ! Extend the datasets
1978  call write_mainout_data()
1979  end if
1980  end subroutine extend_mainout
1981 
1982 
1983 
1984  !> Write the mainout data into a file
1985  !!
1986  !! When this subroutine is called depends on the chunk size.
1987  !!
1988  !! @author Moritz Reichert
1989  !! @date 09.02.21
1990  subroutine write_mainout_data()
1991  implicit none
1992  ! Do nothing if it recently got written already
1993  if (chunk_counter_mainout .lt. 1) return
1994  ! Extend the datasets
2038  chunk_counter_mainout = 0 !< reset the chunk counter
2039  end subroutine write_mainout_data
2040 
2041 
2042 
2043  !> @brief Extend the Y dataset for the net timestep.
2044  !!
2045  !! The dimension of this is given by global_class::net_size and the current
2046  !! iteration \ref iter.
2047  !!
2048  !! @see extend_1d_dataset, extend_1d_int_dataset
2049  !! @author Moritz Reichert
2050  !! @date 28.01.21
2051  subroutine extend_hdf5_y(dset_id,Y_array,nr_nuc,old_size,chunksize)
2052  use global_class, only: net_size
2053  implicit none
2054  integer(HID_T),intent(in) :: dset_id !< Dataset identifier
2055  integer,intent(in) :: nr_nuc !< Amount of abundances
2056  integer,intent(in) :: old_size !< Old length of arrays
2057  integer,intent(in) :: chunksize!< Size of the chunk
2058  real(r_kind),dimension(nr_nuc,chunksize),intent(in) :: y_array !< Abundance array to store
2059  integer(HSIZE_T),dimension(2) :: new_size !< New size of dataset
2060  integer(HSIZE_T),dimension(1:2) :: offset !< offset of the data in the file
2061  integer(HSIZE_T),dimension(1:2) :: count !< Size of the new data
2062  integer :: i_stat !< status variable
2063  integer(HID_T) :: memspace !< Memory dataspace identifier
2064 
2065  !Extend the dataset.
2066  new_size(1:2) = (/nr_nuc,old_size+chunksize/)
2067  ! Set the dimensions
2068  dims_y = (/nr_nuc,chunksize/)
2069 
2070  call h5dset_extent_f(dset_id, new_size, i_stat)
2071  call h5screate_simple_f (2, dims_y, memspace, i_stat)
2072 
2073  ! Offset by the old size
2074  offset(1:2) = (/0,old_size/)
2075  ! write a couple of new rows
2076  count(1:2) = (/nr_nuc,chunksize/)
2077 
2078  ! Create space, select hyperslab
2079  call h5dget_space_f(dset_id, dataspace, i_stat)
2080  call h5sselect_hyperslab_f(dataspace, h5s_select_set_f, &
2081  offset, count, i_stat)
2082  ! Write to the new row
2083  call h5dwrite_f(dset_id, h5t_native_double, y_array, dims_y, i_stat, &
2084  memspace, dataspace)
2085 
2086  end subroutine extend_hdf5_y
2087 
2088 
2089  !> Finalize the hdf5 module
2090  !!
2091  !! This subroutine closes all datasets, dataspaces, files
2092  !! and other things.
2093  !!
2094  !! @author Moritz Reichert
2095  !! @date 28.01.21
2102  use global_class, only: track_nuclei_nr
2103  implicit none
2104  integer :: i_stat !< Status variable
2105  integer :: i !< Loop variable
2106 
2107  ! Don't close anything if there is no file
2108  if (.not. hdf5_output) return
2109 
2110  ! Cleanup snapshots
2111  if ((h_snapshot_every .gt. 0) .or. (h_custom_snapshots)) then
2112  call write_snaps() ! Write the last data into the file
2113  call h5gclose_f(snaps_group_id,i_stat)
2114  if (i_stat .ne. 0) call raise_exception("Unable to close snapshot group.",&
2115  "hdf5_module_finalize",240017)
2116  ! Close all datasets
2117  call h5dclose_f(dset_id_y , i_stat)
2118  if (i_stat .ne. 0) call raise_exception("Unable to close abundance dataset.",&
2119  "hdf5_module_finalize",240007)
2120  call h5dclose_f(snaps_dset_id_t , i_stat)
2121  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2122  "hdf5_module_finalize",240007)
2123  end if
2124 
2125  ! Cleanup mainout
2126  if (h_mainout_every .gt. 0) then
2127  call write_mainout_data() ! Write the last data into the file
2128  call h5gclose_f(mainout_group_id , i_stat)
2129  if (i_stat .ne. 0) call raise_exception("Unable to close mainout group.",&
2130  "hdf5_module_finalize",240017)
2131  call h5dclose_f(mainout_dset_id_t , i_stat)
2132  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2133  "hdf5_module_finalize",240007)
2134  call h5dclose_f(mainout_dset_id_temp , i_stat)
2135  if (i_stat .ne. 0) call raise_exception("Unable to close temperature dataset.",&
2136  "hdf5_module_finalize",240007)
2137  call h5dclose_f(mainout_dset_id_dens , i_stat)
2138  if (i_stat .ne. 0) call raise_exception("Unable to close density dataset.",&
2139  "hdf5_module_finalize",240007)
2140  call h5dclose_f(mainout_dset_id_entr , i_stat)
2141  if (i_stat .ne. 0) call raise_exception("Unable to close entropy dataset.",&
2142  "hdf5_module_finalize",240007)
2143  call h5dclose_f(mainout_dset_id_rad , i_stat)
2144  if (i_stat .ne. 0) call raise_exception("Unable to close radius dataset.",&
2145  "hdf5_module_finalize",240007)
2146  call h5dclose_f(mainout_dset_id_ye , i_stat)
2147  if (i_stat .ne. 0) call raise_exception("Unable to close electron fraction dataset.",&
2148  "hdf5_module_finalize",240007)
2149  call h5dclose_f(mainout_dset_id_iter , i_stat)
2150  if (i_stat .ne. 0) call raise_exception("Unable to close iteration dataset.",&
2151  "hdf5_module_finalize",240007)
2152  call h5dclose_f(mainout_dset_id_ylight, i_stat)
2153  if (i_stat .ne. 0) call raise_exception("Unable to close ylight dataset.",&
2154  "hdf5_module_finalize",240007)
2155  call h5dclose_f(mainout_dset_id_yheavy, i_stat)
2156  if (i_stat .ne. 0) call raise_exception("Unable to close yheavy dataset.",&
2157  "hdf5_module_finalize",240007)
2158  call h5dclose_f(mainout_dset_id_yn , i_stat)
2159  if (i_stat .ne. 0) call raise_exception("Unable to close yn dataset.",&
2160  "hdf5_module_finalize",240007)
2161  call h5dclose_f(mainout_dset_id_yp , i_stat)
2162  if (i_stat .ne. 0) call raise_exception("Unable to close yp dataset.",&
2163  "hdf5_module_finalize",240007)
2164  call h5dclose_f(mainout_dset_id_ya , i_stat)
2165  if (i_stat .ne. 0) call raise_exception("Unable to close ya dataset.",&
2166  "hdf5_module_finalize",240007)
2167  end if
2168 
2169  ! Cleanup tracked nuclei
2170  if (h_track_nuclei_every .gt. 0) then
2171  call write_track_data() ! Write the last datapoints
2172  call h5gclose_f(track_group_id , i_stat)
2173  if (i_stat .ne. 0) call raise_exception("Unable to close track_nuclei group.",&
2174  "hdf5_module_finalize",240017)
2175  call h5dclose_f(tracked_dset_id_t , i_stat)
2176  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2177  "hdf5_module_finalize",240007)
2178  call h5dclose_f(tracked_abu_id , i_stat)
2179  if (i_stat .ne. 0) call raise_exception("Unable to close tracked abundance dataset.",&
2180  "hdf5_module_finalize",240007)
2181  end if
2182 
2183  ! Cleanup neutrino loss/gain
2184  if ((h_nu_loss_every .gt. 0)) then
2185  call write_nu_loss_gain()
2186  call h5gclose_f(nuloss_group_id , i_stat)
2187  if (i_stat .ne. 0) call raise_exception("Unable to close nuloss group.",&
2188  "hdf5_module_finalize",240017)
2189  call h5dclose_f(nuloss_dset_id_t , i_stat)
2190  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2191  "hdf5_module_finalize",240007)
2192  call h5dclose_f(nuloss_dset_id_bet , i_stat)
2193  if (i_stat .ne. 0) call raise_exception("Unable to close beta dataset.",&
2194  "hdf5_module_finalize",240007)
2195  call h5dclose_f(nuloss_dset_id_dens , i_stat)
2196  if (i_stat .ne. 0) call raise_exception("Unable to close density dataset.",&
2197  "hdf5_module_finalize",240007)
2198  call h5dclose_f(nuloss_dset_id_heat , i_stat)
2199  if (i_stat .ne. 0) call raise_exception("Unable to close heat dataset.",&
2200  "hdf5_module_finalize",240007)
2201  call h5dclose_f(nuloss_dset_id_nut , i_stat)
2202  if (i_stat .ne. 0) call raise_exception("Unable to close nu total dataset.",&
2203  "hdf5_module_finalize",240007)
2204  call h5dclose_f(nuloss_dset_id_rad , i_stat)
2205  if (i_stat .ne. 0) call raise_exception("Unable to close radius dataset.",&
2206  "hdf5_module_finalize",240007)
2207  call h5dclose_f(nuloss_dset_id_temp , i_stat)
2208  if (i_stat .ne. 0) call raise_exception("Unable to close temperature dataset.",&
2209  "hdf5_module_finalize",240007)
2210  call h5dclose_f(nuloss_dset_id_the , i_stat)
2211  if (i_stat .ne. 0) call raise_exception("Unable to close thermal dataset.",&
2212  "hdf5_module_finalize",240007)
2213  end if
2214 
2215  ! Cleanup average timescales
2216  if (h_timescales_every .gt. 0) then
2217  call write_av_timescales() ! Write the last datapoints
2218  call h5gclose_f(ts_group_id , i_stat)
2219  if (i_stat .ne. 0) call raise_exception("Unable to close timescale group.",&
2220  "hdf5_module_finalize",240017)
2221  call h5dclose_f(ts_dset_id_t , i_stat)
2222  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2223  "hdf5_module_finalize",240007)
2224  do i=1,17
2225  call h5dclose_f(ts_reac_ids(i) , i_stat)
2226  if (i_stat .ne. 0) call raise_exception("Unable to close timescale dataset.",&
2227  "hdf5_module_finalize",240007)
2228  end do
2229  end if
2230 
2231  ! Cleanup energy generation output
2232  if (h_engen_every .gt. 0) then
2233  call write_engen(h_engen_detailed) ! Write the last datapoints
2234  call h5gclose_f(en_group_id , i_stat)
2235  if (i_stat .ne. 0) call raise_exception("Unable to close energy group.",&
2236  "hdf5_module_finalize",240017)
2237  call h5dclose_f(en_dset_id_t , i_stat)
2238  if (i_stat .ne. 0) call raise_exception("Unable to close time dataset.",&
2239  "hdf5_module_finalize",240007)
2240  do i=1,10
2241  call h5dclose_f(en_reac_ids(i) , i_stat)
2242  if (i_stat .ne. 0) call raise_exception("Unable to close engen dataset.",&
2243  "hdf5_module_finalize",240007)
2244  end do
2245  if (h_engen_detailed .eqv. .true.) then
2246  call h5dclose_f(en_det_bet_id , i_stat)
2247  if (i_stat .ne. 0) call raise_exception("Unable to close decay energy dataset.",&
2248  "hdf5_module_finalize",240007)
2249  call h5dclose_f(en_det_ag_id , i_stat)
2250  if (i_stat .ne. 0) call raise_exception("Unable to close (a,g) energy dataset.",&
2251  "hdf5_module_finalize",240007)
2252  call h5dclose_f(en_det_pg_id , i_stat)
2253  if (i_stat .ne. 0) call raise_exception("Unable to close (p,g) energy dataset.",&
2254  "hdf5_module_finalize",240007)
2255  call h5dclose_f(en_det_ng_id , i_stat)
2256  if (i_stat .ne. 0) call raise_exception("Unable to close (n,g) energy dataset.",&
2257  "hdf5_module_finalize",240007)
2258  call h5dclose_f(en_det_pn_id , i_stat)
2259  if (i_stat .ne. 0) call raise_exception("Unable to close (p,n) energy dataset.",&
2260  "hdf5_module_finalize",240007)
2261  call h5dclose_f(en_det_ap_id , i_stat)
2262  if (i_stat .ne. 0) call raise_exception("Unable to close (a,p) energy dataset.",&
2263  "hdf5_module_finalize",240007)
2264  call h5dclose_f(en_det_an_id , i_stat)
2265  if (i_stat .ne. 0) call raise_exception("Unable to close (a,n) energy dataset.",&
2266  "hdf5_module_finalize",240007)
2267  call h5dclose_f(en_det_other_id , i_stat)
2268  if (i_stat .ne. 0) call raise_exception("Unable to close other energy dataset.",&
2269  "hdf5_module_finalize",240007)
2270  call h5dclose_f(en_det_fiss_id , i_stat)
2271  if (i_stat .ne. 0) call raise_exception("Unable to close fiss energy dataset.",&
2272  "hdf5_module_finalize",240007)
2273  call h5dclose_f(en_det_tot_id , i_stat)
2274  if (i_stat .ne. 0) call raise_exception("Unable to close tot energy dataset.",&
2275  "hdf5_module_finalize",240007)
2276  end if
2277 
2278  end if
2279 
2280  ! Cleanup flow
2281  if (h_flow_every .gt. 0) then
2282  call h5gclose_f(flow_group_id, i_stat)
2283  if (i_stat .ne. 0) call raise_exception("Unable to close flow group.",&
2284  "hdf5_module_finalize",240017)
2285  end if
2286 
2287  ! Close all other helper variables
2288  call h5fclose_f(file_id , i_stat)
2289  if (i_stat .ne. 0) call raise_exception("Unable to close hdf5 file.",&
2290  "hdf5_module_finalize",240018)
2291 
2292  call h5pclose_f(crp_list , i_stat)
2293  if (i_stat .ne. 0) call raise_exception("Unable to close property list.",&
2294  "hdf5_module_finalize",240019)
2295  end subroutine hdf5_module_finalize
2296 
2297 #endif
2298 
2299 end module hdf5_module
hdf5_module::mainout_dsetname_temp
character(len= *), parameter, private mainout_dsetname_temp
Name of the dataset.
Definition: hdf5_module.f90:95
parameter_class::h_track_nuclei_every
integer h_track_nuclei_every
frequency of track nuclei output in hdf5 format
Definition: parameter_class.f90:74
hdf5_module::chunk_store_mainout
real(r_kind), dimension(chunk_size_mainout, 13), private chunk_store_mainout
Storage for the chunk which is later written to the file.
Definition: hdf5_module.f90:82
hdf5_module::nuloss_group_id
integer(hid_t), private nuloss_group_id
The ID of the group.
Definition: hdf5_module.f90:222
hdf5_module::write_nu_loss_gain
subroutine, private write_nu_loss_gain
Write the neutrino loss/gain into the hdf5 file.
Definition: hdf5_module.f90:454
hdf5_module::chunk_size_ts
integer, parameter, private chunk_size_ts
Chunk size.
Definition: hdf5_module.f90:157
hdf5_module::en_det_pn_id
integer(hid_t), private en_det_pn_id
Definition: hdf5_module.f90:205
hdf5_module::snaps_dset_id_t
integer(hid_t), private snaps_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:72
hdf5_module
Module that contains necessary subroutines to write abundances to an hdf5 file.
Definition: hdf5_module.f90:24
hdf5_module::write_engen
subroutine, private write_engen(include_decay)
Write energy generations and time into the hdf5 file.
Definition: hdf5_module.f90:722
hdf5_module::nuloss_dset_id_t
integer(hid_t), private nuloss_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:239
hdf5_module::mainout_dsetname_ye
character(len= *), parameter, private mainout_dsetname_ye
Name of the dataset.
Definition: hdf5_module.f90:107
hdf5_module::chunk_store_nuloss_bet
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_bet
Definition: hdf5_module.f90:228
global_class::net_names
character *5, dimension(:), allocatable, public net_names
list of isotopes contained in the network
Definition: global_class.f90:95
hdf5_module::chunk_store_en_ng
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_ng
Definition: hdf5_module.f90:182
hdf5_module::chunk_store_en_pn
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_pn
Definition: hdf5_module.f90:182
global_class::ipro
integer, public ipro
index of alphas, neutrons and protons
Definition: global_class.f90:94
hdf5_module::init_track_nuclei
subroutine, private init_track_nuclei
Initialize the tracked_nuclei hdf5 group.
Definition: hdf5_module.f90:1035
hdf5_module::en_det_bet_id
integer(hid_t), private en_det_bet_id
Definition: hdf5_module.f90:205
hdf5_module::ts_reac_ids
integer(hid_t), dimension(17), private ts_reac_ids
Dataset identifier.
Definition: hdf5_module.f90:170
hdf5_module::nuloss_dsetname_nut
character(len= *), parameter, private nuloss_dsetname_nut
Name of the dataset.
Definition: hdf5_module.f90:250
hdf5_module::init_flow
subroutine, private init_flow
Initialize the flow output.
Definition: hdf5_module.f90:367
hdf5_module::chunk_store_nuloss_nut
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_nut
Definition: hdf5_module.f90:228
hdf5_module::en_det_ap_name
character(len=14), private en_det_ap_name
Definition: hdf5_module.f90:199
hdf5_module::flow_dsetname_t
character(len= *), parameter, private flow_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:217
hdf5_module::hdf5_output
logical, private hdf5_output
Definition: hdf5_module.f90:41
hdf5_module::extend_snaps
subroutine, public extend_snaps(time, Y_array)
Write abundances and time into the hdf5 file.
Definition: hdf5_module.f90:1872
hdf5_module::mainout_dsetname_abar
character(len= *), parameter, private mainout_dsetname_abar
Name of the dataset.
Definition: hdf5_module.f90:125
hdf5_module::mainout_dsetname_rad
character(len= *), parameter, private mainout_dsetname_rad
Name of the dataset.
Definition: hdf5_module.f90:104
parameter_class::h_timescales_every
integer h_timescales_every
timescales output frequency in hdf5 format
Definition: parameter_class.f90:67
hdf5_module::extend_engen
subroutine, public extend_engen(time, engen_tot, heat, engen_ng_gn, engen_pg_gp, engen_ag_ga, engen_np_pn, engen_an_na, engen_ap_pa, engen_beta, engen_fiss, det_bet_engen, det_ag_engen, det_pg_engen, det_ng_engen, det_pn_engen, det_ap_engen, det_an_engen, det_other_engen, det_fiss_engen, det_tot_engen, include_decay)
Subroutine to write the energy generation per reaction type.
Definition: hdf5_module.f90:665
hdf5_module::mainout_dsetname_ylight
character(len= *), parameter, private mainout_dsetname_ylight
Name of the dataset.
Definition: hdf5_module.f90:119
hdf5_module::chunk_counter_mainout
integer, private chunk_counter_mainout
How full is the chunk already?
Definition: hdf5_module.f90:80
hdf5_module::create_1d_dataset
integer(hsize_t) function, private create_1d_dataset(dsetname, group_id)
Gets a dataset name and creates it.
Definition: hdf5_module.f90:1404
hdf5_module::chunk_counter_snaps
integer, private chunk_counter_snaps
How full is the chunk already?
Definition: hdf5_module.f90:57
hdf5_module::nuloss_dset_id_the
integer(hid_t), private nuloss_dset_id_the
Dataset identifier.
Definition: hdf5_module.f90:257
parameter_class::h_flow_every
integer h_flow_every
flow output frequency in hdf5 format
Definition: parameter_class.f90:65
error_msg_class
Error handling routines.
Definition: error_msg_class.f90:16
hdf5_module::mainout_dset_id_yp
integer(hid_t), private mainout_dset_id_yp
Dataset identifier.
Definition: hdf5_module.f90:114
global_class::ihe4
integer, public ihe4
Definition: global_class.f90:94
hdf5_module::en_det_ag_name
character(len=14), private en_det_ag_name
Definition: hdf5_module.f90:199
hdf5_module::iter_tracked
integer, private iter_tracked
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:134
hdf5_module::nuloss_dsetname_rad
character(len= *), parameter, private nuloss_dsetname_rad
Name of the dataset.
Definition: hdf5_module.f90:247
hdf5_module::chunk_store_track
real(r_kind), dimension(:,:), allocatable, private chunk_store_track
Temporary storage for tracked nuclei.
Definition: hdf5_module.f90:139
hdf5_module::flow_group_id
integer(hid_t), private flow_group_id
The ID of the group.
Definition: hdf5_module.f90:212
hdf5_module::create_1d_int_dataset
integer(hsize_t) function, private create_1d_int_dataset(dsetname, group_id)
Gets a dataset name and creates an integer dataset.
Definition: hdf5_module.f90:1466
global_class::flow_vector
Flow type to store flows.
Definition: global_class.f90:85
hdf5_module::dset_id_y
integer(hid_t), private dset_id_y
Dataset identifier.
Definition: hdf5_module.f90:67
hdf5_module::chunk_size_track
integer, parameter, private chunk_size_track
Chunk size.
Definition: hdf5_module.f90:138
hdf5_module::en_det_ng_id
integer(hid_t), private en_det_ng_id
Definition: hdf5_module.f90:205
hdf5_module::nuloss_dsetname_the
character(len= *), parameter, private nuloss_dsetname_the
Name of the dataset.
Definition: hdf5_module.f90:256
hdf5_module::tracked_dsetname_t
character(len= *), parameter, private tracked_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:143
hdf5_module::maxdims
integer(hsize_t), dimension(1:2), private maxdims
Maximum dimensions (later set to unlimited)
Definition: hdf5_module.f90:49
hdf5_module::chunk_size_nuloss
integer, parameter, private chunk_size_nuloss
Chunk size.
Definition: hdf5_module.f90:227
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
hdf5_module::chunk_store_snaps_y
real(r_kind), dimension(:,:), allocatable, private chunk_store_snaps_y
Storage for the chunk which is later written to the file.
Definition: hdf5_module.f90:62
hdf5_module::en_reac_ids
integer(hid_t), dimension(10), private en_reac_ids
Dataset identifier.
Definition: hdf5_module.f90:197
hdf5_module::iter_snaps
integer, private iter_snaps
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:54
hdf5_module::nuloss_dset_id_heat
integer(hid_t), private nuloss_dset_id_heat
Dataset identifier.
Definition: hdf5_module.f90:260
hdf5_module::nuloss_dset_id_bet
integer(hid_t), private nuloss_dset_id_bet
Dataset identifier.
Definition: hdf5_module.f90:254
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
hdf5_module::en_det_tot_id
integer(hid_t), private en_det_tot_id
Definition: hdf5_module.f90:205
hdf5_module::ts_dsetname_t
character(len= *), parameter, private ts_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:162
hdf5_module::en_det_an_id
integer(hid_t), private en_det_an_id
Definition: hdf5_module.f90:205
hdf5_module::init_hdf5_module
subroutine, public init_hdf5_module()
Initialize the hdf5 module.
Definition: hdf5_module.f90:293
hdf5_module::mainout_group_id
integer(hid_t), private mainout_group_id
The ID of the group.
Definition: hdf5_module.f90:76
hdf5_module::iter_mainout
integer, private iter_mainout
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:77
hdf5_module::mainout_dsetname_t
character(len= *), parameter, private mainout_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:92
flow
Definition: flow.py:1
hdf5_module::mainout_dsetname_dens
character(len= *), parameter, private mainout_dsetname_dens
Name of the dataset.
Definition: hdf5_module.f90:98
hdf5_module::init_av_timescales
subroutine, private init_av_timescales
Initialize the timescales hdf5 group.
Definition: hdf5_module.f90:1131
hdf5_module::dims_track
integer(hsize_t), dimension(1:2), private dims_track
Array dimensions.
Definition: hdf5_module.f90:146
hdf5_module::en_det_pn_name
character(len=14), private en_det_pn_name
Definition: hdf5_module.f90:199
hdf5_module::chunk_size_en
integer, parameter, private chunk_size_en
Chunk size.
Definition: hdf5_module.f90:179
hdf5_module::chunk_store_en_ag
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_ag
Definition: hdf5_module.f90:182
hdf5_module::write_track_data
subroutine, private write_track_data()
Write the abundances of track nuclei into a file.
Definition: hdf5_module.f90:1845
hdf5_module::chunk_counter_ts
integer, private chunk_counter_ts
How full is the chunk already?
Definition: hdf5_module.f90:156
hdf5_module::en_dset_id_t
integer(hid_t), private en_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:190
global_class::ineu
integer, public ineu
Definition: global_class.f90:94
hdf5_module::mainout_dsetname_ya
character(len= *), parameter, private mainout_dsetname_ya
Name of the dataset.
Definition: hdf5_module.f90:116
parameter_class::h_finab
logical h_finab
Store the finab in hdf5 format rather than in ascii format.
Definition: parameter_class.f90:146
hdf5_module::en_det_ag_id
integer(hid_t), private en_det_ag_id
Definition: hdf5_module.f90:205
global_class::track_nuclei_indices
integer, dimension(:), allocatable, public track_nuclei_indices
Variables related to tracking individual nuclei.
Definition: global_class.f90:37
hdf5_module::dims_y
integer(hsize_t), dimension(1:2), private dims_y
Array dimensions (net_size)
Definition: hdf5_module.f90:69
global_class::isotope
type(isotope_type), dimension(:), allocatable, public isotope
all nuclides used in the network
Definition: global_class.f90:34
hdf5_module::mainout_dset_id_temp
integer(hid_t), private mainout_dset_id_temp
Dataset identifier.
Definition: hdf5_module.f90:96
hdf5_module::create_constant_1d_arrays
subroutine, private create_constant_1d_arrays(length, data, dsetname, group_id)
Create a hdf5 entry with constant values.
Definition: hdf5_module.f90:1583
hdf5_module::nuloss_dsetname_bet
character(len= *), parameter, private nuloss_dsetname_bet
Name of the dataset.
Definition: hdf5_module.f90:253
hdf5_module::chunk_store_nuloss_temp
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_temp
Definition: hdf5_module.f90:228
hdf5_module::en_det_fiss_name
character(len=14), private en_det_fiss_name
Definition: hdf5_module.f90:199
hdf5_module::ts_names
character(len=9), dimension(17), private ts_names
Names of the timescales.
Definition: hdf5_module.f90:165
hdf5_module::mainout_dset_id_rad
integer(hid_t), private mainout_dset_id_rad
Dataset identifier.
Definition: hdf5_module.f90:105
hdf5_module::iter_flow
integer, private iter_flow
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:213
hdf5_module::dsetname_u
character(len= *), parameter, private dsetname_u
Name of the units dataset.
Definition: hdf5_module.f90:43
hdf5_module::en_names
character(len=11), dimension(10), private en_names
Name of the energy generations.
Definition: hdf5_module.f90:192
hdf5_module::write_snaps
subroutine, private write_snaps()
Write the abundances of all nuclei into a file.
Definition: hdf5_module.f90:1897
hdf5_module::init_nu_loss_gain
subroutine, private init_nu_loss_gain
Initialize neutrino loss/gain output.
Definition: hdf5_module.f90:383
hdf5_module::mainout_dset_id_ye
integer(hid_t), private mainout_dset_id_ye
Dataset identifier.
Definition: hdf5_module.f90:108
hdf5_module::mainout_dset_id_t
integer(hid_t), private mainout_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:93
hdf5_module::chunk_store_en_an
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_an
Definition: hdf5_module.f90:182
hdf5_module::nuloss_dsetname_dens
character(len= *), parameter, private nuloss_dsetname_dens
Name of the dataset.
Definition: hdf5_module.f90:244
hdf5_module::snaps_group_id
integer(hid_t), private snaps_group_id
The ID of the group.
Definition: hdf5_module.f90:53
hdf5_module::mainout_dsetname_yheavy
character(len= *), parameter, private mainout_dsetname_yheavy
Name of the dataset.
Definition: hdf5_module.f90:122
hdf5_module::write_finab
subroutine, public write_finab(Y)
Write final abundances into hdf5 file.
Definition: hdf5_module.f90:1217
hdf5_module::chunk_store_nuloss_dens
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_dens
Definition: hdf5_module.f90:228
hdf5_module::extend_flow
subroutine, public extend_flow(time, temp, dens, flow, n_flows, Y)
Extend the flow in the file With every call a new group is created and the flows are written in this ...
Definition: hdf5_module.f90:762
parameter_class::h_nu_loss_every
integer h_nu_loss_every
Output neutrino loss and gain in hdf5 format.
Definition: parameter_class.f90:101
hdf5_module::chunk_counter_en
integer, private chunk_counter_en
How full is the chunk already?
Definition: hdf5_module.f90:178
hdf5_module::en_det_pg_name
character(len=14), private en_det_pg_name
Definition: hdf5_module.f90:199
parameter_class::h_engen_detailed
logical h_engen_detailed
Output the energy per parent nucleus and reaction type.
Definition: parameter_class.f90:122
hdf5_module::en_dsetname_t
character(len= *), parameter, private en_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:189
hdf5_module::en_det_ng_name
character(len=14), private en_det_ng_name
Definition: hdf5_module.f90:199
hdf5_module::en_det_ap_id
integer(hid_t), private en_det_ap_id
Definition: hdf5_module.f90:205
hdf5_module::hdf5_filename
character(len=20), private hdf5_filename
Name of the hdf5 file.
Definition: hdf5_module.f90:38
hdf5_module::track_group_id
integer(hid_t), private track_group_id
The ID of the group.
Definition: hdf5_module.f90:133
hdf5_module::nuloss_dset_id_temp
integer(hid_t), private nuloss_dset_id_temp
Dataset identifier.
Definition: hdf5_module.f90:242
hdf5_module::nuloss_dsetname_t
character(len= *), parameter, private nuloss_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:238
hdf5_module::en_det_an_name
character(len=14), private en_det_an_name
Definition: hdf5_module.f90:199
hdf5_module::chunk_store_nuloss_heat
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_heat
Definition: hdf5_module.f90:228
hdf5_module::chunk_store_en
real(r_kind), dimension(chunk_size_en, 11), private chunk_store_en
Temporary storage for energy generation.
Definition: hdf5_module.f90:180
hdf5_module::extend_1d_int_dataset
subroutine, private extend_1d_int_dataset(dset_id, value, in_size, chunksize)
Extend a previously created 1D integer - dataset.
Definition: hdf5_module.f90:1699
hdf5_module::extend_nu_loss_gain
subroutine, public extend_nu_loss_gain(time, temp, dens, rad, the, heat, bet)
Write neutrino gain and loss.
Definition: hdf5_module.f90:415
global_class::net_size
integer, public net_size
total number of isotopes (network size)
Definition: global_class.f90:93
hdf5_module::iter_ts
integer, private iter_ts
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:153
hdf5_module::dims_1d
integer(hsize_t), dimension(1), private dims_1d
Helper variable to specify 1 dimension.
Definition: hdf5_module.f90:46
hdf5_module::mainout_dset_id_yheavy
integer(hid_t), private mainout_dset_id_yheavy
Dataset identifier.
Definition: hdf5_module.f90:123
hdf5_module::init_snaps
subroutine, private init_snaps
Initialize the snapshot hdf5 group.
Definition: hdf5_module.f90:884
hdf5_module::file_id
integer(hid_t), private file_id
File identifier.
Definition: hdf5_module.f90:37
hdf5_module::chunk_store_nuloss_t
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_t
Definition: hdf5_module.f90:228
hdf5_module::tracked_dsetname_y
character(len= *), parameter, private tracked_dsetname_y
Name of the dataset.
Definition: hdf5_module.f90:149
hdf5_module::crp_list
integer(hid_t), private crp_list
Dataset creation property identifier.
Definition: hdf5_module.f90:48
hdf5_module::chunk_store_en_tot
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_tot
Definition: hdf5_module.f90:182
hdf5_module::nuloss_dset_id_rad
integer(hid_t), private nuloss_dset_id_rad
Dataset identifier.
Definition: hdf5_module.f90:248
hdf5_module::en_det_other_id
integer(hid_t), private en_det_other_id
Definition: hdf5_module.f90:205
hdf5_module::init_engen
subroutine, private init_engen(include_decay)
Initialize energy generation output.
Definition: hdf5_module.f90:478
hdf5_module::nuloss_dsetname_temp
character(len= *), parameter, private nuloss_dsetname_temp
Name of the dataset.
Definition: hdf5_module.f90:241
hdf5_module::mainout_dset_id_dens
integer(hid_t), private mainout_dset_id_dens
Dataset identifier.
Definition: hdf5_module.f90:99
hdf5_module::extend_1d_dataset
subroutine, private extend_1d_dataset(dset_id, value, in_size, chunksize)
Extend a previously created 1D - dataset.
Definition: hdf5_module.f90:1641
hdf5_module::dataspace
integer(hid_t), private dataspace
Dataspace identifier.
Definition: hdf5_module.f90:47
hdf5_module::en_det_other_name
character(len=14), private en_det_other_name
Definition: hdf5_module.f90:199
global_class::track_nuclei_nr
integer, public track_nuclei_nr
amount of tracked nuclei
Definition: global_class.f90:38
hdf5_module::mainout_dset_id_abar
integer(hid_t), private mainout_dset_id_abar
Dataset identifier.
Definition: hdf5_module.f90:126
r_kind
#define r_kind
Definition: macros.h:46
hdf5_module::en_det_fiss_id
integer(hid_t), private en_det_fiss_id
Definition: hdf5_module.f90:205
hdf5_module::chunk_store_en_ap
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_ap
Definition: hdf5_module.f90:182
parameter_class::h_mainout_every
integer h_mainout_every
HDF5 output frequency of the mainout.
Definition: parameter_class.f90:72
hdf5_module::en_group_id
integer(hid_t), private en_group_id
The ID of the group.
Definition: hdf5_module.f90:174
hdf5_module::finab_group_id
integer(hid_t), private finab_group_id
The ID of the group.
Definition: hdf5_module.f90:264
hdf5_module::chunk_store_int_mainout
integer, dimension(chunk_size_mainout), private chunk_store_int_mainout
Storage for integers in chunk which is later written to the file.
Definition: hdf5_module.f90:85
parameter_class::h_custom_snapshots
logical h_custom_snapshots
Same, but in hdf5 format.
Definition: parameter_class.f90:108
hdf5_module::write_av_timescales
subroutine, private write_av_timescales()
Write average timescales and time into the hdf5 file.
Definition: hdf5_module.f90:1790
hdf5_module::init_mainout
subroutine, private init_mainout
Initialize the mainout hdf5 group.
Definition: hdf5_module.f90:988
hdf5_module::mainout_dset_id_entr
integer(hid_t), private mainout_dset_id_entr
Dataset identifier.
Definition: hdf5_module.f90:102
hdf5_module::chunk_store_ts
real(r_kind), dimension(chunk_size_ts, 18), private chunk_store_ts
Temporary storage for average timescales.
Definition: hdf5_module.f90:158
hdf5_module::create_constant_1d_int_arrays
subroutine, private create_constant_1d_int_arrays(length, data, dsetname, group_id)
Create a hdf5 entry with constant values.
Definition: hdf5_module.f90:1526
hdf5_module::mainout_dsetname_iter
character(len= *), parameter, private mainout_dsetname_iter
Name of the dataset.
Definition: hdf5_module.f90:89
hdf5_module::en_det_pg_id
integer(hid_t), private en_det_pg_id
Definition: hdf5_module.f90:205
hdf5_module::chunk_size_mainout
integer, parameter, private chunk_size_mainout
Chunk size.
Definition: hdf5_module.f90:81
hdf5_module::iter_en
integer, private iter_en
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:175
hdf5_module::chunk_size_snaps
integer, parameter, private chunk_size_snaps
Chunk size.
Definition: hdf5_module.f90:58
hdf5_module::mainout_dsetname_yn
character(len= *), parameter, private mainout_dsetname_yn
Name of the dataset.
Definition: hdf5_module.f90:110
hdf5_module::mainout_dset_id_ya
integer(hid_t), private mainout_dset_id_ya
Dataset identifier.
Definition: hdf5_module.f90:117
hdf5_module::dsetname_y
character(len= *), parameter, private dsetname_y
Name of the dataset.
Definition: hdf5_module.f90:68
hdf5_module::nuloss_dset_id_dens
integer(hid_t), private nuloss_dset_id_dens
Dataset identifier.
Definition: hdf5_module.f90:245
hdf5_module::write_mainout_data
subroutine, private write_mainout_data()
Write the mainout data into a file.
Definition: hdf5_module.f90:1991
hdf5_module::snaps_dsetname_t
character(len= *), parameter, private snaps_dsetname_t
Name of the dataset.
Definition: hdf5_module.f90:71
hdf5_module::chunk_counter_track
integer, private chunk_counter_track
How full is the chunk already?
Definition: hdf5_module.f90:137
hdf5_module::nuloss_dsetname_heat
character(len= *), parameter, private nuloss_dsetname_heat
Name of the dataset.
Definition: hdf5_module.f90:259
hdf5_module::chunk_store_en_fiss
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_fiss
Definition: hdf5_module.f90:182
hdf5_module::chunk_counter_nuloss
integer, private chunk_counter_nuloss
How full is the chunk already?
Definition: hdf5_module.f90:226
hdf5_module::extend_track_nuclei
subroutine, public extend_track_nuclei(time, Y_array)
Write tracked abundances and time into the hdf5 file.
Definition: hdf5_module.f90:1813
hdf5_module::mainout_dsetname_yp
character(len= *), parameter, private mainout_dsetname_yp
Name of the dataset.
Definition: hdf5_module.f90:113
hdf5_module::chunk_store_snaps_time
real(r_kind), dimension(chunk_size_snaps), private chunk_store_snaps_time
Storage for the chunk which is later written to the file.
Definition: hdf5_module.f90:59
hdf5_module::hdf5_module_finalize
subroutine, public hdf5_module_finalize()
Finalize the hdf5 module.
Definition: hdf5_module.f90:2097
hdf5_module::extend_av_timescales
subroutine, public extend_av_timescales(time, tau_ga, tau_ag, tau_ng, tau_gn, tau_pg, tau_gp, tau_np, tau_pn, tau_an, tau_na, tau_ap, tau_pa, tau_beta, tau_alpha, tau_nfiss, tau_sfiss, tau_bfiss)
Subroutine to write the average timescales (1/s) into the hdf5.
Definition: hdf5_module.f90:1759
hdf5_module::mainout_dset_id_iter
integer(hid_t), private mainout_dset_id_iter
Dataset identifier.
Definition: hdf5_module.f90:90
global_class
Contains types and objects shared between multiple modules.
Definition: global_class.f90:19
hdf5_module::chunk_store_en_other
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_other
Definition: hdf5_module.f90:182
hdf5_module::ts_dset_id_t
integer(hid_t), private ts_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:163
parameter_class::h_snapshot_every
integer h_snapshot_every
snapshot output frequency in hdf5 format
Definition: parameter_class.f90:63
hdf5_module::iter_nuloss
integer, private iter_nuloss
Iteration count, how often was already extended to the datasets?
Definition: hdf5_module.f90:223
hdf5_module::mainout_dsetname_zbar
character(len= *), parameter, private mainout_dsetname_zbar
Name of the dataset.
Definition: hdf5_module.f90:128
hdf5_module::tracked_names
character(len=5), dimension(:), allocatable, private tracked_names
Names of the tracked nuclei.
Definition: hdf5_module.f90:147
hdf5_module::en_det_bet_name
character(len=14), private en_det_bet_name
Definition: hdf5_module.f90:199
hdf5_module::extend_mainout
subroutine, public extend_mainout(cnt, time, temp, dens, entr, rad, Y)
Write the mainout data to the hdf5.
Definition: hdf5_module.f90:1923
hdf5_module::chunk_store_nuloss_rad
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_rad
Definition: hdf5_module.f90:228
hdf5_module::ts_group_id
integer(hid_t), private ts_group_id
The ID of the group.
Definition: hdf5_module.f90:152
hdf5_module::chunk_store_en_bet
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_bet
Definition: hdf5_module.f90:182
hdf5_module::mainout_dsetname_entr
character(len= *), parameter, private mainout_dsetname_entr
Name of the dataset.
Definition: hdf5_module.f90:101
hdf5_module::flow_dset_id_t
integer(hid_t), private flow_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:218
hdf5_module::write_units
subroutine, private write_units()
Write the units of the individual entries into the hdf5 file.
Definition: hdf5_module.f90:1163
hdf5_module::mainout_dset_id_zbar
integer(hid_t), private mainout_dset_id_zbar
Dataset identifier.
Definition: hdf5_module.f90:129
hdf5_module::nuloss_dset_id_nut
integer(hid_t), private nuloss_dset_id_nut
Dataset identifier.
Definition: hdf5_module.f90:251
parameter_class::h_engen_every
integer h_engen_every
Energy generation output frequency in hdf5 format.
Definition: parameter_class.f90:69
hdf5_module::tracked_dset_id_t
integer(hid_t), private tracked_dset_id_t
Dataset identifier.
Definition: hdf5_module.f90:144
hdf5_module::tracked_abu_id
integer(hid_t), private tracked_abu_id
Dataset identifier.
Definition: hdf5_module.f90:148
hdf5_module::mainout_dset_id_yn
integer(hid_t), private mainout_dset_id_yn
Dataset identifier.
Definition: hdf5_module.f90:111
hdf5_module::en_det_tot_name
character(len=14), private en_det_tot_name
Definition: hdf5_module.f90:199
parameter_class
Contains all runtime parameters as well as phys and math constants.
Definition: parameter_class.f90:24
hdf5_module::mainout_dset_id_ylight
integer(hid_t), private mainout_dset_id_ylight
Dataset identifier.
Definition: hdf5_module.f90:120
hdf5_module::extend_hdf5_y
subroutine, private extend_hdf5_y(dset_id, Y_array, nr_nuc, old_size, chunksize)
Extend the Y dataset for the net timestep.
Definition: hdf5_module.f90:2052
hdf5_module::chunk_store_en_pg
real(r_kind), dimension(:,:), allocatable, private chunk_store_en_pg
Definition: hdf5_module.f90:182
hdf5_module::chunk_store_nuloss_the
real(r_kind), dimension(chunk_size_nuloss), private chunk_store_nuloss_the
Definition: hdf5_module.f90:228