Thank you for your help. Now it works. In the meantime, I managed to read the data with the attached script without initializing the FORTRAN interface and without defining the compound data type. This seems a shorter approach but I wonder whether this approach might lead to some erroneous results or not while reading data. Is the other one preferable over this one?

Regards,

Ekin


On 03/26/2012 06:09 PM, [email protected] wrote:
CALL h5open_f(hdferr)
program read_complexcompound

use hdf5

implicit none

type data
 real(4) :: a(2)
 real(8) :: b(3)
 integer :: c
end type data

type(data), dimension(4), target :: wdata

! This is the name of the data file we will read. 
character (len = 9), parameter :: filename  = "cc_res.h5"
character (len = 7), parameter :: dsetname1 = "ms_data"

integer         , parameter        :: ms_dim0 = 4
integer(hsize_t), dimension(1)     :: ms_dims = (/ms_dim0/), ndims


integer, parameter                :: arraydim0   = 2
integer(hsize_t), DIMENSION(1)    :: arraydims   = (/arraydim0/)
integer, parameter                :: arraydim1   = 3
integer(hsize_t), DIMENSION(1)    :: arraydims1  = (/arraydim1/)

integer(hid_t)  :: file_id, dspace_id, dset_id, memtype ! Handles
integer         :: hdferr, i
integer(hid_t)  :: s1_tid, s2_tid, s3_tid
type(c_ptr)     :: f_ptr_ms

 call h5open_f(hdferr)

 ! open file
 call h5fopen_f(filename, H5F_ACC_RDONLY_F, file_id, hdferr)

 ! open dataset
 call h5dopen_f(file_id, dsetname1, dset_id, hdferr)

 ! get the datatype
 call h5dget_type_f(dset_id, memtype, hdferr)

 ! read the data
 f_ptr_ms = c_loc(wdata(1))
 call h5dread_f(dset_id, memtype, f_ptr_ms, hdferr)

 do i=1, ms_dim0
   print *, wdata(i)%a, wdata(i)%b, wdata(i)%c
 end do

 ! close and release resources
 call h5dclose_f(dset_id, hdferr)
 call h5tclose_f(memtype, hdferr)
 call h5fclose_f(file_id, hdferr)

end program read_complexcompound
_______________________________________________
Hdf-forum is for HDF software users discussion.
[email protected]
http://mail.hdfgroup.org/mailman/listinfo/hdf-forum_hdfgroup.org

Reply via email to