This is an archival copy of the Visualization Group's web page 1998 to 2017. For current information, please vist our group's new web page.

H5Part: Using the Fortran API

These references contain the information on how to access the H5Part API using FORTRAN bindings. All pointers are cast to haddr_t (a unint64_t) within the C/C++ code. In fortran, these pointers (handles) are carried as INTEGER*8


Opening Datafiles

Like the familiar OPEN in FORTRAN files can be opened to read and write. Different functions are used for the serial and parallel case.

FORTRAN Prototypes

Serial File
INTEGER*8 h5pt_openr
FUNCTION h5pt_openw(file)
in CHARACTER file(*) : the filename to open for writing

returns INTEGER*8 : and open filehandle for serial reads

INTEGER*8 h5pt_openw
FUNCTION h5pt_openw(file)
in CHARACTER file(*) : the filename to open for writing
returns INTEGER*8 : and open filehandle for serial writes


Parallel File
INTEGER*8 h5pt_openr_par
FUNCTION h5pt_openr_par(file,mpi_communicator)
in CHARACTER file(*) : the filename to open for writing
in INTEGER mpi_communicator : the MPI_Communicator used by the program
returns INTEGER*8 : and open filehandle for parallel reads


INTEGER*8 h5pt_openw_par
FUNCTION h5pt_openw_par(file,mpi_communicator)
in CHARACTER file(*) : the filename to open for writing
in INTEGER mpi_communicator : the MPI_Communicator used by the program
returns INTEGER*8 : and open filehandle for parallel reads

Example Use

include 'H5Part.inc'
INTEGER*8 file
...
file = h5pt_openw("testfilef.h5")
...


Closing Datafiles

To close the file, you simply use h5pt_close() for both parallel and serial files. You must call h5pt_close() on any file descriptor created by h5pt_open*() regardless of whether the file turns out to be valid or not.

FORTRAN Prototype
EXTERNAL h5pt_close
SUBROUTINE h5pt_close(filehandle)
in INTEGER*8 filehandle : close this open filehandle

Example Use
include 'H5Part.inc'
INTEGER*8 file
...
call h5pt_close(file)
...


Validating Datafiles

You can test if the file was opened successfully using the h5p_isvalid() function. It returns 1 if valid, 0 if invalid.

FORTRAN Prototype
INTEGER h5pt_isvalid
FUNCTION h5pt_isvalid(filehandle)
in INTEGER*8 filehandle: an open filehandle
returns INTEGER : 1 if the file is valid, 0 if it is not

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER status 
...
status = h5pt_isvalid(file)
...


Setting the Timestep

When writing data to a file the current time step must be set (even if there is only one). In a file with N time steps, the steps are numbered from 0 to N-1.

FORTRAN Prototype
EXTERNAL h5pt_setstep
SUBROUTINE h5pt_setstep(filehandle,step)
in INTEGER*8 filehandle : an open filehandle
in INTEGER step : Set the current timestep in the file to this

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER I
INTEGER nstep
...
do I=1,nstep
	call h5pt_setstep(file,I)
... more code ...
enddo


Setting the Number of Particles

This function's sole purpose is to prevent needless creation of new HDF5 DataSpace handles if the number of particles is invariant throughout the sim. That's its only reason for existence. After you call this subroutine, all subsequent operations will assume this number of particles will be written.

FORTRAN Prototype
EXTERNAL h5pt_setnpoints
SUBROUTINE h5pt_setnpoints(filehandle,npoints)
in INTEGER*8 filehandle : an open filehandle
in INTEGER*8 npoints : The number of particles on *this* processor

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER*8 npoints

...
call h5pt_setnpoints(file,npoints)
...

Writing Datasets

After setting the number of particles with h5pt_setnpoints() and the current timestep using h5pt_setstep(), you can start writing datasets into the file. Each dataset has a name associated with it (chosen by the user) in order to facilitate later retrieval. The writing routines also implicitly store the datatype of the array so that the array can be reconstructed properly on other systems with incompatible type representations. The data is committed to disk before the routine returns. All data that is written after setting the timestep is associated with that timestep. While the number of particles can change for each timestep, you cannot change the number of particles in the middle of a given timestep.

