save_simulation_outputs Subroutine

public subroutine save_simulation_outputs(params, spp, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params

Core KORC simulation parameters.

type(SPECIES), intent(in), DIMENSION(:), ALLOCATABLE:: spp

An instance of KORC's derived type SPECIES containing all the information of different electron species. See korc_types.

type(FIELDS), intent(in) :: F

Calls

proc~~save_simulation_outputs~~CallsGraph proc~save_simulation_outputs save_simulation_outputs proc~rsave_2d_array_to_hdf5 rsave_2d_array_to_hdf5 proc~save_simulation_outputs->proc~rsave_2d_array_to_hdf5 interface~save_1d_array_to_hdf5 save_1d_array_to_hdf5 proc~save_simulation_outputs->interface~save_1d_array_to_hdf5 h5fclose_f h5fclose_f proc~save_simulation_outputs->h5fclose_f h5gclose_f h5gclose_f proc~save_simulation_outputs->h5gclose_f h5dclose_f h5dclose_f proc~rsave_2d_array_to_hdf5->h5dclose_f h5screate_simple_f h5screate_simple_f proc~rsave_2d_array_to_hdf5->h5screate_simple_f h5dwrite_f h5dwrite_f proc~rsave_2d_array_to_hdf5->h5dwrite_f h5sclose_f h5sclose_f proc~rsave_2d_array_to_hdf5->h5sclose_f proc~isave_1d_array_to_hdf5 isave_1d_array_to_hdf5 interface~save_1d_array_to_hdf5->proc~isave_1d_array_to_hdf5 proc~rsave_1d_array_to_hdf5 rsave_1d_array_to_hdf5 interface~save_1d_array_to_hdf5->proc~rsave_1d_array_to_hdf5 proc~isave_1d_array_to_hdf5->h5dclose_f proc~isave_1d_array_to_hdf5->h5screate_simple_f proc~isave_1d_array_to_hdf5->h5dwrite_f proc~isave_1d_array_to_hdf5->h5sclose_f h5tset_size_f h5tset_size_f proc~isave_1d_array_to_hdf5->h5tset_size_f h5aclose_f h5aclose_f proc~isave_1d_array_to_hdf5->h5aclose_f h5tcopy_f h5tcopy_f proc~isave_1d_array_to_hdf5->h5tcopy_f h5awrite_f h5awrite_f proc~isave_1d_array_to_hdf5->h5awrite_f h5acreate_f h5acreate_f proc~isave_1d_array_to_hdf5->h5acreate_f proc~rsave_1d_array_to_hdf5->h5dclose_f proc~rsave_1d_array_to_hdf5->h5screate_simple_f proc~rsave_1d_array_to_hdf5->h5dwrite_f proc~rsave_1d_array_to_hdf5->h5sclose_f proc~rsave_1d_array_to_hdf5->h5tset_size_f proc~rsave_1d_array_to_hdf5->h5aclose_f proc~rsave_1d_array_to_hdf5->h5tcopy_f proc~rsave_1d_array_to_hdf5->h5awrite_f proc~rsave_1d_array_to_hdf5->h5acreate_f

Called by

proc~~save_simulation_outputs~~CalledByGraph proc~save_simulation_outputs save_simulation_outputs program~main main program~main->proc~save_simulation_outputs

Contents


Source Code

  subroutine save_simulation_outputs(params,spp,F)
    !! @note Subroutine that saves the electrons' variables specified in
    !! params::outputs_list to HDF5 files. @endnote
    TYPE(KORC_PARAMS), INTENT(IN) 				:: params
    !! Core KORC simulation parameters.
    TYPE(SPECIES), DIMENSION(:), ALLOCATABLE, INTENT(IN) 	:: spp
    !! An instance of KORC's derived type SPECIES containing all
    !! the information
    !! of different electron species. See [[korc_types]].
    TYPE(FIELDS), INTENT(IN)                 :: F
    CHARACTER(MAX_STRING_LENGTH) 				:: filename
    !! String containing the name of the HDF5 file.
    CHARACTER(MAX_STRING_LENGTH) 				:: gname
    !! String containing the group name of a set of KORC parameters.
    CHARACTER(MAX_STRING_LENGTH) 				:: subgname
    !! String containing the subgroup name of a set of KORC parameters.
    CHARACTER(MAX_STRING_LENGTH) 				:: dset
    !! Name of data set to be saved to file.
    INTEGER(HID_T) 						:: h5file_id
    !! HDF5 file identifier.
    INTEGER(HID_T) 						:: group_id
    !! HDF5 group identifier.
    INTEGER(HID_T) 						:: subgroup_id
    !! HDF5 subgroup identifier.
    INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE 		:: dims
    !! Dimensions of data saved to HDF5 file.
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: rdata
    !! 1-D array of real data to be saved to HDF5 file.
    INTEGER, DIMENSION(:), ALLOCATABLE 				:: idata
    !!1-D array of integer data to be saved to HDF5 file.
    CHARACTER(MAX_STRING_LENGTH), DIMENSION(:), ALLOCATABLE       :: attr_array
    !! An 1-D array with attributes of 1-D real or integer arrays that are
    !! passed to KORC interfaces of HDF5 I/O subroutines.
    CHARACTER(MAX_STRING_LENGTH) 				:: attr
    !! A single attributes of real or integer data that is passed to KORC
    !! interfaces of HDF5 I/O subroutines.
    INTEGER 							:: h5error
    !!HDF5 error status.
    CHARACTER(19) 						:: tmp_str
    !!Temporary string used to manipulate various strings.
    REAL(rp) 						:: units
    !! Temporary variable used to add physical units to electrons' variables.
    INTEGER 						:: ss
    !! Electron species iterator.
    INTEGER 						:: jj
    !! Iterator for reading all the entried of params::outputs_list.
    LOGICAL 						:: object_exists
    !! Flag determining if a certain dataset is already present in
    !! the HDF5 output files.
    REAL(rp), DIMENSION(:,:), ALLOCATABLE  ::YY
    !! Temporary variable get proper units on vars%Y(1,:) and vars%Y(3,:), which
    !! are lengths, while keeping vars%Y(2,:), which is an angle

    if (params%mpi_params%rank .EQ. 0) then
       write(output_unit_write,'("Saving snapshot: ",I15)') &
            params%it/(params%t_skip)
       !write(output_unit_write,*) 'it',params%it,'t_skip',params%t_skip,'t_SC',params%t_it_SC
       
    end if

    if (SIZE(params%outputs_list).GT.1_idef) then
       write(tmp_str,'(I18)') params%mpi_params%rank
       filename = TRIM(params%path_to_outputs) // "file_" &
            // TRIM(ADJUSTL(tmp_str)) // ".h5"
       call h5fopen_f(TRIM(filename), H5F_ACC_RDWR_F, h5file_id, h5error)

       ! Create group 'it'
       write(tmp_str,'(I18)') params%it
       gname = TRIM(ADJUSTL(tmp_str))
       call h5lexists_f(h5file_id,TRIM(gname),object_exists,h5error)

       if (.NOT.object_exists) then ! Check if group does exist.
          call h5gcreate_f(h5file_id, TRIM(gname), group_id, h5error)

          dset = TRIM(gname) // "/time"
          attr = "Simulation time in secs"
          call save_to_hdf5(h5file_id,dset,params%init_time*params%cpp%time &
               + REAL(params%it,rp)*params%dt*params%cpp%time,attr)
          
          do ss=1_idef,params%num_species

             write(tmp_str,'(I18)') ss
             subgname = "spp_" // TRIM(ADJUSTL(tmp_str))
             call h5gcreate_f(group_id, TRIM(subgname), subgroup_id, h5error)

             do jj=1_idef,SIZE(params%outputs_list)
                SELECT CASE (TRIM(params%outputs_list(jj)))
                CASE ('X')
                   dset = "X"
                   units = params%cpp%length
                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%X)
                CASE ('Y')
                   dset = "Y"
                   units = params%cpp%length

                   YY=spp(ss)%vars%Y
                   YY(:,1)=units*YY(:,1)
                   YY(:,3)=units*YY(:,3)

                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        YY)

                   DEALLOCATE(YY)

                CASE('V')
                   dset = "V"
                   if (params%orbit_model(1:2).eq.'FO') then
                      units = params%cpp%velocity
                      call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                           units*spp(ss)%vars%V)
                   else if (params%orbit_model(1:2).eq.'GC') then
                      YY=spp(ss)%vars%V

                      YY(:,1)=YY(:,1)*params%cpp%mass*params%cpp%velocity
                      YY(:,2)=YY(:,2)*params%cpp%mass* &
                           (params%cpp%velocity)**2/params%cpp%Bo

                      call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                           YY)
                      DEALLOCATE(YY)

                   end if
                CASE('RHS')
                   dset = "RHS"
                   YY=spp(ss)%vars%RHS

                   units = params%cpp%length/params%cpp%time
                   YY(:,1)=YY(:,1)*units
                   YY(:,2)=YY(:,2)*units
                   YY(:,3)=YY(:,3)*units
                   units = params%cpp%mass*params%cpp%velocity/params%cpp%time
                   YY(:,4)=YY(:,4)*units
                   YY(:,5)=YY(:,5)*params%cpp%mass* &
                           (params%cpp%velocity)**2/params%cpp%Bo/params%cpp%time

                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        YY)
                   DEALLOCATE(YY)
                   
                CASE('Rgc')
                   dset = "Rgc"
                   units = params%cpp%length
                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%Rgc)
                CASE('g')
                   dset = "g"
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        spp(ss)%vars%g)
                CASE('eta')
                   dset = "eta"
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        spp(ss)%vars%eta)
                CASE('mu')
                   dset = "mu"
                   units = params%cpp%mass*params%cpp%velocity**2/params%cpp%Bo
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%mu)
                CASE('Prad')
                   dset = "Prad"
                   units = params%cpp%mass*(params%cpp%velocity**3)/ &
                        params%cpp%length
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%Prad)
                CASE('Pin')
                   dset = "Pin"
                   units = params%cpp%mass*(params%cpp%velocity**3)/ &
                        params%cpp%length
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%Pin)
                CASE('flagCon')
                   dset = "flagCon"
                   call save_1d_array_to_hdf5(subgroup_id,dset, &
                        INT(spp(ss)%vars%flagCon,idef))
                CASE('flagCol')
                   dset = "flagCol"
                   call save_1d_array_to_hdf5(subgroup_id,dset, &
                        INT(spp(ss)%vars%flagCol,idef))
                CASE('flagRE')
                   dset = "flagRE"
                   call save_1d_array_to_hdf5(subgroup_id,dset, &
                        INT(spp(ss)%vars%flagRE,idef))
                CASE('B')
                   dset = "B"
                   units = params%cpp%Bo
                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%B)
                CASE('gradB')
                   if (params%orbit_model(3:5).eq.'pre') then
                      dset = "gradB"
                      units = params%cpp%Bo/params%cpp%length
                      call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                           units*spp(ss)%vars%gradB)
                   end if
                CASE('curlb')
                   if (params%orbit_model(3:5).eq.'pre') then
                      dset = "curlb"
                      units = 1./params%cpp%length
                      call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                           units*spp(ss)%vars%curlb)
                   end if
                CASE('E')
                   dset = "E"
                   units = params%cpp%Eo
                   call rsave_2d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%E)
                   
                CASE('PSIp')
                   
                   dset = "PSIp"
                   if (.not.params%field_model.eq.'M3D_C1') then
                      units = params%cpp%Bo*params%cpp%length**2
                   else
                      units = 1._rp
                   end if
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%PSI_P)


                   
                CASE('AUX')
                   dset = "AUX"
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        spp(ss)%vars%AUX)
                CASE ('ne')
                   dset = "ne"
                   units = params%cpp%density
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%ne)
                CASE ('nimp')
                   dset = "nimp"
                   units = params%cpp%density
                   call save_2d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%nimp)
                CASE ('Te')
                   dset = "Te"
                   units = params%cpp%temperature
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        units*spp(ss)%vars%Te/C_E)
                CASE ('Zeff')
                   dset = "Zeff"
                   call save_1d_array_to_hdf5(subgroup_id, dset, &
                        spp(ss)%vars%Zeff)                   
                   
                CASE ('J_SC')

                   dset = "J_SC"
                   if (params%SC_E) then
                      call save_1d_array_to_hdf5(subgroup_id, dset, &
                           F%J1_SC_1D%PHI)
                   end if


                CASE ('A_SC')

                   dset = "A_SC"
                   if (params%SC_E) then
                      call save_1d_array_to_hdf5(subgroup_id, dset, &
                           F%A1_SC_1D%PHI)
                   end if

                CASE ('E_SC')

                   dset = "E_SC"
                   units = params%cpp%Eo
                   if (params%SC_E) then
                      call save_1d_array_to_hdf5(subgroup_id, dset, &
                           units*F%E_SC_1D%PHI)
                   end if

                CASE DEFAULT

                   
                END SELECT
             end do

             call h5gclose_f(subgroup_id, h5error)
          end do

          call h5gclose_f(group_id, h5error)
       end if ! Check if group does exist.

       call h5fclose_f(h5file_id, h5error)
    end if
  end subroutine save_simulation_outputs