! ! 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 TYPE(hdset_reg_ref_t_f), DIMENSION(1:15), TARGET :: ref ! array to read region references INTEGER :: status INTEGER(hid_t) :: dtype ! file datatype handle INTEGER(hid_t) :: mtype ! mempry datatype handle INTEGER(size_t) :: msize ! size of memory datatype INTEGER(size_t) :: rnumelem ! number of elements to read REAL, ALLOCATABLE, DIMENSION(:), TARGET :: rdata ! POINTER to READ buffer INTEGER :: class INTEGER(HSIZE_T), DIMENSION(1:1) :: dims =(/15/) 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 datatype of the data the region reference points to. ! ! Important to initialize optional variables dtype = 0 CALL H5LRget_region_info_f(file_id, ref(3), status, DTYPE=dtype) ! ! Find the corresponding type in memory and its size. ! CALL H5Tget_native_type_f(dtype, H5T_DIR_ASCEND_F, mtype, status) CALL H5Tget_size_f(mtype, msize, status) ! ! Find number of elements in the region to read. ! f_ptr = C_NULL_PTR CALL H5LRread_region_f(file_id, ref(3), mtype, rnumelem, f_ptr, status) CALL H5Tget_class_f(dtype, class, status) IF(class.EQ.H5T_FLOAT_F)THEN ! ! Allocate buffer to read data in. ! ALLOCATE( rdata(1:rnumelem) ) f_ptr = C_LOC(rdata(1)) CALL H5LRread_region_f(file_id, ref(3), mtype, rnumelem, f_ptr, status) 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) ENDIF ! ! Close dataset with region references and file. ! CALL H5Dclose_f(dset_id,status) CALL H5Fclose_f(file_id,status) END PROGRAM main