FORTRAN Prototypes

The two data types supported for the moment are REAL*8 and INTEGER*8 (float64 and int64).

EXTERNAL h5pt_writedata_r8
SUBROUTINE h5pt_writedata_r8(filehandle,name,data)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the data we are writing eg. "X" or "Y" or "PX" etc...
in REAL*8 data(*) : The dataarray to write


EXTERNAL h5pt_writedata_i8
SUBROUTINE h5pt_writedata_i8(filehandle,name,data)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the data we are writing eg. "X" or "Y" or "PX" etc...
in INTEGER*8 data(*) : The dataarray to write

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER nstep
INTEGER I
REAL*8,ALLOCATABLE:: X(:)

...
do I=1,nstep
	call h5pt_setstep(file,I)
	call h5pt_writedata_r8(file,"x",X)
enddo
...

Reading the Number of Time Steps

This reads the number of datasteps that are currently stored in the datafile. It works for both reading and writing of files, but is probably only typically used when you are reading.

FORTRAN Prototypes
INTEGER h5pt_getnsteps
FUNCTION h5pt_getnsteps(filehandle)
in INTEGER*8 filehandle : an open filehandle
returns INTEGER : number of timesteps stored in the file

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER nstep

file = h5pt_openr("testfilef.h5")
nstep = h5pt_getnsteps(file)

Reading the Number of Particles

This reads the number of particles that are currently stored in the current time step. It will arbitrarily select a timestep if you haven't already set the timestep with H5PartSetStep().

FORTRAN Prototypes
INTEGER h5pt_getnpointss
FUNCTION h5pt_getnpoints(filehandle)
in INTEGER*8 filehandle : an open filehandle
returns INTEGER : number of particles in the current time step

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER*8 npoints
INTEGET step;

file = h5pt_openr("testfilef.h5")
call h5pt_setstep(file,0)
npoints = h5pt_getnpoints(file)
...

Reading Datasets

After setting the time step and getting the number of particles to allocate the data arrays, you can start to read the data.

FORTRAN Prototypes
INTEGER h5pt_readdata_r8
FUNCTION h5pt_readdata_r8(filehandle,name,data)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the data we are writing, eg. "X" or "Y" or "PX" etc...
out REAL*8 data(*) : The data array to read. The number of points to read is either the number within the view setby h5pt_setview() or the default (the total number of particles in the file).
Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER err
INTEGER*8,ALLOCATABLE:: ID(:)

...
call h5pt_setstep(file,step)
err=h5pt_readdata_i8(file,"id",ID)
...

Reading the Number and Names of Datasets

H5Part provides funtions to find out how many datasets are stored at a particular timestep and what their names are if you don't know what they are a-priori.

FORTRAN Prototypes
INTEGER h5pt_getndatasets
FUNCTION h5pt_getndatasets(filehandle)
in INTEGER*8 filehandle : an open filehandle
returns INTEGER*8 : number of datasets stored per timestep

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER ndata

...
call h5pt_setstep(file,1)
ndata = h5pt_getndatasets(file)
...

FORTRAN Prototypes
INTEGER h5pt_getdatasetname
FUNCTION h5pt_getdatasetname(filehandle,index,name)
in INTEGER*8 filehandle : an open filehandle
in INTEGER index : Index for a given dataset name
out CHARACTER name(*) returns the name of the dataset at that index
returns INTEGER, 1 on success 0 on failure.

Example Use
include 'H5Part.inc'
INTEGER*8 file
INTEGER err
CHARACTER,ALLOCATABLE:: name(:)

...
err=h5pt_getdatasetname(file, 1, name)
...

Attributes Interface

