H5R (F03)

[ Top ] [ Modules ]

NAME

  MODULE H5R_PROVISIONAL

FILE

  fortran/src/H5Rff_F03.f90

PURPOSE

  This file contains Fortran 90 and Fortran 2003 interfaces for H5R functions.
  It contains the same functions as H5Rff_DEPRECIATE.f90 but includes the
  Fortran 2003 functions and the interface listings. This file will be compiled
  instead of H5Rff_DEPRECIATE.f90 if Fortran 2003 functions are enabled.

NOTES

                         *** IMPORTANT ***
  If you add a new H5R function you must add the function name to the
  Windows dll file 'hdf5_fortrandll.def' in the fortran/src directory.
  This is needed for Windows based operating systems.

h5rcreate_object_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rcreate_object_f

PURPOSE

  Creates reference to the object

INPUTS

  loc_id    - location identifier
  name      - name of the object at the specified location

OUTPUTS

  ref       - reference to the specified object
  hdferr:   - error code
               Success:  0
               Failure: -1

AUTHOR

  Elena Pourmal
  August 12, 1999

HISTORY

  Explicit Fortran interfaces were added for
  called C functions (it is needed for Windows
  port).  February 28, 2001

NOTES

  This is a module procedure for the h5rcreate_f subroutine.

SOURCE

  SUBROUTINE h5rcreate_object_f(loc_id, name, ref, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id   ! Location identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the object at location specified
                                           ! by loc_id identifier
    TYPE(hobj_ref_t_f), INTENT(INOUT), TARGET :: ref   ! Object reference
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5rcreate_ptr_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rcreate_ptr_f

PURPOSE

  Creates a reference.

INPUTS

  loc_id     - location identifier
  name       - name of the dataset at the specified location
  ref_type   - type of reference:
                H5R_OBJECT
                H5T_STD_REF_DSETREG

OUTPUTS

  ref        - reference created by the function call.
  hdferr     - error code
                  Success:  0
                  Failure: -1
 OPTIONAL
  space_id   - dataspace identifier that describes selected region

AUTHOR

  M. Scot Breitenfeld
  June 20, 2008

NOTES

  This is a module procedure for the h5rcreate_f
  subroutine where the output is a pointer.

SOURCE

  SUBROUTINE h5rcreate_ptr_f(loc_id, name, ref_type, ref, hdferr, space_id)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id     ! Location identifier
    CHARACTER(LEN=*), INTENT(IN) :: name     ! Name of the dataset at location specified
                                             ! by loc_id identifier
    INTEGER, INTENT(IN) :: ref_type          ! type of reference
    TYPE(C_PTR), INTENT(INOUT) :: ref        ! Reference created by the function call
    INTEGER, INTENT(OUT) :: hdferr           ! Error code
    INTEGER(HID_T), INTENT(IN), OPTIONAL :: space_id ! Dataset's dataspace identifier

h5rcreate_region_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rcreate_region_f

PURPOSE

  Creates reference to the dataset region

INPUTS

  loc_id        - location identifier
  name          - name of the dataset at the specified location
  space_id      - dataspace identifier that describes selected region

OUTPUTS

  ref           - reference to the dataset region
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  August 12, 1999

HISTORY

  Explicit Fortran interfaces were added for
  called C functions (it is needed for Windows
  port).  February 28, 2001

NOTES

  This is a module procedure for the h5rcreate_f subroutine.

SOURCE

  SUBROUTINE h5rcreate_region_f(loc_id, name, space_id, ref, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id   ! Location identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the dataset at location specified
                                           ! by loc_id identifier
    INTEGER(HID_T), INTENT(IN) :: space_id ! Dataset's dataspace identifier
    TYPE(hdset_reg_ref_t_f), INTENT(INOUT), TARGET :: ref ! Dataset region reference
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5rdereference_object_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rdereference_object_f

PURPOSE

  Opens the HDF5 object referenced

INPUTS

  dset_id  - identifier of the dataset containing
             reference
  ref      - reference to open

OUTPUTS

  obj_id   - object_identifier
  hdferr:  - error code
              Success:  0
              Failure: -1

AUTHOR

  Elena Pourmal
  August 12, 1999

HISTORY

  Explicit Fortran interfaces were added for
  called C functions (it is needed for Windows
  port).  February 28, 2001

NOTES

  This is a module procedure for the h5rdereference_f subroutine.

SOURCE

  SUBROUTINE h5rdereference_object_f(obj_id, ref, ref_obj_id, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: obj_id          ! Dataset identifier
    TYPE(hobj_ref_t_f), INTENT(IN), TARGET :: ref ! Object reference
    INTEGER(HID_T), INTENT(OUT) :: ref_obj_id     ! Object identifier
    INTEGER, INTENT(OUT) :: hdferr                ! Error code

h5rdereference_ptr_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rdereference_ptr_f

PURPOSE

  Opens the HDF5 object referenced.

INPUTS

  obj_id     - valid identifier for the file containing the
               referenced object or any object in that file.
  ref_type   - the reference type of ref.
  ref        - Reference to open.

OUTPUTS

  ref_obj_id - identifier of referenced object
  hdferr     - error code
                Success:  0
                Failure: -1

AUTHOR

  M. Scot Breitenfeld
  June 20, 2008

NOTES

  This is a module procedure for the h5rdereference_f
  subroutine using pointers.

SOURCE

  SUBROUTINE h5rdereference_ptr_f(obj_id, ref_type, ref, ref_obj_id, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: obj_id  ! Valid identifier for the file containing the
                                          !  referenced object or any object in that file.
    INTEGER, INTENT(IN) :: ref_type       ! The reference type of ref.
    TYPE(C_PTR), INTENT(IN) :: ref        ! Object reference
    INTEGER(HID_T), INTENT(OUT) :: ref_obj_id
                                          ! Identifier of referenced object
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5rdereference_region_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rdereference_region_f

PURPOSE

  Opens the dataset region

INPUTS

  dset_id       - identifier of the dataset containing
                  reference to teh regions
  ref           - reference to open

OUTPUTS

  obj_id        - dataspace identifier
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  August 12, 1999

HISTORY

  Explicit Fortran interfaces were added for
  called C functions (it is needed for Windows
  port).  February 28, 2001

NOTES

  This is a module procedure for the h5rdereference_f subroutine.

SOURCE

  SUBROUTINE h5rdereference_region_f(obj_id, ref, ref_obj_id, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: obj_id   ! Dataset identifier
    TYPE(hdset_reg_ref_t_f), INTENT(IN), TARGET :: ref   ! Object reference
    INTEGER(HID_T), INTENT(OUT) :: ref_obj_id  ! Dataspace identifier
    INTEGER, INTENT(OUT) :: hdferr          ! Error code

h5rget_name_object_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rget_name_object_f

PURPOSE

  Retrieves a name of a referenced object.

INPUTS

  loc_id    - Identifier for the dataset containing the reference or for the group that dataset is in.
  ref       - An object or dataset region reference.

OUTPUTS

  name      - A name associated with the referenced object or dataset region.

  hdferr:   - error code
               Success:  0
               Failure: -1

OPTIONAL PARAMETERS

  size     - The size of the name buffer.

AUTHOR

  M. Scot Breitenfeld
  March 28, 2008

 SOURCES
 or for the group that dataset is in.
 returning 0 (zero) if no name is associated
 with the identifier

h5rget_name_ptr_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rget_name_ptr_f

PURPOSE

  Retrieves a name of a referenced object.

INPUTS

  loc_id   - Identifier for the dataset containing the reference or
             for the group that dataset is in.
  ref_type - Type of reference.
  ref      - An object or dataset region reference.

OUTPUTS

  name     - A name associated with the referenced object or dataset ptr.

  hdferr   - error code
               Success:  0
               Failure: -1

OPTIONAL PARAMETERS

   size   - The size of the name buffer.

AUTHOR

  M. Scot Breitenfeld
  March 28, 2008

SOURCE

  SUBROUTINE h5rget_name_ptr_f(loc_id, ref_type, ref, name, hdferr, size)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id   ! Identifier for the dataset containing the reference
                                           !  or for the group that dataset is in.
    INTEGER, INTENT(IN) :: ref_type ! Type of reference.
    TYPE(C_PTR), INTENT(IN) :: ref  ! An object or dataset region reference.
    CHARACTER(LEN=*), INTENT(OUT) :: name  ! A name associated with the referenced object or dataset ptr.
    INTEGER, INTENT(OUT) :: hdferr         ! Error code
    INTEGER(SIZE_T), OPTIONAL, INTENT(OUT) :: size   ! The size of the name buffer,
                                                     ! returning 0 (zero) if no name is associated
                                                     ! with the identifier

h5rget_name_region_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rget_name_region_f

PURPOSE

  Retrieves a name of a dataset region.

INPUTS

  loc_id  - Identifier for the dataset containing the reference or
            for the group that dataset is in.
  ref     - An object or dataset region reference.

OUTPUTS

  name    - A name associated with the referenced object or dataset region.
  hdferr  - error code
              Success:  0
              Failure: -1

OPTIONAL PARAMETERS

  size    - The size of the name buffer.

AUTHOR

  M. Scot Breitenfeld
  March 28, 2008

SOURCE

  SUBROUTINE h5rget_name_region_f(loc_id, ref, name, hdferr, size)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id   ! Identifier for the dataset containing the reference
                                           ! or for the group that dataset is in.
    TYPE(hdset_reg_ref_t_f), INTENT(IN), TARGET :: ref ! Object reference
    INTEGER(SIZE_T), OPTIONAL, INTENT(OUT) :: size     ! The size of the name buffer,
                                                       ! returning 0 (zero) if no name is associated with the identifier
    CHARACTER(LEN=*), INTENT(OUT) :: name  ! A name associated with the referenced object or dataset region.
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5rget_obj_type_f

[ Top ] [ H5R (F03) ] [ Subroutines ]

NAME

  h5rget_obj_type_f

PURPOSE

  Retrieves the type of object that an object reference points to.

INPUTS

  loc_id   - Identifier for the dataset containing the reference or
             for the group that dataset is in.
  ref_type - Type of reference to query.
  ref      - Reference to query.

OUTPUTS

  obj_type - Type of referenced object. 
               H5G_UNKNOWN_F (-1)
               H5G_LINK_F      0
               H5G_GROUP_F     1
               H5G_DATASET_F   2
               H5G_TYPE_F      3
              
  hdferr   - error code
               Success:  0
               Failure: -1

AUTHOR

  M. Scot Breitenfeld
  Decemeber 17, 2008

SOURCE

  SUBROUTINE h5rget_obj_type_f(loc_id, ref_type, ref, obj_type, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: loc_id
    INTEGER, INTENT(IN) :: ref_type
    TYPE(C_PTR), INTENT(IN) :: ref
    INTEGER, INTENT(OUT) :: obj_type
    INTEGER, INTENT(OUT) :: hdferr