Write Deuterium-Tritium interaction cross sections to a HDF5 file
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer(kind=HID_T), | intent(inout) | :: | id | HDF5 file or group object id | ||
| character(len=*), | intent(in) | :: | namelist_file | Namelist file that contains settings | 
subroutine write_bb_D_T(id, namelist_file)
    !+ Write Deuterium-Tritium interaction cross sections to a HDF5 file
    integer(HID_T), intent(inout) :: id
        !+ HDF5 file or group object id
    character(len=*), intent(in)  :: namelist_file
        !+ Namelist file that contains settings
    integer :: nbranch = 1
    real(Float64) :: emin
    real(Float64) :: emax
    integer :: nenergy
    real(Float64) :: eb
    real(Float64) :: dlogE
    real(Float64), dimension(:), allocatable :: ebarr
    real(Float64), dimension(:,:), allocatable :: fusion
    integer(HID_T) :: gid
    integer(HSIZE_T), dimension(1) :: dim1
    integer(HSIZE_T), dimension(2) :: dim2
    integer :: i, cnt, error
    logical :: exis
    NAMELIST /D_T_cross/ nenergy, emin, emax
    nenergy = 200; emin = 1.d-3 ; emax = 8.d2
    inquire(file=namelist_file,exist=exis)
    if(.not.exis) then
        write(*,'(a,a)') 'WRITE_BB_D_T: Input file does not exist: ',trim(namelist_file)
        write(*,'(a)') 'Continuing with default settings...'
    else
        open(13,file=namelist_file)
        read(13,NML=D_T_cross)
        close(13)
    endif
    allocate(ebarr(nenergy))
    allocate(fusion(nenergy,nbranch))
    ebarr = 0.d0
    fusion = 0.d0
    write(*,'(a)') "---- D-T cross sections settings ----"
    write(*,'(T2,"Emin = ",e9.2, " keV")') emin
    write(*,'(T2,"Emax = ",e9.2, " keV")') emax
    write(*,'(T2,"Nenergy = ", i4)') nenergy
    write(*,*) ''
    cnt = 0
    dlogE = (log10(emax) - log10(emin))/(nenergy - 1)
    !$OMP PARALLEL DO private(i, eb)
    do i=1, nenergy
        eb = 10.d0**(log10(emin) + (i-1)*dlogE)
        ebarr(i) = eb
        fusion(i,1) = d_t_fusion(eb)
        cnt = cnt + 1
        WRITE(*,'(f7.2,"%",a,$)') 100*cnt/real(nenergy),char(13)
    enddo
    !$OMP END PARALLEL DO
    call h5gcreate_f(id, "D_T", gid, error)
    dim1 = [1]
    call h5ltmake_dataset_int_f(gid, "nbranch", 0, dim1, [nbranch], error)
    call h5ltmake_dataset_int_f(gid, "nenergy", 0, dim1, [nenergy], error)
    call h5ltmake_dataset_double_f(gid, "dlogE", 0, dim1, [dlogE], error)
    call h5ltmake_dataset_double_f(gid, "emin", 0, dim1, [emin], error)
    call h5ltmake_dataset_double_f(gid, "emax", 0, dim1, [emax], error)
    dim1 = [nenergy]
    dim2 = [nenergy, nbranch]
    call h5ltmake_compressed_dataset_double_f(gid, "energy", 1, dim1, ebarr, error)
    call h5ltmake_compressed_dataset_double_f(gid, "fusion", 2, dim2, fusion, error)
    call h5ltset_attribute_string_f(id, "D_T", "description", &
         "Cross sections for Deuterium-Tritium interactions", error)
    call h5ltset_attribute_string_f(gid, "nbranch", "description", &
         "Number of reaction branches", error)
    call h5ltset_attribute_string_f(gid, "nenergy", "description", &
         "Number of energy values", error)
    call h5ltset_attribute_string_f(gid, "energy", "description", &
         "Deuterium energy values", error)
    call h5ltset_attribute_string_f(gid, "energy", "units", "keV", error)
    call h5ltset_attribute_string_f(gid, "dlogE", "description", &
         "Energy spacing in log-10", error)
    call h5ltset_attribute_string_f(gid, "dlogE", "units", "log10(keV)", error)
    call h5ltset_attribute_string_f(gid, "emin","description", &
         "Minimum energy", error)
    call h5ltset_attribute_string_f(gid, "emin", "units", "keV", error)
    call h5ltset_attribute_string_f(gid, "emax","description", &
         "Maximum energy", error)
    call h5ltset_attribute_string_f(gid, "emax", "units", "keV", error)
    call h5ltset_attribute_string_f(gid, "fusion", "description", &
         "Total cross sections for D-T nuclear reactions: fusion(deuterium energy, branch)", error)
    call h5ltset_attribute_string_f(gid, "fusion", "units", "cm^2", error)
    call h5ltset_attribute_string_f(gid, "fusion", "reaction", &
         "D + T -> He4(3.5 MeV) + n(14.1 MeV)", error)
    call h5gclose_f(gid, error)
    deallocate(ebarr, fusion)
end subroutine write_bb_D_T