! ! This example copies subregions of the satellite data 'SatelliteZenithAngle' ! 'SatelliteAzimuthAngle' and 'SatelliteRange' under '/All_Data/VIIRS-MOD-GTM-EDR-GEO_All' ! to one dataset,'Satellite', located at '/Data_Products/Subset' of the NPP ! file. ! Main illustrative functions: H5LRcreate_region_references_f and H5LRmake_dataset_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" INTEGER(hid_t) :: file_id ! file identifier INTEGER(hsize_t), DIMENSION(1:12) :: block_coord = (/52,4,54,8,52,4,54,8,52,4,54,8/) ! hyperslab coordinates, (52,4)-(54,8), for ! 'SatelliteZenithAngle', 'SatelliteAzimuthAngle', 'SatelliteRange' TYPE(hdset_reg_ref_t_f), DIMENSION(1:3) :: ref_subset ! region references to hyperslabs of 'SatelliteZenithAngle', 'SatelliteAzimuthAngle', 'SatelliteRange' CHARACTER(LEN=80), DIMENSION(1:3) :: path ! full paths to the satellite target datasets for the region references INTEGER(hsize_t), DIMENSION(1:1) :: dims = (/3/) INTEGER(hid_t), DIMENSION(1:3) :: file_id_array ! identifiers describing which HDF5 file the corresponding region reference belongs to INTEGER :: status path(1)= "/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/SatelliteZenithAngle" path(2)= "/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/SatelliteAzimuthAngle" path(3)= "/All_Data/VIIRS-MOD-GTM-EDR-GEO_All/SatelliteRange" ! ! Initialize FORTRAN interface. ! CALL H5open_f(status) ! ! OPEN the NPP file. ! CALL H5Fopen_f(filename, H5F_ACC_RDWR_F, file_id, status) ! ! We are creating the data set in the same file, so fill the file_id path with the same file id. ! file_id_array(1:3) = file_id ! ! Create three region references pointing to hyperslabs with block coordinates (52,4)-(54,8) in ! 'SatelliteZenithAngle', 'SatelliteAzimuthAngle' and 'SatelliteRange' datasets. ! CALL H5LRcreate_region_references_f(file_id, 3_size_t, path, block_coord, ref_subset, status); ! ! Combine the three datasets into one dataset, 'Satellite', under '/Data_Products/Subset', ! resulting in a final dataset of size (0,0)-(14,2). Notice the group 'Subset' did not exist ! so the FUNCTION automatically created the necessary intermediate group. ! CALL H5LRmake_dataset_f(file_id, "/Data_Products/Subset/Satellite", H5T_NATIVE_REAL, 3_size_t, file_id_array, ref_subset, status) CALL H5Fclose_f(file_id, status) END PROGRAM main