H5P (F03)

[ Top ] [ Modules ]

NAME

  H5P_PROVISIONAL

PURPOSE

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

NOTES

                         *** IMPORTANT ***
  If you add a new H5P 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.

h5pget_double

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pget_double

PURPOSE

  Gets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify

OUTPUTS

  value         - value of property
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pget_double(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id  ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to modify
    DOUBLE PRECISION,   INTENT(OUT), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5pcreate_class_f

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pcreate_class_f

PURPOSE

  Create a new property list class

INPUTS

  parent        - Property list identifier of the parent class
                  Possible values include:
                   H5P_ROOT_F
                   H5P_FILE_CREATE_F
                   H5P_FILE_ACCESS_F
                   H5P_DATASET_CREATE_F
                   H5P_DATASET_XFER_F
                   H5P_FILE_MOUNT_F
  name          - name of the class we are creating

OUTPUTS

  class         - porperty list class identifier
  hdferr:       - error code

  Success: 0
  Failure: -1

OPTIONAL PARAMETERS

  H5P_cls_create_func_t (create) - Callback routine called when a property list is created
  create_data                    - User pointer to any class creation information needed
  H5P_cls_copy_func_t   (copy)   - Callback routine called when a property list is copied
  copy_data                      - User pointer to any class copy information needed
  H5P_cls_close_func_t  (close)  - Callback routine called when a property list is being closed
  close_data                     - User pointer to any class close information needed

AUTHOR

  Elena Pourmal
  October 9, 2002

HISTORY

  Added callback arguments
  M. Scot Breitenfeld, July 3, 2008

SOURCE

  SUBROUTINE h5pcreate_class_f(parent, name, class, hdferr, create, create_data, copy, copy_data, close, close_data)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: parent  ! parent property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! name of property tocreate
    INTEGER(HID_T), INTENT(OUT) :: class  ! property list class identifier
    INTEGER, INTENT(OUT) :: hdferr        ! Error code
    TYPE(C_PTR), OPTIONAL :: create_data, copy_data, close_data
    TYPE(C_FUNPTR), OPTIONAL :: create, copy, close

h5pget_char

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pget_char

PURPOSE

  Gets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify

OUTPUTS

  value         - value of property
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pget_char(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id   ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of property to modify
    CHARACTER(LEN=*), INTENT(OUT) :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5pget_integer

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pget_integer

PURPOSE

  Gets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify

OUTPUTS

  value         - value of property
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pget_integer(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id    ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name    ! Name of property to modify
    INTEGER,   INTENT(OUT), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr          ! Error code

h5pget_real

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pget_real

PURPOSE

  Gets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify

OUTPUTS

  value         - value of property
  hdferr:       - error code
                   Success:  0
                   Failure: -1

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pget_real(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
    REAL,   INTENT(OUT), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr       ! Error code

h5pinsert_char

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pinsert_char

PURPOSE

  Registers a temporary property with a property list class.

INPUTS

  plist         - property list identifier
                  permanent property within
  name          - name of property to insert
  size          - size of property in bytes
  value         - initial value for the property

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pinsert_char(plist, name, size, value, hdferr)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: plist      ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name     ! Name of property to insert
    INTEGER(SIZE_T), INTENT(IN) :: size      ! Size of property value
    CHARACTER(LEN=*),   INTENT(IN) :: value  ! Property value
    INTEGER, INTENT(OUT) :: hdferr           ! Error code

h5pinsert_double

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pinsert_double

PURPOSE

  Registers a temporary property with a property list class.

INPUTS

  plist         - property list identifier
                  permanent property within
  name          - name of property to insert
  size          - size of property in bytes
  value         - initial value for the property

OUTPUTS

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

OPTIONAL PARAMETERS

  NONE

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pinsert_double(plist, name, size, value, hdferr)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: plist   ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to insert
    INTEGER(SIZE_T), INTENT(IN) :: size   ! Size of the property value
    DOUBLE PRECISION, INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5pinsert_integer

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pinsert_integer

PURPOSE

  Registers a temporary property with a property list class.

INPUTS

  plist         - property list identifier
  name          - name of property to insert
  size          - size of property in bytes
  value         - initial value for the property

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pinsert_integer(plist, name, size, value, hdferr)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: plist    ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of property to insert
    INTEGER(SIZE_T), INTENT(IN) :: size    ! Size of the property value
    INTEGER,   INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5pinsert_ptr

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pinsert_ptr

PURPOSE

  Registers a temporary property with a property list class.

INPUTS

  plist         - property list identifier
                  permanent property within
  name          - name of property to insert
  size          - size of property in bytes
  value         - initial value for the property

OUTPUTS

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

AUTHOR

  M. Scot Breitenfeld
  June 24, 2008

SOURCE

  SUBROUTINE h5pinsert_ptr(plist, name, size, value, hdferr)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: plist  ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
    INTEGER(SIZE_T), INTENT(IN) :: size  ! Size of property value
    TYPE(c_ptr),   INTENT(IN) :: value   ! Property value
    INTEGER, INTENT(OUT) :: hdferr       ! Error code

h5pinsert_real

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pinsert_real

PURPOSE

  Registers a temporary property with a property list class.

INPUTS

  plist         - property list identifier
                  permanent property within
  name          - name of property to insert
  size          - size of property in bytes
  value         - initial value for the property

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pinsert_real(plist, name, size, value, hdferr)
    USE iso_c_binding
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: plist   ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to insert
    INTEGER(SIZE_T), INTENT(IN) :: size   ! Size of the property value
    REAL,   INTENT(IN), TARGET :: value   ! Property value
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5pregister_char

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pregister_char

PURPOSE

  Registers a permanent property with a property list class.

INPUTS

  class         - property list class to register
                  permanent property within
  name          - name of property to register
  size          - size of property in bytes
  value         - default value for property in newly
                  created property lists

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pregister_char(class, name, size, value, hdferr)
    USE ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: class     ! Property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name    ! Name of property to register
    INTEGER(SIZE_T), INTENT(IN) :: size     ! size of the property value
    CHARACTER(LEN=*),   INTENT(IN) :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr          ! Error code

h5pregister_double

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pregister_double

PURPOSE

  Registers a permanent property with a property list class.

INPUTS

  class         - property list class to register
                  permanent property within
  name          - name of property to register
  size          - size of property in bytes
  value         - default value for property in newly
                  created property lists

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pregister_double(class, name, size, value, hdferr)
    USE ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: class  ! Property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
    INTEGER(SIZE_T), INTENT(IN) :: size  ! size of the property value
    DOUBLE PRECISION,   INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr       ! Error code

h5pregister_integer

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pregister_integer

PURPOSE

  Registers a permanent property with a property list class.

INPUTS

  class         - property list class to register
                  permanent property within
  name          - name of property to register
  size          - size of property in bytes
  value         - default value for property in newly
                  created property lists

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pregister_integer(class, name, size, value, hdferr)
    USE ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: class    ! Property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of property to register
    INTEGER(SIZE_T), INTENT(IN) :: size    ! Size of the property value
    INTEGER,   INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5pregister_ptr

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pregister_ptr

PURPOSE

  Registers a permanent property with a property list class.

INPUTS

  class         - property list class to register
                  permanent property within
  name          - name of property to register
  size          - size of property in bytes
  value         - default value for property in newly
                  created property lists

OUTPUTS

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

AUTHOR

  M. Scot Breitenfeld
  June 24, 2008

SOURCE

  SUBROUTINE h5pregister_ptr(class, name, size, value, hdferr)
    USE ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: class   ! Property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to register
    INTEGER(SIZE_T), INTENT(IN) :: size   ! Size of the property value
    TYPE(C_PTR), INTENT(IN) :: value      ! Property value
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5pregister_real

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pregister_real

PURPOSE

  Registers a permanent property with a property list class.

INPUTS

  class         - property list class to register
                  permanent property within
  name          - name of property to register
  size          - size of property in bytes
  value         - default value for property in newly
                  created property lists

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 10, 2002

SOURCE

  SUBROUTINE h5pregister_real(class, name, size, value, hdferr)
    USE ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: class   ! Property list class identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to register
    INTEGER(SIZE_T), INTENT(IN) :: size   ! size of the property value
    REAL,   INTENT(IN), TARGET :: value   ! Property value
    INTEGER, INTENT(OUT) :: hdferr        ! Error code

h5pset(get)fill_value_f

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pset(get)fill_value_f

PURPOSE

  Sets(gets) fill value for a dataset creation property list

INPUTS

  prp_id        - dataset creation property list identifier
  type_id       - datatype identifier for fill value
  fillvalue     - fill value

OUTPUTS

  type_id       - datatype identifier for fill value
  fillvalue     - fill value
  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).  March 14, 2001

  Added the recommended way of passing fillvalue
  and that is by passing the C address, all other
  ways are obsolete and should be avoided. June, 2008 MSB

NOTES

  h5pset(get)fill_value_f function is overloaded to support
  INTEGER, REAL, DOUBLE PRECISION and CHARACTER dtatypes.

SOURCE

  SUBROUTINE h5pset_fill_value_integer(prp_id, type_id, fillvalue, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id  ! Property list identifier
    INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
                                          ! of fillvalue datatype
                                          ! (in memory)
    INTEGER, INTENT(IN), TARGET :: fillvalue   ! Fillvalue
    INTEGER, INTENT(OUT) :: hdferr  ! Error code

h5pset_char

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pset_char

PURPOSE

  Sets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify
  value         - value to set property to

OUTPUTS

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

OPTIONAL PARAMETERS

  NONE

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pset_char(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id    ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name    ! Name of property to modify
    CHARACTER(LEN=*),   INTENT(IN) :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr          ! Error code

h5pset_double

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pset_double

PURPOSE

  Sets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify
  value         - value to set property to

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pset_double(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id  ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of property to modify
    DOUBLE PRECISION,   INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr                  ! Error code

h5pset_integer

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pset_integer

PURPOSE

  Sets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify
  value         - value to set property to

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pset_integer(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id   ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of property to modify
    INTEGER,   INTENT(IN), TARGET :: value ! Property value
    INTEGER, INTENT(OUT) :: hdferr         ! Error code

h5pset_real

[ Top ] [ H5P (F03) ] [ Subroutines ]

NAME

  h5pset_real

PURPOSE

  Sets a property list value

INPUTS

  prp_id        - iproperty list identifier to modify
  name          - name of property to modify
  value         - value to set property to

OUTPUTS

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

AUTHOR

  Elena Pourmal
  October 9, 2002

SOURCE

  SUBROUTINE h5pset_real(prp_id, name, value, hdferr)
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
    CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
    REAL,   INTENT(IN), TARGET :: value  ! Property value
    INTEGER, INTENT(OUT) :: hdferr       ! Error code