rload_3d_array_from_hdf5 Subroutine

private subroutine rload_3d_array_from_hdf5(h5file_id, dset, rdata, attr)

Arguments

Type IntentOptional AttributesName
integer(kind=HID_T), intent(in) :: h5file_id
character(len=MAX_STRING_LENGTH), intent(in) :: dset
real(kind=rp), intent(inout), DIMENSION(:,:,:), ALLOCATABLE:: rdata
character(len=MAX_STRING_LENGTH), intent(in), optional DIMENSION(:), ALLOCATABLE:: attr

Calls

proc~~rload_3d_array_from_hdf5~~CallsGraph proc~rload_3d_array_from_hdf5 rload_3d_array_from_hdf5 proc~korc_abort korc_abort proc~rload_3d_array_from_hdf5->proc~korc_abort h5dclose_f h5dclose_f proc~rload_3d_array_from_hdf5->h5dclose_f h5dread_f h5dread_f proc~rload_3d_array_from_hdf5->h5dread_f mpi_abort mpi_abort proc~korc_abort->mpi_abort

Called by

proc~~rload_3d_array_from_hdf5~~CalledByGraph proc~rload_3d_array_from_hdf5 rload_3d_array_from_hdf5 interface~load_array_from_hdf5 load_array_from_hdf5 interface~load_array_from_hdf5->proc~rload_3d_array_from_hdf5 proc~load_profiles_data_from_hdf5 load_profiles_data_from_hdf5 proc~load_profiles_data_from_hdf5->interface~load_array_from_hdf5 proc~load_1d_fs_from_hdf5 load_1D_FS_from_hdf5 proc~load_1d_fs_from_hdf5->interface~load_array_from_hdf5 proc~load_data_from_hdf5_bmc load_data_from_hdf5_BMC proc~load_data_from_hdf5_bmc->interface~load_array_from_hdf5 proc~load_field_data_from_hdf5 load_field_data_from_hdf5 proc~load_field_data_from_hdf5->interface~load_array_from_hdf5 proc~load_particles_ic load_particles_ic proc~load_particles_ic->interface~load_array_from_hdf5 proc~load_data_from_hdf5 load_data_from_hdf5 proc~load_data_from_hdf5->interface~load_array_from_hdf5 proc~initialize_fields initialize_fields proc~initialize_fields->proc~load_1d_fs_from_hdf5 proc~initialize_fields->proc~load_field_data_from_hdf5 proc~initialize_hollmann_params initialize_Hollmann_params proc~initialize_hollmann_params->proc~load_data_from_hdf5 proc~initialize_profiles initialize_profiles proc~initialize_profiles->proc~load_profiles_data_from_hdf5 proc~set_up_particles_ic set_up_particles_ic proc~set_up_particles_ic->proc~load_particles_ic proc~bmc_radial BMC_radial proc~bmc_radial->proc~load_data_from_hdf5_bmc proc~get_hollmann_distribution_3d get_Hollmann_distribution_3D proc~get_hollmann_distribution_3d->proc~initialize_hollmann_params program~main main program~main->proc~initialize_fields program~main->proc~initialize_profiles program~main->proc~set_up_particles_ic proc~get_hollmann_distribution_1dtransport get_Hollmann_distribution_1Dtransport proc~get_hollmann_distribution_1dtransport->proc~initialize_hollmann_params proc~get_hollmann_distribution_3d_psi get_Hollmann_distribution_3D_psi proc~get_hollmann_distribution_3d_psi->proc~initialize_hollmann_params proc~get_hollmann_distribution get_Hollmann_distribution proc~get_hollmann_distribution->proc~initialize_hollmann_params

Contents


Source Code

  subroutine rload_3d_array_from_hdf5(h5file_id,dset,rdata,attr)
    INTEGER(HID_T), INTENT(IN) 					:: h5file_id
    CHARACTER(MAX_STRING_LENGTH), INTENT(IN) 			:: dset
    REAL(rp), DIMENSION(:,:,:), ALLOCATABLE, INTENT(INOUT) 	:: rdata
    REAL, DIMENSION(:,:,:), ALLOCATABLE 				:: raw_data
    CHARACTER(MAX_STRING_LENGTH), OPTIONAL, DIMENSION(:), ALLOCATABLE, INTENT(IN) 	:: attr
    CHARACTER(MAX_STRING_LENGTH) 							:: aname
    INTEGER(HID_T) 									:: dset_id
    INTEGER(HID_T) 									:: dspace_id
    INTEGER(HID_T) 									:: aspace_id
    INTEGER(HID_T) 									:: attr_id
    INTEGER(HID_T) 									:: atype_id
    INTEGER(HSIZE_T), DIMENSION(3) 				:: dims
    INTEGER(HSIZE_T), DIMENSION(3) 				:: adims
    INTEGER 							:: h5error

    dims = shape(rdata)

    ALLOCATE( raw_data(dims(1),dims(2),dims(3)) )

    ! * * * Read data from file * * *

    call h5dopen_f(h5file_id, TRIM(dset), dset_id, h5error)
    if (h5error .EQ. -1) then
       write(output_unit_write,'("KORC ERROR: Something went wrong in: rload_from_hdf5 --> h5dopen_f")')
       call KORC_ABORT(14)
    end if

    call h5dread_f(dset_id, H5T_NATIVE_REAL, raw_data, dims, h5error)
    if (h5error .EQ. -1) then
       write(output_unit_write,'("KORC ERROR: Something went wrong in: rload_from_hdf5 --> h5dread_f")')
       call KORC_ABORT(14)
    end if
    rdata = REAL(raw_data,rp)

    call h5dclose_f(dset_id, h5error)
    if (h5error .EQ. -1) then
       write(output_unit_write,'("KORC ERROR: Something went wrong in: rload_from_hdf5 --> h5dclose_f")')
       call KORC_ABORT(14)
    end if

    DEALLOCATE( raw_data )

    if (PRESENT(attr)) then
       ! * * * Read data attribute(s) from file * * *
    end if

    ! * * * Read data from file * * *
  end subroutine rload_3d_array_from_hdf5