save_restart_variables Subroutine

public subroutine save_restart_variables(params, spp, F)

Arguments

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

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

Contents


Source Code

  subroutine save_restart_variables(params,spp,F)
    !! @note Subroutine that saves all the variables that KORC needs for
    !! restarting a simulation. These variables are saved to "restart_file.h5".
    TYPE(KORC_PARAMS), INTENT(IN) 				:: params
    !! 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
    REAL(rp), DIMENSION(:), ALLOCATABLE :: send_buffer_rp, receive_buffer_rp
    !! Temporary buffer to be used by MPI to gather different electrons'
    !! variables.
    !! Temporary buffer to be used by MPI to gather different electrons'
    !! variables.
    INTEGER(is), DIMENSION(:), ALLOCATABLE :: send_buffer_is, receive_buffer_is
    !! Temporary buffer to be used by MPI to gather different electrons'
    !! variables.
    !! Temporary buffer to be used by MPI to gather different electrons'
    !! variables.
    REAL(rp), DIMENSION(:,:), ALLOCATABLE 			:: X
    REAL(rp), DIMENSION(:,:), ALLOCATABLE 			:: V
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: g
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: J0_SC
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: J1_SC
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: J2_SC
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: J3_SC
    REAL(rp), DIMENSION(:), ALLOCATABLE 			:: E_SC
    INTEGER(is), DIMENSION(:), ALLOCATABLE 			:: flag
    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
    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 restart variables.
    INTEGER 							:: ss,jj
    !! Electron species iterator.
    !! Iterator for reading all the entried of params::outputs_list.
    INTEGER 							:: mpierr
    !! MPI error status.
    INTEGER 					:: numel_send, numel_receive
    !! Variable used by MPI to count the amount of data sent by each MPI
    !! procces.
    !! Variable used by MPI to count the amount of data received by the main
    !! MPI procces.


