H5dread_f not working. Error = -1 and data is not read from file

Hello everyone,

I am trying to read some data from an HDF5 file (rainfall.hdf5), the file is in the link below.

I am compiling my FORTRAN code using Visual Studio Professional 2019 (MVS2019) and IFORT Intel® Fortran Compiler Classic (IntelOneAPI).

The HDF5 version that I am using is HDF5 1.8.1. I included the following directories to my properties in MVS2019: “C:\Program Files\HDF_Group\HDF5\1.8.17 \include\static” and "C:\Program Files\HDF_Group\HDF5\1.8.17\lib My code (inserted below) compiles with no errors.

I am able to open the file (rainfall.hdf5), open the groups ( h5dopen_f) but when I tried to read the data using h5dread_f, the error is equal to -1 and the data is not retrieved from the HDF5 data file.

My code is the following:

use HDF5
use H5FORTRAN_TYPES

IMPLICIT NONE

INTEGER :: error
CHARACTER(LEN=16), PARAMETER :: filename = “rainfall.hdf5”
INTEGER(HID_T) :: file
INTEGER(HID_T) :: dset_id1,dset_id2,dset_id3,dset_id4 !Dataset identifier
INTEGER(HID_T) :: group,group1 !Handles
CHARACTER(LEN=8), PARAMETER :: dsetname = “raincell” !Dataset name
CHARACTER(LEN=8), PARAMETER :: dsetIRAINDUM = “IRAINDUM” !Dataset name
CHARACTER(LEN=8), PARAMETER :: dsetIRINTERS = “IRINTERS” !Dataset name
CHARACTER(LEN=10), PARAMETER :: dsetRAININTIME = “RAININTI” !Dataset name
CHARACTER(LEN=9), PARAMETER :: dsetTIMESTAMP = “TIMESTAM” !Dataset name

INTEGER , PARAMETER :: dim0 = 54310 !Change to NNOD after testing
INTEGER , PARAMETER :: dim1 = 288 !Change to IRINTERS after testing Number of output intervals
INTEGER , PARAMETER :: dim2 = 1 !Change to IRINTERS after testing Number of output intervals

INTEGER(HSIZE_T), DIMENSION(1:3) :: dims = (/dim1,dim0,dim2/)
INTEGER(HSIZE_T), DIMENSION(1) :: dims1 = (/dim2/)

DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE, TARGET :: rdata4 !Read buffer
INTEGER, DIMENSION(:), ALLOCATABLE, TARGET :: rdata1,rdata2,rdata3 !Read buffer
ALLOCATE(rdata1(1))
ALLOCATE(rdata2(1))
ALLOCATE(rdata3(1))
ALLOCATE(rdata4(dim1,dim0,dim2))

! open the file and edit the values
! Initialize FORTRAN interface.
CALL h5open_f(error)

! Open file. Error = 0 means no issues
CALL h5fopen_f(filename,H5T_NATIVE_DOUBLE, file, error)

! Open group, file is the same variable identifier initialized by the h5open_f() subroutine.
! This gives the HDF5 library the link between the file and the requested group to be opened.
CALL h5gopen_f(file, dsetname, group, error)

!Open an existing dataset IRAINDUM
CALL h5dopen_f(group, dsetIRAINDUM, dset_id1, error)
!Read data IRAINDUM
CALL h5dread_f(dset_id1,H5T_NATIVE_DOUBLE, rdata4, dims, error)

!Open an existing dataset IRINTERS
CALL h5dopen_f(group, dsetIRINTERS, dset_id2, error)
!Read data IRINTERS
CALL h5dread_f(dset_id2,H5T_NATIVE_INTEGER, rdata1, dims1, error)

!Open an existing dataset RAININTIME
CALL h5dopen_f(group, dsetRAININTIME, dset_id3, error)
!Read data RAININTIME
CALL h5dread_f(dset_id3,H5T_NATIVE_INTEGER, rdata2, dims1, error)

!Open an existing dataset TIMESTAMP
CALL h5dopen_f(group, dsetTIMESTAMP, dset_id4, error)
!Read data TIMESTAMP
CALL h5dread_f(dset_id4,H5T_NATIVE_INTEGER, rdata3, dims1, error)

Can someone please help me figure out why h5dread_f doesn’t work?

Thanks!
N

N, FORTRAN is over my head. What’s the error message you are getting? The file looks fine to me:

> h5ls -vr Downloads/Rainfall.hdf5 
Opened "Downloads/Rainfall.hdf5" with sec2 driver.
/                        Group
    Attribute: hdf5_version {1}
        Type:      6-byte null-padded ASCII string
    Attribute: plugin {1}
        Type:      6-byte null-padded ASCII string
    Location:  1:96
    Links:     1
