hdf5_obj Derived Type

type, public :: hdf5_obj

A utility to read/write files in HDF5 format


Inherits

type~~hdf5_obj~~InheritsGraph type~hdf5_obj hdf5_obj type~hashtbl_obj hashtbl_obj type~hdf5_obj->type~hashtbl_obj tbl type~parallel_obj parallel_obj type~hdf5_obj->type~parallel_obj parallel type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec MPI_Datatype MPI_Datatype type~parallel_obj->MPI_Datatype REAL_SP, REAL_DP, REAL_WP, COMPLEX_SP, COMPLEX_DP, COMPLEX_WP, INTEGER, INT8, LOGICAL type~communicators communicators type~parallel_obj->type~communicators comm type~patch patch type~parallel_obj->type~patch rank MPI_Comm MPI_Comm type~communicators->MPI_Comm w, g type~sllist_obj->type~sllist_obj child

Inherited by

type~~hdf5_obj~~InheritedByGraph type~hdf5_obj hdf5_obj type~bc_set bc_set type~bc_set->type~hdf5_obj hdf5 type~block_obj block_obj type~bc_set->type~block_obj block type~region_obj region_obj type~bc_set->type~region_obj region type~block_obj->type~hdf5_obj hdf5 type~cdifs_obj cdifs_obj type~cdifs_obj->type~hdf5_obj hdf5 type~cdifs_obj->type~bc_set bcs type~cdifs_obj->type~block_obj block type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~eulerian_set eulerian_set type~cdifs_obj->type~eulerian_set fields type~hypre_obj hypre_obj type~cdifs_obj->type~hypre_obj hypre, VFSolver type~marker_set marker_set type~cdifs_obj->type~marker_set IB type~op_obj op_obj type~cdifs_obj->type~op_obj op type~respart_set ResPart_set type~cdifs_obj->type~respart_set RP type~eulerian_obj_i eulerian_obj_i type~cdifs_obj->type~eulerian_obj_i maskV type~eulerian_obj_r eulerian_obj_r type~cdifs_obj->type~eulerian_obj_r V, P, dP, ibS, ibVF, ibF, ibN, Vold, resV, rhs, divu, Vm, srcV type~grans_obj grans_obj type~grans_obj->type~hdf5_obj hdf5 type~grans_obj->type~bc_set bcs type~grans_obj->type~block_obj block type~grans_obj->type~collision_obj collisions type~grans_obj->type~eulerian_set fields type~grans_obj->type~hypre_obj VFSolver type~grans_obj->type~marker_set IB type~grans_obj->type~op_obj op type~grans_obj->type~respart_set RP type~grans_obj->type~eulerian_obj_r ibVF, PVF, ibS, Fp, ibF, ibN, rhs type~particle_set particle_set type~grans_obj->type~particle_set PP type~h5hut_obj h5hut_obj type~h5hut_obj->type~hdf5_obj hdf5 type~collision_obj->type~block_obj cblock type~collision_obj->type~marker_set IB type~collision_obj->type~respart_set RP type~collision_obj->type~particle_set PP type~eulerian_obj_base eulerian_obj_base type~eulerian_obj_base->type~block_obj block type~eulerian_set->type~block_obj block type~eulerian_ptr eulerian_ptr type~eulerian_set->type~eulerian_ptr field type~hypre_obj->type~block_obj block type~hypre_obj->type~eulerian_obj_i irow type~lagrangian_set lagrangian_set type~lagrangian_set->type~block_obj block type~marker_set->type~bc_set bcs type~marker_set->type~lagrangian_set type~marker_set->type~op_obj op type~op_obj->type~block_obj block type~region_obj->type~block_obj region type~respart_set->type~bc_set bcs type~respart_set->type~lagrangian_set type~respart_set->type~marker_set ib type~respart_set->type~op_obj op type~solid_set solid_set type~solid_set->type~block_obj block type~solid_obj solid_obj type~solid_set->type~solid_obj p type~eulerian_obj_i->type~eulerian_obj_base type~eulerian_obj_r->type~eulerian_obj_base type~eulerian_ptr->type~eulerian_obj_base p type~particle_set->type~lagrangian_set type~particle_set->type~op_obj op type~solid_obj->type~marker_set

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: filename

file to read/write

type(parallel_obj), public, pointer :: parallel => null()

Associated parallel structure

integer(kind=HID_T), private :: fid

File identifier

logical, private :: is_open = .false.

Switch for when file is open/closed

integer(kind=HID_T), private :: plistid

Property list identifier

type(hashtbl_obj), private :: tbl

Hash table


Type-Bound Procedures