In the current H5Part implemtation there are two types of attributes: file attributes which are bound to the file and step attributes which are bound to the current timestep. You must set the timestep explicitly before writing the attributes (just as you must do when you write a new dataset. Currently there are no attributes that are bound to a particular data array, but this could easily be done if required.

FORTRAN Prototypes
INTEGER h5pt_getnstepattribs
FUNCTION h5pt_getnstepattribs(filehandle)
in INTEGER*8 filehandle : an open filehandle
returns INTEGER : number of attributes bound to this particular step

INTEGER h5pt_getnfileattribs
FUNCTION h5pt_getnfileattribs(filehandle)
in INTEGER*8 filehandle : an open filehandle
returns INTEGER : number of attributes bound to the file

INTEGER h5pt_getstepattribinfo
FUNCTION h5pt_getstepattribinfo(filehandle,idx,attribname,nelem)
in INTEGER*8 filehandle : an open filehandle
in INTEGER idx : index of the attribute being queried
out CHARACTER name(*) : The name of the attribute
out INTEGER nelem : Number of elements in the attrib array
returns INTEGER, 1 on success 0 on failure.

INTEGER h5pt_getfileattribinfo
FUNCTION h5pt_getfileattribinfo(filehandle,idx,attribname,nelem)
in INTEGER*8 filehandle : an open filehandle
in INTEGER idx : index of the attribute being queried
out CHARACTER name(*) : The name of the attribute
out INTEGER nelem : Number of elements in the attrib array
returns INTEGER, 1 on success 0 on failure.


Writing Attributes

An attribute can be bound to the file or after setting the time step to this time step.

FORTRAN Prototypes
INTEGER h5pt_writefileattrib_r8
FUNCTION h5pt_writefileattrib_r8(filehandle,name,attrib,nelem)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the attribute
in REAL*8 attrib(*) : The array of data to write into the attribute
in INTEGER nelem : Number of elements in the attrib array
returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_writefileattrib_i8
FUNCTION h5pt_writefileattrib_i8(filehandle,name,attrib,nelem)
in INTEGER*8 filehandle : The filehandle
in CHARACTER name(*) : The name of the attribute
in INTEGER*8 attrib(*) : The array of data to write into the attribute
in INTEGER nelem : Number of elements in the attrib array
returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_writefileattrib_string
FUNCTION h5pt_writefileattrib_string(filehandle,name,string)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the attribute
in CHARACTER*8 attrib(*) : The array of data to write into the attribute
returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_writestepattrib_r8
FUNCTION h5pt_writestepattrib_r8(filehandle,name,attrib,nelem)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the attribute
in REAL*8 attrib(*) : The array of data to write into the attribute
in INTEGER nelem : Number of elements in the attrib array returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_writestepattrib_i8
FUNCTION h5pt_writestepattrib_i8(filehandle,name,attrib,nelem)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the attribute
in INTEGER*8 attrib(*) : The array of data to write into the attribute
in INTEGER nelem : Number of elements in the attrib array
returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_writestepattrib_string
FUNCTION h5pt_writestepattrib_string(filehandle,name,string)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER name(*) : The name of the attribute
in CHARACTER*8 attrib(*) : The array of data to write into the attribute
returns INTEGER, 1 on success 0 on failure
Example Use
include 'H5Part.inc'
INTEGER*8 file
REAL*8 REALTIME
INTEGER err

...
err=h5pt_writefileattrib_string(file,"Annotation","Testing 1 2 3")
err=h5pt_writestepattrib_r8(file,"RealTime",REALTIME,1)
...


Reading Attributes

As with the writing of attributes, there are two basic reading interfaces one that reads file bound attributes and one that reads step bound attributes. If the step is not set the current one will be used.

FORTRAN Prototypes
INTEGER h5pt_readstepattrib
FUNCTION h5pt_readstepattrib(filehandle,name,data)
in INTEGER*8 filehandle : an open filehandle
in CHARACTER attributename(*) : name of the attribute to read
out data(*) : the attribute data will be read into this array
returns INTEGER, 1 on success 0 on failure

INTEGER h5pt_readfileattrib
FUNCTION h5pt_readfileattrib(filehandle,name,data)
in INTEGER*8 filehandle an open filehandle
in CHARACTER attributename(*) : name of the attribute to read
out data(*) : the attribute data will be read into this array
returns INTEGER, 1 on success 0 on failure
Example Use
include 'H5Part.inc'
INTEGER*8 file
REAL*8 REALTIME

...
call h5pt_setstep(file,0)
err=h5pt_readstepattrib(file,"RealTime",data)
...