! ! This example opens a file, and extracts ! the bit field from a subset of a dataset. ! The values are returned as a base-10 integer. ! Main illustrative function: H5LTread_bitfield_value_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 = & "SVI01-GIMFG_NPP_d2003125_t101038_e10116_b9_c2005829153351_dev.h5" CHARACTER(LEN=78), PARAMETER :: DATASET = & "/All_Data/VIIRS-I1-SDR_All/QF_VIIRSI1SDR_Array" INTEGER, PARAMETER :: num_flags = 1 INTEGER, DIMENSION(1:3) :: dim_qf_data =(/6,5,num_flags/) ! Dimensions of qf_data INTEGER, DIMENSION(1:num_flags,1:6,1:5) :: qf_data ! Read buffer, transposed because data written with C convention INTEGER, DIMENSION(1:1) :: offset = (/2/) ! Starting bits to be extracted from element INTEGER, DIMENSION(1:1) :: length = (/2/) ! Number of bits to be extracted for each value INTEGER(hid_t) :: file, space ! Handles INTEGER(hid_t) :: qf_dset INTEGER :: status INTEGER(hsize_t), DIMENSION(1:3) :: start = (/0,0,0/) INTEGER(hsize_t), DIMENSION(1:3) :: count = (/num_flags,6,5/) INTEGER :: i, j ! ! Initialize FORTRAN interface. ! CALL H5open_f(status) ! ! Open file. CALL H5Fopen_f(FILENAME, H5F_ACC_RDONLY_F, file, status) ! ! Open the data set CALL H5Dopen_f(file, DATASET, qf_dset, status) ! ! Get dataspace and allocate memory for read buffer. Quality flags dataset ! has the same dimensionality as corresponding product dataset ! we are using its dimensions for illustration purposes only. CALL H5Dget_space_f(qf_dset, space, status) CALL H5Sselect_hyperslab_f(space, H5S_SELECT_SET_F, start, count, status) ! ! For each element read the value that takes first two bits and ! store it in a char buffer. This selects all the elements (H5S_ALL) CALL H5LTread_bitfield_value_f(qf_dset, num_flags, offset, length, space, qf_data, dim_qf_data, status) CALL H5Sclose_f(space, status) ! Print out the bit field WRITE(*,'("Bit Field:")') DO i = 1, 6 WRITE( *, '(A)', ADVANCE = "NO") "[" DO j = 1, 5 WRITE( *, '(A)', ADVANCE = "NO") " {" WRITE( *, '(20i2)', ADVANCE = "NO") qf_data(1,i,j) WRITE( *, '(A)', ADVANCE = "NO") "} " ENDDO WRITE(*,'(A)',ADVANCE="YES") "]" ENDDO END PROGRAM main