!    if ( MODULO(params%it,params%restart_output_cadence) .EQ. 0_ip ) then 
    if (params%mpi_params%rank.EQ.0_idef) then

       write(6,'("Saving restart: ",I15)') &
            params%it/(params%t_skip*params%t_it_SC)

       filename = TRIM(params%path_to_outputs) // "restart_file.h5"
       call h5fcreate_f(TRIM(filename), H5F_ACC_TRUNC_F, h5file_id, h5error)

       dset = "it"
       attr = "Iteration"
       call save_to_hdf5(h5file_id,dset,params%it,attr)

       dset = "time"
       attr = "Current 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)

       dset = "simulation_time"
       attr = "Total simulation time in secs"
       call save_to_hdf5(h5file_id,dset,params%simulation_time* &
            params%cpp%time,attr)

       dset = "snapshot_frequency"
       attr = "Snapshot frequency in secs"
       call save_to_hdf5(h5file_id,dset,params%snapshot_frequency* &
            params%cpp%time,attr)

       dset = "dt"
       attr = "Time step in secs"
       call save_to_hdf5(h5file_id,dset,params%dt*params%cpp%time,attr)

       dset = "t_steps"
       attr = "Time steps in simulation"
       call save_to_hdf5(h5file_id,dset,params%t_steps,attr)

       dset = "output_cadence"
       attr = "Output cadence"
       call save_to_hdf5(h5file_id,dset,params%output_cadence,attr)

       dset = "restart_output_cadence"
       attr = "Restart output cadence"
       call save_to_hdf5(h5file_id,dset,params%restart_output_cadence,attr)

       dset = "num_snapshots"
       attr = "Number of snapshots in time for saving simulation variables"
       call save_to_hdf5(h5file_id,dset,params%num_snapshots,attr)

       if (F%ReInterp_2x1t) then
          dset = "ind_2x1t"
          attr = "ReInterp_2x1t iteration"
          call save_to_hdf5(h5file_id,dset,F%ind_2x1t,attr)
       end if
       
    end if

    do ss=1_idef,params%num_species
       numel_send = 3_idef*spp(ss)%ppp
       numel_receive = 3_idef*spp(ss)%ppp*params%mpi_params%nmpi

       if (params%mpi_params%rank.EQ.0_idef) then
          ALLOCATE(X(spp(ss)%ppp*params%mpi_params%nmpi,3))
          ALLOCATE(V(spp(ss)%ppp*params%mpi_params%nmpi,3))
          ALLOCATE(g(spp(ss)%ppp*params%mpi_params%nmpi))
          ALLOCATE(flag(spp(ss)%ppp*params%mpi_params%nmpi))
       end if

       ALLOCATE(send_buffer_rp(numel_send))
       ALLOCATE(receive_buffer_rp(numel_receive))

       if (params%orbit_model(1:2).EQ.'FO') then             
          send_buffer_rp = RESHAPE(spp(ss)%vars%X,(/numel_send/))
       else if (params%orbit_model(1:2).EQ.'GC') then
          send_buffer_rp = RESHAPE(spp(ss)%vars%Y,(/numel_send/))
       end if
       receive_buffer_rp = 0.0_rp
       CALL MPI_GATHER(send_buffer_rp,numel_send,MPI_REAL8, &
            receive_buffer_rp,numel_send,MPI_REAL8,0,MPI_COMM_WORLD, &
            mpierr)
       if (params%mpi_params%rank.EQ.0_idef) then
          X = RESHAPE(receive_buffer_rp,(/spp(ss)%ppp* &
               params%mpi_params%nmpi,3/))
       end if

       send_buffer_rp = RESHAPE(spp(ss)%vars%V,(/numel_send/))
       receive_buffer_rp = 0.0_rp
       CALL MPI_GATHER(send_buffer_rp,numel_send,MPI_REAL8, &
            receive_buffer_rp,numel_send,MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       if (params%mpi_params%rank.EQ.0_idef) then
          V = RESHAPE(receive_buffer_rp,(/spp(ss)%ppp* &
               params%mpi_params%nmpi,3/))
       end if

       DEALLOCATE(send_buffer_rp)
       DEALLOCATE(receive_buffer_rp)

       numel_send = spp(ss)%ppp
       numel_receive = spp(ss)%ppp*params%mpi_params%nmpi

       ALLOCATE(send_buffer_is(numel_send))
       ALLOCATE(receive_buffer_is(numel_receive))

       send_buffer_is = spp(ss)%vars%flag
       receive_buffer_is = 0_is
       CALL MPI_GATHER(send_buffer_is,numel_send,MPI_INTEGER1, &
            receive_buffer_is,numel_send,&
            MPI_INTEGER1,0,MPI_COMM_WORLD,mpierr)
       if (params%mpi_params%rank.EQ.0_idef) then
          flag = receive_buffer_is
       end if

       DEALLOCATE(send_buffer_is)
       DEALLOCATE(receive_buffer_is)

       ALLOCATE(send_buffer_rp(numel_send))
       ALLOCATE(receive_buffer_rp(numel_receive))

       send_buffer_rp = spp(ss)%vars%g
       receive_buffer_rp = 0_rp
       CALL MPI_GATHER(send_buffer_rp,numel_send,MPI_REAL8, &
            receive_buffer_rp,numel_send,&
            MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       if (params%mpi_params%rank.EQ.0_idef) then
          g = receive_buffer_rp
       end if

       DEALLOCATE(send_buffer_rp)
       DEALLOCATE(receive_buffer_rp)

       if (params%mpi_params%rank.EQ.0_idef) then
          write(tmp_str,'(I18)') ss
          subgname = "spp_" // TRIM(ADJUSTL(tmp_str))
          call h5gcreate_f(h5file_id, TRIM(subgname), group_id, h5error)

          dset = "X"
          call rsave_2d_array_to_hdf5(group_id, dset, X)

          dset = "V"
          call rsave_2d_array_to_hdf5(group_id, dset, V)

          dset = "flag"
          call save_1d_array_to_hdf5(group_id,dset, INT(flag,idef))

          dset = "g"
          call save_1d_array_to_hdf5(group_id,dset, g)

          if (params%SC_E) then

             ALLOCATE(J0_SC(F%dim_1D))
             ALLOCATE(J1_SC(F%dim_1D))
             ALLOCATE(J2_SC(F%dim_1D))
             ALLOCATE(J3_SC(F%dim_1D))
             ALLOCATE(E_SC(F%dim_1D))
             J0_SC=F%J1_SC_1D%PHI/F%Ip0
             J1_SC=F%J1_SC_1D%PHI
             J2_SC=F%J2_SC_1D%PHI
             J3_SC=F%J3_SC_1D%PHI
             E_SC=F%E_SC_1D%PHI

             dset = "J0_SC"
             call save_1d_array_to_hdf5(group_id,dset,J0_SC)
             dset = "J1_SC"
             call save_1d_array_to_hdf5(group_id,dset,J1_SC)
             dset = "J2_SC"
             call save_1d_array_to_hdf5(group_id,dset,J2_SC)
             dset = "J3_SC"
             call save_1d_array_to_hdf5(group_id,dset,J3_SC)
             dset = "E_SC"
             call save_1d_array_to_hdf5(group_id,dset,E_SC)
             
             DEALLOCATE(J0_SC)
             DEALLOCATE(J1_SC)
             DEALLOCATE(J2_SC)
             DEALLOCATE(J3_SC)
             DEALLOCATE(E_SC)
          end if
          
          call h5gclose_f(group_id, h5error)
       end if

       if (params%mpi_params%rank.EQ.0_idef) then
          DEALLOCATE(X)
          DEALLOCATE(V)
          DEALLOCATE(g)
          DEALLOCATE(flag)
       end if
    end do

    
    if (params%mpi_params%rank.EQ.0_idef) then
       call h5fclose_f(h5file_id, h5error)
    end if

!    end if
  end subroutine save_restart_variables