! ! This example copies a hyperslab region of 'SatelliteRange' under ! '/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/' to another hyperslab region ! '/SatelliteRange_Subset' under '/All_Data'. It then reads back ! the newly created hyperslab region. ! Main illustrative functions: H5LTread_region_f, H5LTcopy_region_f ! PROGRAM main USE ISO_C_BINDING USE HDF5 ! module of HDF5 library USE H5LT ! module of H5LT USE H5HL_REGION IMPLICIT NONE CHARACTER(LEN=78), PARAMETER :: filename = & "GMGTO_npp_d20030125_t0657104_e0659047_b00014_c20090811150425926728_unkn_SCI.h5" CHARACTER(LEN=78), PARAMETER :: PATH_DEST = & "/Data_Products/SatelliteRange_Subset" ! Full path of the source dataset CHARACTER(LEN=78), PARAMETER :: PATH_SRC = & "/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/SatelliteRange" ! Full path to the destination dataset INTEGER, PARAMETER :: NRANK = 2 ! rank of source and destination dataset INTEGER(hid_t) :: file_id ! file identifier INTEGER(hid_t) :: dset_id ! dataset identifier INTEGER(hid_t) :: space_id ! dataspace identifier INTEGER(hsize_t), DIMENSION(1:4) :: block_coord_src = (/52,4,54,8/) ! source's block coordinates (52,4)-(54,8) INTEGER(hsize_t), DIMENSION(1:4) :: block_coord_dest= (/2, 2, 4, 6/) ! destination's BLOCK coordinates (2,2)-(4,6) INTEGER(hsize_t), DIMENSION(1:NRANK) :: dims = (/5,7/) ! receiving dataset dimensions REAL, DIMENSION(1:3,1:5), TARGET :: rdata ! buffer to read destination data into INTEGER :: i, j INTEGER :: status TYPE(C_PTR) :: f_ptr ! ! Initialize FORTRAN interface. ! CALL H5open_f(status) ! ! Open the NPP file. ! CALL H5Fopen_f(filename, H5F_ACC_RDWR_F, file_id, status) ! ! First create the destination dataset "SatelliteRange_Subset" since it does not exist. ! ! NOTE: If the destination dataset does not already exist then H5LTcopy_region ! will automatically create a destination dataset that is the same size ! and rank of the source data and will, additionally, fill the destination ! block starting at (1,1) thus ignoring the destination's block coordinates. ! CALL H5Screate_simple_f(NRANK, dims, space_id, status) CALL H5Dcreate_f(file_id, PATH_DEST, H5T_NATIVE_REAL, space_id, dset_id, status) CALL H5Sclose_f(space_id, status) CALL H5Fclose_f(file_id, status) ! ! Copy a block of the "/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/SatelliteRange" ! data with block corner coordinates of (52,4)-(54,8) to ! a subset of the "/Data_Products/SatelliteRange_Subset" with hyperslab ! coordinates (2,2)-(4,6). ! ! CALL H5LTcopy_region_f(filename, PATH_SRC, block_coord_src, filename, PATH_DEST, & block_coord_dest, status) ! ! ! Reads a subset region of "/Data_Products/SatelliteRange_Subset" ! specified by coordinates (2,2)-(4,6). ! ! f_ptr = C_LOC(rdata(1,1)) CALL H5LTread_region_f(filename, PATH_DEST, block_coord_dest, H5T_NATIVE_REAL, & f_ptr, status) WRITE(*,'(/,"Subset of /Data_Products/SatelliteRange_Subset with coordinates (",i1,",",i1,")-(",i1,",",i1,"):")') block_coord_dest(1:4) DO i = 1, 3 WRITE(*,'(A)', ADVANCE="NO") "[" DO j = 1, 5 WRITE(*,'(x,f12.4)', ADVANCE="NO") rdata(i,j) ENDDO WRITE(*,'(A)') " ]" ENDDO WRITE(*,'(/)') END PROGRAM main