load_particles_ic Subroutine

public subroutine load_particles_ic(params, spp, F)

Arguments

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

Core KORC simulation parameters.

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

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

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

Contents

Source Code


Source Code

  subroutine load_particles_ic(params,spp,F)
    !! @note Subroutine that loads all the electrons' data from
    !! "restart_file.h5" to restart a simulation.
    TYPE(KORC_PARAMS), INTENT(INOUT) 			:: params
    !! Core KORC simulation parameters.
    TYPE(SPECIES), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: spp
    !! An instance of KORC's derived type SPECIES containing all the
    !! information of different electron species. See korc_types.f90.
    TYPE(FIELDS), INTENT(INOUT) 			:: F
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: X_send_buffer
    !! Temporary buffer used by MPI for scattering the electrons' position
    !! to different MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: X_receive_buffer
    !! Temporary buffer used by MPI for scattering the electrons' position
    !! among MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: V_send_buffer
    !! Temporary buffer used by MPI for scattering the electrons' velocity
    !! among MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: V_receive_buffer
    !! Temporary buffer used by MPI for scattering the electrons' velocity
    !! among MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: AUX_send_buffer
    !!  Temporary buffer used by MPI to scatter various electrons' variables
    !! among MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: AUX_receive_buffer
    !! Temporary buffer used by MPI to scatter various electrons' variables
    !! among MPI processes.
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: JSC0_buffer
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: JSC1_buffer
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: JSC2_buffer
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: JSC3_buffer
    REAL(rp), DIMENSION(:), ALLOCATABLE 		:: ESC_buffer


    CHARACTER(MAX_STRING_LENGTH) 			:: filename
    !! String containing the name of the HDF5 file.
    CHARACTER(MAX_STRING_LENGTH) 			:: dset
    !! Name of data set to be saved to file.
    INTEGER(HID_T) 					:: h5file_id
    !! HDF5 file identifier.
    CHARACTER(19) 					:: tmp_str
    !! Temporary string used to manipulate various strings.
    INTEGER 						:: h5error
    !! HDF5 error status.
    INTEGER 						:: mpierr
    !! Electron species iterator.
    INTEGER 						:: ss
    !! MPI error status.

    do ss=1_idef,params%num_species
       ALLOCATE(X_send_buffer(3*spp(ss)%ppp*params%mpi_params%nmpi))
       ALLOCATE(X_receive_buffer(3*spp(ss)%ppp))

       ALLOCATE(V_send_buffer(3*spp(ss)%ppp*params%mpi_params%nmpi))
       ALLOCATE(V_receive_buffer(3*spp(ss)%ppp))

       ALLOCATE(AUX_send_buffer(spp(ss)%ppp*params%mpi_params%nmpi))
       ALLOCATE(AUX_receive_buffer(spp(ss)%ppp))
       
       if (params%mpi_params%rank.EQ.0_idef) then
          filename = TRIM(params%path_to_outputs) // "restart_file.h5"
          call h5fopen_f(filename, H5F_ACC_RDONLY_F, h5file_id, h5error)
          if (h5error .EQ. -1) then
             write(6,'("KORC ERROR: Something went wrong in: &
                  &load_particles_ic --> h5fopen_f")')
             call KORC_ABORT()
          end if

          write(tmp_str,'(I18)') ss

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/X"
          call load_array_from_hdf5(h5file_id,dset,X_send_buffer)

          call h5fclose_f(h5file_id, h5error)
       end if

       X_receive_buffer = 0.0_rp
       CALL MPI_SCATTER(X_send_buffer,3*spp(ss)%ppp,MPI_REAL8, &
            X_receive_buffer,3*spp(ss)%ppp,MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       if (params%orbit_model(1:2).EQ.'FO') then  
          spp(ss)%vars%X = RESHAPE(X_receive_buffer,(/spp(ss)%ppp,3/))
       else if (params%orbit_model(1:2).EQ.'GC') then
          spp(ss)%vars%Y = RESHAPE(X_receive_buffer,(/spp(ss)%ppp,3/))

          spp(ss)%vars%Y(:,2)=modulo(spp(ss)%vars%Y(:,2),2*C_PI)          
       end if

       if (params%mpi_params%rank.EQ.0_idef) then
          filename = TRIM(params%path_to_outputs) // "restart_file.h5"
          call h5fopen_f(filename, H5F_ACC_RDONLY_F, h5file_id, h5error)
          if (h5error .EQ. -1) then
             write(6,'("KORC ERROR: Something went wrong in: &
                  &load_particles_ic --> h5fopen_f")')
             call KORC_ABORT()
          end if

          write(tmp_str,'(I18)') ss

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/V"
          call load_array_from_hdf5(h5file_id,dset,V_send_buffer)

          call h5fclose_f(h5file_id, h5error)
       end if

       

       V_receive_buffer = 0.0_rp
       CALL MPI_SCATTER(V_send_buffer,3*spp(ss)%ppp,MPI_REAL8, &
            V_receive_buffer,3*spp(ss)%ppp,MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       spp(ss)%vars%V = RESHAPE(V_receive_buffer,(/spp(ss)%ppp,3/))

       if (params%mpi_params%rank.EQ.0_idef) then
          filename = TRIM(params%path_to_outputs) // "restart_file.h5"
          call h5fopen_f(filename, H5F_ACC_RDONLY_F, h5file_id, h5error)
          if (h5error .EQ. -1) then
             write(6,'("KORC ERROR: Something went wrong in: &
                  &load_particles_ic --> h5fopen_f")')
             call KORC_ABORT()
          end if

          write(tmp_str,'(I18)') ss

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/flag"
          call load_array_from_hdf5(h5file_id,dset,AUX_send_buffer)

          call h5fclose_f(h5file_id, h5error)
       end if

       AUX_receive_buffer = 0.0_rp
       CALL MPI_SCATTER(AUX_send_buffer,spp(ss)%ppp,MPI_REAL8, &
            AUX_receive_buffer,spp(ss)%ppp,MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       spp(ss)%vars%flag = INT(AUX_receive_buffer,is)

       if (params%mpi_params%rank.EQ.0_idef) then
          filename = TRIM(params%path_to_outputs) // "restart_file.h5"
          call h5fopen_f(filename, H5F_ACC_RDONLY_F, h5file_id, h5error)
          if (h5error .EQ. -1) then
             write(6,'("KORC ERROR: Something went wrong in: &
                  &load_particles_ic --> h5fopen_f")')
             call KORC_ABORT()
          end if

          write(tmp_str,'(I18)') ss

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/g"
          call load_array_from_hdf5(h5file_id,dset,AUX_send_buffer)

          call h5fclose_f(h5file_id, h5error)
       end if

       AUX_receive_buffer = 0.0_rp
       CALL MPI_SCATTER(AUX_send_buffer,spp(ss)%ppp,MPI_REAL8, &
            AUX_receive_buffer,spp(ss)%ppp,MPI_REAL8,0,MPI_COMM_WORLD,mpierr)
       spp(ss)%vars%g = AUX_receive_buffer

       if (params%SC_E) then
          
          ALLOCATE(JSC0_buffer(F%dim_1D))
          ALLOCATE(JSC1_buffer(F%dim_1D))
          ALLOCATE(JSC2_buffer(F%dim_1D))
          ALLOCATE(JSC3_buffer(F%dim_1D))
          ALLOCATE(ESC_buffer(F%dim_1D))

          filename = TRIM(params%path_to_outputs) // "restart_file.h5"
          call h5fopen_f(filename, H5F_ACC_RDONLY_F, h5file_id, h5error)
          if (h5error .EQ. -1) then
             write(6,'("KORC ERROR: Something went wrong in: &
                  &load_particles_ic --> h5fopen_f")')
             call KORC_ABORT()
          end if

          write(tmp_str,'(I18)') ss

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/J0_SC"
          call load_array_from_hdf5(h5file_id,dset,JSC0_buffer)
          
          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/J1_SC"
          call load_array_from_hdf5(h5file_id,dset,JSC1_buffer)

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/J2_SC"
          call load_array_from_hdf5(h5file_id,dset,JSC2_buffer)

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/J3_SC"
          call load_array_from_hdf5(h5file_id,dset,JSC3_buffer)

          dset = "/spp_" // TRIM(ADJUSTL(tmp_str)) // "/E_SC"
          call load_array_from_hdf5(h5file_id,dset,ESC_buffer)
          
          call h5fclose_f(h5file_id, h5error)

          F%J0_SC_1D%PHI=JSC0_buffer
          F%J1_SC_1D%PHI=JSC1_buffer
          F%J2_SC_1D%PHI=JSC2_buffer
          F%J3_SC_1D%PHI=JSC3_buffer
          F%E_SC_1D%PHI=ESC_buffer/params%cpp%Eo
          
          DEALLOCATE(JSC0_buffer)
          DEALLOCATE(JSC1_buffer)
          DEALLOCATE(JSC2_buffer)
          DEALLOCATE(JSC3_buffer)
          DEALLOCATE(ESC_buffer)
          
       end if
       
       DEALLOCATE(X_send_buffer)
       DEALLOCATE(X_receive_buffer)

       DEALLOCATE(V_send_buffer)
       DEALLOCATE(V_receive_buffer)

       DEALLOCATE(AUX_send_buffer)
       DEALLOCATE(AUX_receive_buffer)
    end do

    if (params%orbit_model(1:2).EQ.'GC') then
       params%GC_coords=.TRUE.
    end if

  end subroutine load_particles_ic