procedure, public :: Close => hdf5_obj_Close

  • private impure subroutine hdf5_obj_Close(this)

    Closes hdf5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

procedure, public :: CloseGroup => hdf5_obj_CloseGroup

  • private impure subroutine hdf5_obj_CloseGroup(this, groupname)

    Closes an HDF5 group and removes it from the hashtable.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Group to close

procedure, public :: CreateGroup => hdf5_obj_CreateGroup

  • private impure subroutine hdf5_obj_CreateGroup(this, groupname)

    Creates a group (analogous to directory) in an HDF5 file and updates hash table.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Group name

procedure, public :: Finalize => hdf5_obj_Final

  • private impure subroutine hdf5_obj_Final(this)

    Finalizes object and frees memory.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

procedure, public :: GetNPoints => hdf5_obj_GetNPoints

  • private impure function hdf5_obj_GetNPoints(this, groupname, name) result(val)

    Returns the number of points in a dataset given by name under group given by name.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Parent group name

    character(len=*), intent(in) :: name

    Dataset name

    Return Value integer

    Result

procedure, public :: Initialize => hdf5_obj_Init

  • private impure subroutine hdf5_obj_Init(this, parallel)

    Initializes the hdf5 object.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    type(parallel_obj), intent(in), target :: parallel

    Parallel structure to point to

procedure, public :: Open => hdf5_obj_Open

  • private impure subroutine hdf5_obj_Open(this, name, flag)

    Opens a hdf5 file given by name with mode stated by flag. This can take one of these values: 'R' for read only 'W' for write only (will delete existing file) 'RW' for read-write

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: name

    Filename

    character(len=*), intent(in) :: flag

    Access mode

procedure, public :: OpenGroup => hdf5_obj_OpenGroup

  • private impure subroutine hdf5_obj_OpenGroup(this, groupname)

    Opens a group (analogous to directory) in an HDF5 file and updates hash table.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Group name

generic, public :: Read => hdf5_obj_Read3D, hdf5_obj_Read1D

  • private impure subroutine hdf5_obj_Read3D(this, groupname, name, array, lo, hi)

    Reads a 3D dataset located under groupname and given by name.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Parent group containing the dataset

    character(len=*), intent(in) :: name

    Dataset name

    class(*), intent(out), target :: array(:,:,:)

    Data array

    integer, intent(in) :: lo(3)

    Low bounds

    integer, intent(in) :: hi(3)

    High bounds

  • private impure subroutine hdf5_obj_Read1D(this, groupname, name, array, offset)

    Reads a 1D dataset located under groupname and given by name. If no offset is provided, uses default file view. Otherwise, sets file view manually.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Parent group containing the dataset

    character(len=*), intent(in) :: name

    Dataset name

    class(*), intent(out), target :: array(:)

    Data array

    integer, intent(in), optional :: offset

    Indicates number of elements to skip before reading

generic, public :: ReadAttributes => hdf5_obj_ReadAttributes0D, hdf5_obj_ReadAttributes1D

  • private impure subroutine hdf5_obj_ReadAttributes0D(this, groupname, label, val)

    Read a scalar attribute under a given group.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    Attribute label

    class(*), intent(out), target :: val

    Attribute value

  • private impure subroutine hdf5_obj_ReadAttributes1D(this, groupname, label, val)

    Read a 1-D array of attributes under a given group.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    Attribute label

    class(*), intent(out), target :: val(:)

    Attribute values

procedure, public :: ReadCoord => hdf5_obj_ReadCoord

  • private impure subroutine hdf5_obj_ReadCoord(this, groupname, name, Coord)

    Reads coordinates from HDF5 file. Only the root MPI rank does the reading, and then broadcasts to other MPI ranks.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(out), target :: Coord(:)

    1-D Coordinates

procedure, public :: ReadDatasetNames => hdf5_obj_ReadDatasetNames

  • private impure subroutine hdf5_obj_ReadDatasetNames(this, basegroup, names)

    Reads the dataset names under a given base group in an HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: basegroup

    Base group to explore

    character(len=str64), intent(out), allocatable :: names(:)

    Dataset names under the base group

procedure, public :: ReadGroupNames => hdf5_obj_ReadGroupNames

  • private impure subroutine hdf5_obj_ReadGroupNames(this, basegroup, names)

    Reads the groups (i.e., directories) under a given base group in an HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: basegroup

    Base group to explore

    character(len=str64), intent(out), allocatable :: names(:)

    Names of groups under the base group