/raincell                Group
    Location:  1:992
    Links:     1
/raincell/IRAINDUM       Dataset {54310/54310, 288/288, 1/1}
    Attribute: description {1}
        Type:      59-byte null-padded ASCII string
    Location:  1:5216
    Links:     1
    Storage:   125130240 logical bytes, 125130240 allocated bytes, 100.00% utilization
    Type:      native double
/raincell/IRINTERS       Dataset {SCALAR}
    Attribute: description {1}
        Type:      35-byte null-padded ASCII string
    Location:  1:4672
    Links:     1
    Storage:   4 logical bytes, 4 allocated bytes, 100.00% utilization
    Type:      native int
/raincell/RAININTIME     Dataset {SCALAR}
    Attribute: description {1}
        Type:      55-byte null-padded ASCII string
    Location:  1:2024
    Links:     1
    Storage:   4 logical bytes, 4 allocated bytes, 100.00% utilization
    Type:      native int
/raincell/TIMESTAMP      Dataset {1/1}
    Attribute: description {1}
        Type:      56-byte null-padded ASCII string
    Location:  1:4944
    Links:     1
    Storage:   29 logical bytes, 29 allocated bytes, 100.00% utilization
    Type:      29-byte null-padded ASCII string

There is a subtle difference between singletons (/raincell/IRINTERS and /raincell/RAININTIME) and a single element array (/raincell/TIMESTAMP), but that shouldn’t matter in this case.

Puzzled, G.

Hi Gheber,

I am not getting any error message in Fortran, the code compiles fine and the dataset opens, but the h5dread_f instruction is not retrieving the data from the file and give me an error= -1, see below the details:

!Open an existing dataset IRAINDUM
CALL h5dopen_f(group, dsetIRAINDUM, dset_id1, error) … This opens fine and the error is 0

!Read data IRAINDUM
CALL h5dread_f(dset_id1,H5T_NATIVE_DOUBLE, rdata4, dims, error) … This error is -1 and the data is not read from the file

Thanks for your help.

N

The middle dimension (of 3) of in the rdata4 allocate statement is dim0 or 54310. The middle dimension of IRAINDUM in the h5ls output is 288. I’m guessing this isn’t what you want, but I’m not sure it should cause an error.

Daniel,

Thank you for pointing this out. I fixed it and my dimensions for rdata4 and dims are now (54310,288,1) but the issue still the same.

N

N, I think there’s something odd about your use of h5fopen_f:

Why would there be a datatype in the position where the call expects a file access flag such as H5F_ACC_RDONLY_F? I’m surprised that the compiler doesn’t catch that. Can you try that to see if it makes any difference?

G.

I’ve noticed that older compilers aren’t so strict with the type checking. The access flag is an INTEGER while the type object is an INTEGER(HID_T). If HID_T turns out to be the same word size as INTEGER (whose size will be implementation dependent) the compiler might not complain. I’ve recently moved to a newer compiler which catches these mistakes even though the code compiled and functioned fine under an older compiler.

Gheber,

Thanks for catching this. The compiler did not catch it, not sure why, maybe the type is not checked. I am not an expert with HDF5 and I changed the flag trying to troubleshoot my error and made that mistake.

I just changed back (see below) but that does not change anything

 CALL h5fopen_f(filename,H5F_ACC_RDONLY_F, file, error)

! Open group, file is the same variable identifier initialized by the h5open_f() subroutine.
! This gives the HDF5 library the link between the file and requested group to be opened.
CALL h5gopen_f(file, dsetname, group, error)

!Open an existing dataset IRAINDUM
CALL h5dopen_f(group, dsetIRAINDUM, dset_id1, error)
!Read data IRAINDUM
CALL h5dread_f(dset_id1,H5T_NATIVE_DOUBLE, rdata4, dims, error) The issue still here with error = -1 and rdata4 with all zeros, not reading the data from the file

N

Looking at my own code I see that I get a data space (h5dget_space_f) associated with the object corresponding to dset_id1 before doing the read. I don’t see that in your code.

If you are trying to learn HDF5 then you should probably look at some examples and the use of data space.

If all you want to do is do a simple read of an array, and by simple I mean no subsetting or other transformations, and get on with your work then I’d recommend using h5ltread_dataset_f.

On a related note, there is a either an Fortran90 or an Fortran 2003 interface provided with HDF5; if you are using HDF5-1.8 then the library defaulted to Fortan90 at build time, while for HDF5-1.10 the default is Fortran 2003. The Fortran 2003 is nicer since it does more of the bookkeeping for you.

Thanks for the explanation. I am trying just to read the data file and use it, I am not interested to learn HDF5 beyond that. I will follow your advice and see if that help me to figure out the issue.

Any progress? If not, can you compile and and run a simple example such as this? G.