Hi,
Please let me put it this way. I have a user-defined type in FORTRAN
called "ep_data" of dimension 4, i.e. ep_data(4). It has fields named
biomass, pob, qob, ... etc. and so on. Each field holds a scalar value.
For instance, if you print "ep_data(1)%biomass", it will give you, let's
say, "4". In other words, fields of "ep_data" are not arrays. I
succeeded to write this "ep_data" to HDF5 by using compound datatype. So
no problem up till here. However, I have another user-defined type
called "ms_data" in FORTRAN of size 7, i.e. , "ms_data(7)" and just like
"ep_data", it also has fields named biomass, mortality, qob, ... etc.
and so on. Differently from "ep_data" type, "ms_data" fields are arrays
of different size. For instance, if you print "ms_data(1)%biomass(:)"|,
you will get an array of real numbers. And if you print
"ms_data(1)%mortality(:)", you also get an array of real numbers of
different length that of "biomass" field. So, how can I store "ms_data"
in HDF5 format?
For your reference, my FORTRAN implementation of storing "ep_data" is
attached.
Regards,
Ekin
On 03/14/2012 10:00 AM, Ekin Akoglu wrote:
Hello,
I am sorry that I could not make myself clear. What I meant to say is
that I aim to form a compound datatype which comprises VL (variable
length) and fixed-length array fields/datatypes. In the example for
creating VL datatype, using a user-defined datatype which includes a
pointer is suggested (Example 27 on page 227 in the HDF user manual).
That is what I want to avoid but it seems it is the only way. What I
want to achieve is summarized in Figure 18 on page 238 in the HDF user
manual; a compound datatype built up of numerous VL and atomic datatypes.
Ekin
On 03/14/2012 07:16 AM, [email protected] wrote:
Hi,
suggestions about storing this data as a compound type with variable
length fields without using pointers as explained in
h5ex_t_vlen_F03.f90 [1] example script on HDF GROUP web site. Thank
you in advance for your concerns.
I don't understand what you mean by "not using pointers", do you mean
you don't want to use C_LOC and/or F2003 and still do the same thing
as h5ex_t_vlen_F03.f90? Can you explain further what in
h5ex_t_vlen_F03.f90 you want to avoid doing?
Scot
_______________________________________________
Hdf-forum is for HDF software users discussion.
[email protected]
http://mail.hdfgroup.org/mailman/listinfo/hdf-forum_hdfgroup.org
--
*Ekin Akoglu*
Research Assistant
Institute of Marine Sciences
Middle East Technical University
P.O. Box 28, 33731
Erdemli, Mersin
Turkey
Web: www.ims.metu.edu.tr
Email: [email protected] <mailto:[email protected]>
Phone: +90 324 521 34 34
GSM: +90 506 554 03 90
Fax: +90 324 521 23 27
_______________________________________________
Hdf-forum is for HDF software users discussion.
[email protected]
http://mail.hdfgroup.org/mailman/listinfo/hdf-forum_hdfgroup.org
--
*Ekin Akoglu*
Research Assistant
Institute of Marine Sciences
Middle East Technical University
P.O. Box 28, 33731
Erdemli, Mersin
Turkey
Web: www.ims.metu.edu.tr
Email: [email protected] <mailto:[email protected]>
Phone: +90 324 521 34 34
GSM: +90 506 554 03 90
Fax: +90 324 521 23 27
subroutine h5write(nvars, nstanzas, drows, dcols, ep_data, ms_data, ep_diet)
use statevartypesEcopath_mod
use iso_c_binding
use hdf5
implicit none
! This is the name of the data file we will read.
character (len = 9), parameter :: filename = "ep_res.h5"
character (len = 7), parameter :: dsetname0 = "ep_data" ! name of the Ecopath base dataset
character (len = 7), parameter :: dsetname1 = "ms_data" ! name of the Ecopath multistanza dataset
! variables inherited from Ecopath model
integer(8), intent(in) :: nvars, nstanzas, drows, dcols
type(ecopath_data), intent(in), target :: ep_data
type(multi_stanza), intent(in), target :: ms_data(nstanzas)
real(4), intent(in), target :: ep_diet(drows, dcols)
! in-subroutine variable declarations for ep_data
integer(8), parameter :: ep_dim0 = 52 ! dimension of ep_data
integer :: hdferr ! variable to handle errors
integer(hid_t) :: file_id, plist_id ! file identifier of the output file
integer(hid_t) :: dset_id ! dataset identifier
integer(hid_t) :: dtype_id, dt1_id ! dataset type identifier
integer(4) :: dspace_id ! dataspace identifier
integer(hid_t) :: memtype
integer(8) :: type_size, offset
integer(8) :: type_sizei, type_sizer
integer(hsize_t), DIMENSION(1) :: ep_dims = (/ep_dim0/)
type(c_ptr) :: f_ptr
! initialize FORTRAN interface
call h5open_f(hdferr)
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
call h5pset_preserve_f(plist_id, .TRUE., hdferr)
! create file, if it already exists overwrite (H%F_ACC_TRUNC_F)
call h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, hdferr)
! get size of each member in the compound datatype
call h5tget_size_f(H5T_NATIVE_INTEGER, type_sizei, hdferr)
call h5tget_size_f(H5T_NATIVE_REAL, type_sizer, hdferr)
type_size = (19 * type_sizer) + (5 * type_sizei)
! create the compound datatype for memory
call h5tcreate_f(H5T_COMPOUND_F, type_size, memtype, hdferr)
! insert members
offset = 0
call h5tinsert_f(memtype, "biomass", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "pob", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "qob", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "ee", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "poq", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "unass_q", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "detritus_import", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "immig", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "emig", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "emig_rate", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "ba", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "ba_rate", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "landings", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizei
call h5tinsert_f(memtype, "org_type", offset, H5T_NATIVE_INTEGER, hdferr)
offset = offset + type_sizei
call h5tinsert_f(memtype, "stanza", offset, H5T_NATIVE_INTEGER, hdferr)
offset = offset + type_sizei
call h5tinsert_f(memtype, "stanza_no", offset, H5T_NATIVE_INTEGER, hdferr)
offset = offset + type_sizei
call h5tinsert_f(memtype, "age_start", offset, H5T_NATIVE_INTEGER, hdferr)
offset = offset + type_sizei
call h5tinsert_f(memtype, "leading", offset, H5T_NATIVE_INTEGER, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "production", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "consumption", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "respiration", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "assimilation", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "eatenof", offset, H5T_NATIVE_REAL, hdferr)
offset = offset + type_sizer
call h5tinsert_f(memtype, "eatenby", offset, H5T_NATIVE_REAL, hdferr)
call h5screate_simple_f(1, ep_dims, dspace_id, hdferr)
call h5dcreate_f(file_id, dsetname0, memtype, dspace_id, dset_id, hdferr)
f_ptr = C_LOC(ep_data)
call h5dwrite_f(dset_id, memtype, f_ptr, hdferr)
end subroutine h5write
_______________________________________________
Hdf-forum is for HDF software users discussion.
[email protected]
http://mail.hdfgroup.org/mailman/listinfo/hdf-forum_hdfgroup.org