generic, public :: Write => hdf5_obj_Write3D, hdf5_obj_Write1D

  • private impure subroutine hdf5_obj_Write3D(this, groupname, name, array, lo, hi)

    Writes Eulerian/3D data to a HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(in), target :: array(:,:,:)

    3-D data array

    integer, intent(in) :: lo(3)

    Low bounds

    integer, intent(in) :: hi(3)

    High bounds

  • private impure subroutine hdf5_obj_Write1D(this, groupname, name, array)

    Writes an array/1D data to a HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(in), target :: array(:)

    1-D data array

generic, public :: WriteAttributes => hdf5_obj_WriteAttributes0D, hdf5_obj_WriteAttributes1D

  • private impure subroutine hdf5_obj_WriteAttributes0D(this, groupname, label, val)

    Writes a scalar attribute.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    attribute label

    class(*), intent(in), target :: val

    Attribute label

  • private impure subroutine hdf5_obj_WriteAttributes1D(this, groupname, label, val)

    Writes an array of attributes.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    attribute label

    class(*), intent(in), target :: val(:)

    Attribute labels

procedure, public :: WriteCoord => hdf5_obj_WriteCoord

  • private impure subroutine hdf5_obj_WriteCoord(this, groupname, name, Coord)

    Writes coordinates to HDF5 file. Only the root MPI rank does the writing.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(in), target :: Coord(:)

    1-D Coordinates

procedure, private, nopass :: FixGroupName => hdf5_obj_FixGroupName

  • private pure function hdf5_obj_FixGroupName(groupname) result(val)

    Function that will append and prepend '/' if missing.

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: groupname

    Return Value character(len=:), allocatable

procedure, private :: GetGroupObject => hdf5_obj_GetGroupObject

  • private impure function hdf5_obj_GetGroupObject(this, groupname) result(val)

    Returns the HDF5 object id of the group.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(in) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Name of region

    Return Value integer(kind=HID_T)

procedure, private :: hdf5_obj_Read1D

  • private impure subroutine hdf5_obj_Read1D(this, groupname, name, array, offset)

    Reads a 1D dataset located under groupname and given by name. If no offset is provided, uses default file view. Otherwise, sets file view manually.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Parent group containing the dataset

    character(len=*), intent(in) :: name

    Dataset name

    class(*), intent(out), target :: array(:)

    Data array

    integer, intent(in), optional :: offset

    Indicates number of elements to skip before reading

procedure, private :: hdf5_obj_Read3D

  • private impure subroutine hdf5_obj_Read3D(this, groupname, name, array, lo, hi)

    Reads a 3D dataset located under groupname and given by name.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Parent group containing the dataset

    character(len=*), intent(in) :: name

    Dataset name

    class(*), intent(out), target :: array(:,:,:)

    Data array

    integer, intent(in) :: lo(3)

    Low bounds

    integer, intent(in) :: hi(3)

    High bounds

procedure, private :: hdf5_obj_ReadAttributes0D

  • private impure subroutine hdf5_obj_ReadAttributes0D(this, groupname, label, val)

    Read a scalar attribute under a given group.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    Attribute label

    class(*), intent(out), target :: val

    Attribute value

procedure, private :: hdf5_obj_ReadAttributes1D

  • private impure subroutine hdf5_obj_ReadAttributes1D(this, groupname, label, val)

    Read a 1-D array of attributes under a given group.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    Attribute label

    class(*), intent(out), target :: val(:)

    Attribute values

procedure, private :: hdf5_obj_Write1D

  • private impure subroutine hdf5_obj_Write1D(this, groupname, name, array)

    Writes an array/1D data to a HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(in), target :: array(:)

    1-D data array

procedure, private :: hdf5_obj_Write3D

  • private impure subroutine hdf5_obj_Write3D(this, groupname, name, array, lo, hi)

    Writes Eulerian/3D data to a HDF5 file.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: name

    Variable name

    class(*), intent(in), target :: array(:,:,:)

    3-D data array

    integer, intent(in) :: lo(3)

    Low bounds

    integer, intent(in) :: hi(3)

    High bounds

procedure, private :: hdf5_obj_WriteAttributes0D

  • private impure subroutine hdf5_obj_WriteAttributes0D(this, groupname, label, val)

    Writes a scalar attribute.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    attribute label

    class(*), intent(in), target :: val

    Attribute label

procedure, private :: hdf5_obj_WriteAttributes1D

  • private impure subroutine hdf5_obj_WriteAttributes1D(this, groupname, label, val)

    Writes an array of attributes.

    Arguments

    Type IntentOptional Attributes Name
    class(hdf5_obj), intent(inout) :: this

    A HDF5 object

    character(len=*), intent(in) :: groupname

    Groupname

    character(len=*), intent(in) :: label

    attribute label

    class(*), intent(in), target :: val(:)

    Attribute labels