! ! This example opens an NPP example file and reads a dataset with region references ! VIIRS-MOD_GTM-EDR-GEO_Gran_0 under the /Data_Products/VIIRS-MOD-GTM-EDR-GEO group. ! Then it finds information about the selected elements pointed by the third reference ! and reads the data in. ! Main illustrative functions: H5LRget_region_info_f, H5LRread_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=65), PARAMETER :: dsetname = & "/Data_Products/VIIRS-MOD-GTM-EDR-GEO/VIIRS-MOD-GTM-EDR-GEO_Gran_0" ! dataset with region references INTEGER(hid_t) :: file_id ! file identifier INTEGER(hid_t) :: dset_id ! region reference dataset identifier INTEGER(hsize_t), DIMENSION(1:1) :: dims = (/15/) ! size of the VIIRS-MOD_GTM-EDR-GEO_Gran_0 dataset TYPE(hdset_reg_ref_t_f), DIMENSION(1:15) :: ref ! array to READ region references INTEGER(hsize_t), DIMENSION(1:4) :: buf ! buffer to READ hyperslab coordinates defining region references INTEGER :: status INTEGER(size_t) :: name_length CHARACTER(LEN = 50) :: name INTEGER(hid_t) :: dtype INTEGER(size_t) :: numelem INTEGER(size_t), PARAMETER :: type_string_length = 15 CHARACTER(LEN=15) :: type_string INTEGER(hsize_t), DIMENSION(1:2) :: rdims REAL, ALLOCATABLE, DIMENSION(:), TARGET :: rdata INTEGER(size_t) :: rnumelem INTEGER :: class 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) ! ! Open dataset and read the dataset with the region references. ! We made an assumption that the size of the dataset is known. ! CALL H5Dopen_f(file_id, dsetname, dset_id, status) CALL H5Dread_f(dset_id, H5T_STD_REF_DSETREG, ref, dims, status) ! ! Get region reference information such as a name of the dataset the region reference point to, ! number of contiguous blocks in the selection (should be 1) and the hyperslab coordinates (0,0) - (770,4120) ! ! Important to initialize optional variables name_length = LEN(name) dtype = 0 name = '' CALL H5LRget_region_info_f(file_id, ref(3), status, LENGTH=name_length, PATH=name, DTYPE=dtype, & NUMELEM=numelem, BUF=buf) ! ! Display the info ! CALL H5Tget_class_f(dtype, class, status) WRITE(*, '(" Information retrieved by H5LRget_region_info:")') WRITE(*,'(" Third element of the array with the region references points to ",A)') name WRITE(*,'(" Length of the string above is ", I0)') name_length IF(class.EQ.H5T_FLOAT_F) WRITE(*,' (" Datatype of region is ", A)') "H5T_FLOAT_F" WRITE(*,'(" Number of blocks in the region is ", I0)') numelem WRITE(*,'(" Block''s coordinates are (",I0,",",I0,") - (",I0,",",I0,")",/)') buf(1),buf(2),buf(3),buf(4) ! ! We will read data to the floating-point buffer using information provided by H5LRget_region_info ! to allocate the buffer to read data in. rdims(1) = buf(3) - buf(1) + 1 rdims(2) = buf(4) - buf(2) + 1 ALLOCATE(rdata(rdims(1) * rdims(2))) ! ! Read data pointed by the third region reference into a buffer and display the first six elements. ! f_ptr = C_LOC(rdata(1)) CALL H5LRread_region_f(file_id, ref(3), H5T_NATIVE_REAL, rnumelem, f_ptr, status) WRITE(*,'(" Information retrieved by H5LRread_region:")') WRITE(*,'(" Number of elements pointed by a region reference is ",I0)') rnumelem WRITE(*,'(" The first six elements are: ")') WRITE(*,'(6(x,f7.3))') rdata(1:6) DEALLOCATE(rdata) ! ! Close dataset with region references and file. ! CALL H5Dclose_f(dset_id, status) CALL H5Fclose_f(file_id, status) END PROGRAM main