summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Pff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Pff.f90')
-rw-r--r--fortran/src/H5Pff.f902984
1 files changed, 1492 insertions, 1492 deletions
diff --git a/fortran/src/H5Pff.f90 b/fortran/src/H5Pff.f90
index 48d36ab..50aad81 100644
--- a/fortran/src/H5Pff.f90
+++ b/fortran/src/H5Pff.f90
@@ -1,4 +1,4 @@
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
! All rights reserved. *
@@ -11,7 +11,7 @@
! is linked from the top-level documents page. It can also be found at *
! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
! access to either file, you may request a copy from help@hdfgroup.org. *
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
!
! This file contains Fortran90 interfaces for H5P functions.
@@ -25,7 +25,7 @@
MODULE PROCEDURE h5pset_fill_value_real
MODULE PROCEDURE h5pset_fill_value_char
END INTERFACE
-
+
INTERFACE h5pget_fill_value_f
MODULE PROCEDURE h5pget_fill_value_integer
MODULE PROCEDURE h5pget_fill_value_real
@@ -37,7 +37,7 @@
MODULE PROCEDURE h5pset_real
MODULE PROCEDURE h5pset_char
END INTERFACE
-
+
INTERFACE h5pget_f
MODULE PROCEDURE h5pget_integer
MODULE PROCEDURE h5pget_real
@@ -49,28 +49,28 @@
MODULE PROCEDURE h5pregister_real
MODULE PROCEDURE h5pregister_char
END INTERFACE
-
+
INTERFACE h5pinsert_f
MODULE PROCEDURE h5pinsert_integer
MODULE PROCEDURE h5pinsert_real
MODULE PROCEDURE h5pinsert_char
END INTERFACE
-
+
INTERFACE h5pset_fapl_multi_f
MODULE PROCEDURE h5pset_fapl_multi_l
MODULE PROCEDURE h5pset_fapl_multi_s
- END INTERFACE
+ END INTERFACE
+
-
CONTAINS
!----------------------------------------------------------------------
-! Name: h5pcreate_f
+! Name: h5pcreate_f
!
-! Purpose: Creates a new property as an instance of a property
+! Purpose: Creates a new property as an instance of a property
! list class.
!
-! Inputs:
+! Inputs:
! class - type of the property class to be created.
! Possible values are:
! H5P_FILE_CREATE_F
@@ -78,34 +78,34 @@
! H5P_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_FILE_MOUNT_F
-! Outputs:
+! Outputs:
! prp_id - property list identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pcreate_f(class, prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: class ! The type of the property list
+ INTEGER(HID_T), INTENT(IN) :: class ! The type of the property list
! to be created. Possible values
- ! are:
+ ! are:
! H5P_FILE_CREATE_F
! H5P_FILE_ACCESS_F
! H5P_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_FILE_MOUNT_F
- INTEGER(HID_T), INTENT(OUT) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(OUT) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pcreate_c
@@ -122,46 +122,46 @@
END FUNCTION h5pcreate_c
END INTERFACE
- hdferr = h5pcreate_c(class, prp_id)
+ hdferr = h5pcreate_c(class, prp_id)
END SUBROUTINE h5pcreate_f
!----------------------------------------------------------------------
-! Name: h5pset_preserve_f
+! Name: h5pset_preserve_f
!
-! Purpose: Sets the dataset transfer property list status to
+! Purpose: Sets the dataset transfer property list status to
! TRUE or FALSE for initializing compound datatype
! members during write/read operations.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
! flag - status flag
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-! Datatype of the flag parameter is changed from
-! INTEGER to LOGICAL
-! June 4, 2003
+! port). March 14, 2001
+! Datatype of the flag parameter is changed from
+! INTEGER to LOGICAL
+! June 4, 2003
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_preserve_f(prp_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
LOGICAL, INTENT(IN) :: flag ! TRUE/FALSE flag to set the dataset
! transfer property for partila writing/reading
- ! compound datatype
+ ! compound datatype
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: flag_c
@@ -180,43 +180,43 @@
END INTERFACE
flag_c = 0
if(flag) flag_c = 1
- hdferr = h5pset_preserve_c(prp_id, flag_c)
+ hdferr = h5pset_preserve_c(prp_id, flag_c)
END SUBROUTINE h5pset_preserve_f
!----------------------------------------------------------------------
-! Name: h5pget_preserve_f
+! Name: h5pget_preserve_f
!
! Purpose: Checks status of the dataset transfer property list.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
-! Outputs:
+! Outputs:
! flag - status flag
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-! Datatype of the flag parameter is changed from
-! INTEGER to LOGICAL
-! June 4, 2003
+! port). March 14, 2001
+! Datatype of the flag parameter is changed from
+! INTEGER to LOGICAL
+! June 4, 2003
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_preserve_f(prp_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
LOGICAL, INTENT(OUT) :: flag ! TRUE/FALSE flag. Shows status of the dataset's
! transfer property for partial writing/reading
- ! compound datatype
+ ! compound datatype
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: flag_c
@@ -234,19 +234,19 @@
END FUNCTION h5pget_preserve_c
END INTERFACE
- hdferr = h5pget_preserve_c(prp_id, flag_c)
+ hdferr = h5pget_preserve_c(prp_id, flag_c)
flag = .FALSE.
if(flag_c .eq. 1) flag = .TRUE.
END SUBROUTINE h5pget_preserve_f
!----------------------------------------------------------------------
-! Name: h5pget_class_f
+! Name: h5pget_class_f
!
! Purpose: Returns the property list class for a property list.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
-! Outputs:
+! Outputs:
! classtype - property list class
! Possible values are:
! H5P_ROOT_F
@@ -255,32 +255,32 @@
! H5PE_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_FILE_MOUNT_F
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_class_f(prp_id, classtype, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER, INTENT(OUT) :: classtype ! The type of the property list
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER, INTENT(OUT) :: classtype ! The type of the property list
! to be created. Possible values
- ! are:
+ ! are:
! H5P_ROOT_F
! H5P_FILE_CREATE_F
! H5P_FILE_ACCESS_F
- ! H5PE_DATASET_CREATE_F
+ ! H5PE_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_FILE_MOUNT_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -295,46 +295,46 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_CLASS_C'::h5pget_class_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(OUT) :: classtype
+ INTEGER, INTENT(OUT) :: classtype
END FUNCTION h5pget_class_c
END INTERFACE
- hdferr = h5pget_class_c(prp_id, classtype)
+ hdferr = h5pget_class_c(prp_id, classtype)
END SUBROUTINE h5pget_class_f
!----------------------------------------------------------------------
-! Name: h5pcopy_f
+! Name: h5pcopy_f
!
-! Purpose: Copies an existing property list to create a new
+! Purpose: Copies an existing property list to create a new
! property list
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
-! Outputs:
+! Outputs:
! new_prp_id - new property list identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pcopy_f(prp_id, new_prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(OUT) :: new_prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(OUT) :: new_prp_id
! Identifier of property list
- ! copy
+ ! copy
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pcopy_c
@@ -355,34 +355,34 @@
END SUBROUTINE h5pcopy_f
!----------------------------------------------------------------------
-! Name: h5pclose_f
+! Name: h5pclose_f
!
-! Purpose: Terminates access to a property list.
+! Purpose: Terminates access to a property list.
!
-! Inputs:
-! prp_id - identifier of the property list to
-! terminate access to.
-! Outputs:
-! hdferr: - error code
+! Inputs:
+! prp_id - identifier of the property list to
+! terminate access to.
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pclose_f(prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pclose_c
@@ -394,7 +394,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PCLOSE_C'::h5pclose_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
END FUNCTION h5pclose_c
END INTERFACE
@@ -402,38 +402,38 @@
END SUBROUTINE h5pclose_f
!----------------------------------------------------------------------
-! Name: h5pset_chunk_f
+! Name: h5pset_chunk_f
!
-! Purpose: Sets the size of the chunks used to store
-! a chunked layout dataset.
+! Purpose: Sets the size of the chunks used to store
+! a chunked layout dataset.
!
-! Inputs:
+! Inputs:
! prp_id - datatset creation property list identifier
! ndims - number of dimensions for each chunk
! dims - array with dimension sizes for each chunk
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_chunk_f(prp_id, ndims, dims, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions
- INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(IN) :: dims
+ INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(IN) :: dims
! Array containing sizes of
! chunk dimensions
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -457,39 +457,39 @@
END SUBROUTINE h5pset_chunk_f
!----------------------------------------------------------------------
-! Name: h5pget_chunk_f
+! Name: h5pget_chunk_f
!
-! Purpose: Retrieves the size of chunks for the raw data of a
+! Purpose: Retrieves the size of chunks for the raw data of a
! chunked layout dataset
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
! ndims - size of dims array
-! Outputs:
+! Outputs:
! dims - array with dimension sizes for each chunk
-! hdferr: - error code
+! hdferr: - error code
! Success: number of chunk dimensions
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_chunk_f(prp_id, ndims, dims, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions to
! to return
- INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(OUT) :: dims
+ INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(OUT) :: dims
! Array containing sizes of
! chunk dimensions
INTEGER, INTENT(OUT) :: hdferr ! Error code; number of
@@ -515,35 +515,35 @@
END SUBROUTINE h5pget_chunk_f
!----------------------------------------------------------------------
-! Name: h5pset_deflate_f
+! Name: h5pset_deflate_f
!
-! Purpose: Sets compression method and compression level.
+! Purpose: Sets compression method and compression level.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier
! level - compression level
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_deflate_f(prp_id, level, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER, INTENT(IN) :: level ! Compression level
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER, INTENT(IN) :: level ! Compression level
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_deflate_c
@@ -564,41 +564,41 @@
END SUBROUTINE h5pset_deflate_f
!----------------------------------------------------------------------
-! Name: h5pset(get)fill_value_f
+! Name: h5pset(get)fill_value_f
!
! Purpose: Sets(gets) fill value for a dataset creation property list
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
! type_id - datatype identifier for fill value
! fillvalue - fill value
-! Outputs:
+! Outputs:
! ( type_id - datatype identifier for fill value )
! ( fillvalue - fill value )
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
! Comment: h5pset(get)fill_value_f function is overloaded to support
-! INTEGER, REAL, DOUBLE PRECISION and CHARACTER dtatypes.
+! INTEGER, REAL, DOUBLE PRECISION and CHARACTER dtatypes.
!----------------------------------------------------------------------
SUBROUTINE h5pset_fill_value_integer(prp_id, type_id, fillvalue, &
hdferr)
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
+ 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) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -625,10 +625,10 @@
SUBROUTINE h5pget_fill_value_integer(prp_id, type_id, fillvalue, &
hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
+ 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)
+ ! (in memory)
INTEGER, INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -654,9 +654,9 @@
SUBROUTINE h5pset_fill_value_real(prp_id, type_id, fillvalue, &
hdferr)
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
+ 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)
REAL, INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -683,10 +683,10 @@
SUBROUTINE h5pget_fill_value_real(prp_id, type_id, fillvalue, &
hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
+ 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)
+ ! (in memory)
REAL, INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -713,9 +713,9 @@
SUBROUTINE h5pset_fill_value_char(prp_id, type_id, fillvalue, &
hdferr)
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
+ 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)
CHARACTER, INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -729,7 +729,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FILL_VALUEC_C'::h5pset_fill_valuec_c
!DEC$ENDIF
- !DEC$ATTRIBUTES reference :: fillvalue
+ !DEC$ATTRIBUTES reference :: fillvalue
INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER(HID_T), INTENT(IN) :: type_id
CHARACTER, INTENT(IN) :: fillvalue
@@ -742,10 +742,10 @@
SUBROUTINE h5pget_fill_value_char(prp_id, type_id, fillvalue, &
hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
+ 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)
+ ! (in memory)
CHARACTER, INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -758,7 +758,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_FILL_VALUEC_C'::h5pget_fill_valuec_c
!DEC$ENDIF
- !DEC$ATTRIBUTES reference :: fillvalue
+ !DEC$ATTRIBUTES reference :: fillvalue
INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER(HID_T), INTENT(IN) :: type_id
CHARACTER :: fillvalue
@@ -769,43 +769,43 @@
END SUBROUTINE h5pget_fill_value_char
!----------------------------------------------------------------------
-! Name: h5pget_version_f
+! Name: h5pget_version_f
!
-! Purpose: Retrieves the version information of various objects
+! Purpose: Retrieves the version information of various objects
! for a file creation property list
!
-! Inputs:
+! Inputs:
! prp_id - file createion property list identifier
-! Outputs:
+! Outputs:
! boot - super block version number
! freelist - global freelist version number
! stab - symbol table version number
! shhdr - shared object header version number
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_version_f(prp_id, boot, freelist, &
stab, shhdr, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, DIMENSION(:), INTENT(OUT) :: boot !array to put boot
!block version number
INTEGER, DIMENSION(:), INTENT(OUT) :: freelist !array to put global
!freelist version number
-
+
INTEGER, DIMENSION(:), INTENT(OUT) :: stab !array to put symbol
!table version number
INTEGER, DIMENSION(:), INTENT(OUT) :: shhdr !array to put shared
@@ -822,8 +822,8 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_VERSION_C'::h5pget_version_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, DIMENSION(:), INTENT(OUT) :: boot
- INTEGER, DIMENSION(:), INTENT(OUT) :: freelist
+ INTEGER, DIMENSION(:), INTENT(OUT) :: boot
+ INTEGER, DIMENSION(:), INTENT(OUT) :: freelist
INTEGER, DIMENSION(:), INTENT(OUT) :: stab
INTEGER, DIMENSION(:), INTENT(OUT) :: shhdr
END FUNCTION h5pget_version_c
@@ -833,34 +833,34 @@
END SUBROUTINE h5pget_version_f
!----------------------------------------------------------------------
-! Name: h5pset_userblock_f
+! Name: h5pset_userblock_f
!
! Purpose: Sets user block size
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list to modify
! size - size of the user-block in bytes
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
-
+
SUBROUTINE h5pset_userblock_f (prp_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HSIZE_T), INTENT(IN) :: size !Size of the user-block in bytes
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HSIZE_T), INTENT(IN) :: size !Size of the user-block in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_userblock_c
@@ -881,36 +881,36 @@
END SUBROUTINE h5pset_userblock_f
!----------------------------------------------------------------------
-! Name: h5pget_userblock_f
+! Name: h5pget_userblock_f
!
! Purpose: Gets user block size.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! Outputs:
+! Outputs:
! block_size - size of the user block in bytes
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_userblock_f(prp_id, block_size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HSIZE_T), INTENT(OUT) :: block_size !Size of the
- !user-block in bytes
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HSIZE_T), INTENT(OUT) :: block_size !Size of the
+ !user-block in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pget_userblock_c
@@ -930,39 +930,39 @@
END SUBROUTINE h5pget_userblock_f
!----------------------------------------------------------------------
-! Name: h5pset_sizes_f
+! Name: h5pset_sizes_f
!
-! Purpose: Sets the byte size of the offsets and lengths used
+! Purpose: Sets the byte size of the offsets and lengths used
! to address objects in an HDF5 file.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! sizeof_addr - size of an object offset in bytes
+! sizeof_addr - size of an object offset in bytes
! sizeof_size - size of an object length in bytes
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_sizes_f (prp_id, sizeof_addr, sizeof_size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr !Size of an object
- !offset in bytes
- INTEGER(SIZE_T), INTENT(IN) :: sizeof_size !Size of an object
- !length in bytes
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr !Size of an object
+ !offset in bytes
+ INTEGER(SIZE_T), INTENT(IN) :: sizeof_size !Size of an object
+ !length in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_sizes_c
@@ -974,7 +974,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_SIZES_C'::h5pset_sizes_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr
INTEGER(SIZE_T), INTENT(IN) :: sizeof_size
END FUNCTION h5pset_sizes_c
@@ -984,41 +984,41 @@
END SUBROUTINE h5pset_sizes_f
!----------------------------------------------------------------------
-! Name: h5pget_sizes_f
+! Name: h5pget_sizes_f
!
-! Purpose: Retrieves the size of the offsets and lengths used
+! Purpose: Retrieves the size of the offsets and lengths used
! in an HDF5 file
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! Outputs:
-! sizeof_addr - size of an object offset in bytes
+! Outputs:
+! sizeof_addr - size of an object offset in bytes
! sizeof_size - size of an object length in bytes
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_sizes_f(prp_id, sizeof_addr, sizeof_size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: sizeof_addr !Size of an object
- !offset in bytes
+ !offset in bytes
INTEGER(SIZE_T), INTENT(OUT) :: sizeof_size !Size of an object
- !length in bytes
-
+ !length in bytes
+
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pget_sizes_c
@@ -1030,7 +1030,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_SIZES_C'::h5pget_sizes_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER(SIZE_T), INTENT(OUT) :: sizeof_addr
INTEGER(SIZE_T), INTENT(OUT) :: sizeof_size
END FUNCTION h5pget_sizes_c
@@ -1040,38 +1040,38 @@
END SUBROUTINE h5pget_sizes_f
!----------------------------------------------------------------------
-! Name: h5pset_sym_k_f
+! Name: h5pset_sym_k_f
!
-! Purpose: Sets the size of parameters used to control the
+! Purpose: Sets the size of parameters used to control the
! symbol table nodes
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
! ik - symbol table tree rank
! lk - symbol table node size
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_sym_k_f (prp_id, ik, lk, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER, INTENT(IN) :: ik ! Symbol table tree rank
- INTEGER, INTENT(IN) :: lk ! Symbol table node size
-
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER, INTENT(IN) :: ik ! Symbol table tree rank
+ INTEGER, INTENT(IN) :: lk ! Symbol table node size
+
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_sym_k_c
@@ -1083,7 +1083,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_SYM_K_C'::h5pset_sym_k_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER, INTENT(IN) :: ik
INTEGER, INTENT(IN) :: lk
END FUNCTION h5pset_sym_k_c
@@ -1093,36 +1093,36 @@
END SUBROUTINE h5pset_sym_k_f
!----------------------------------------------------------------------
-! Name: h5pget_sym_k_f
+! Name: h5pget_sym_k_f
!
! Purpose: Retrieves the size of the symbol table B-tree 1/2 rank
-! and the symbol table leaf node 1/2 size.
+! and the symbol table leaf node 1/2 size.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! Outputs:
+! Outputs:
! ik - symbol table tree 1/2 rank
! lk - symbol table node 1/2 size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_sym_k_f(prp_id, ik, lk, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik !Symbol table tree rank
INTEGER, INTENT(OUT) :: lk !Symbol table node size
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1136,7 +1136,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_SYM_K_C'::h5pget_sym_k_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER, INTENT(OUT) :: ik
INTEGER, INTENT(OUT) :: lk
END FUNCTION h5pget_sym_k_c
@@ -1146,36 +1146,36 @@
END SUBROUTINE h5pget_sym_k_f
!----------------------------------------------------------------------
-! Name: h5pset_istore_k_f
+! Name: h5pset_istore_k_f
!
-! Purpose: Sets the size of the parameter used to control the
+! Purpose: Sets the size of the parameter used to control the
! B-trees for indexing chunked datasets
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
! ik - 1/2 rank of chunked storage B-tree
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_istore_k_f (prp_id, ik, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ik ! 1/2 rank of chunked storage B-tree
-
+
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_istore_k_c
@@ -1196,34 +1196,34 @@
END SUBROUTINE h5pset_istore_k_f
!----------------------------------------------------------------------
-! Name: h5pget_istore_k_f
+! Name: h5pget_istore_k_f
!
-! Purpose: Queries the 1/2 rank of an indexed storage B-tree.
+! Purpose: Queries the 1/2 rank of an indexed storage B-tree.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! Outputs:
+! Outputs:
! ik - 1/2 rank of chunked storage B-tree
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_istore_k_f(prp_id, ik, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik !1/2 rank of chunked storage B-tree
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1245,34 +1245,34 @@
END SUBROUTINE h5pget_istore_k_f
!----------------------------------------------------------------------
-! Name: h5pget_driver_f
+! Name: h5pget_driver_f
!
-! Purpose: Returns low-lever driver identifier.
+! Purpose: Returns low-lever driver identifier.
!
-! Inputs:
-! prp_id - file access or data transfer property
-! list identifier.
-! Outputs:
+! Inputs:
+! prp_id - file access or data transfer property
+! list identifier.
+! Outputs:
! driver - low-level driver identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_driver_f(prp_id, driver, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: driver !low-level file driver identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1294,32 +1294,32 @@
END SUBROUTINE h5pget_driver_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_stdio_f
+! Name: h5pset_fapl_stdio_f
!
-! Purpose: Sets the standard I/O driver.
+! Purpose: Sets the standard I/O driver.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_stdio_f (prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_fapl_stdio_c
@@ -1339,34 +1339,34 @@
END SUBROUTINE h5pset_fapl_stdio_f
!----------------------------------------------------------------------
-! Name: h5pget_stdio_f
+! Name: h5pget_stdio_f
!
! Purpose: NOT AVAILABLE
!
-! Inputs:
-! Outputs:
-! hdferr: - error code
+! Inputs:
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
! SUBROUTINE h5pget_stdio_f (prp_id, io, hdferr)
!
! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
-! INTEGER, INTENT(OUT) :: io ! value indicates that the file
- !access property list is set to
+! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+! INTEGER, INTENT(OUT) :: io ! value indicates that the file
+ !access property list is set to
!the stdio driver
! INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pget_stdio_c
@@ -1374,32 +1374,32 @@
! END SUBROUTINE h5pget_stdio_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_sec2_f
+! Name: h5pset_fapl_sec2_f
!
-! Purpose: Sets the sec2 driver.
+! Purpose: Sets the sec2 driver.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_sec2_f (prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_fapl_sec2_c
@@ -1411,7 +1411,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_SEC2_C'::h5pset_fapl_sec2_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
END FUNCTION h5pset_fapl_sec2_c
END INTERFACE
@@ -1419,32 +1419,32 @@
END SUBROUTINE h5pset_fapl_sec2_f
!----------------------------------------------------------------------
-! Name: h5pget_sec2_f
+! Name: h5pget_sec2_f
!
! Purpose: NOT AVAILABLE
!
-! Inputs:
-! Outputs:
-! hdferr: - error code
+! Inputs:
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
-! SUBROUTINE h5pget_sec2_f (prp_id, sec2, hdferr)
+! SUBROUTINE h5pget_sec2_f (prp_id, sec2, hdferr)
! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
-! INTEGER, INTENT(OUT) :: sec2 ! value indicates whether the file
+! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+! INTEGER, INTENT(OUT) :: sec2 ! value indicates whether the file
!driver uses the functions declared
!in the unistd.h file
! INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1453,34 +1453,34 @@
! END SUBROUTINE h5pget_sec2_f
!----------------------------------------------------------------------
-! Name: h5pset_alignment_f
+! Name: h5pset_alignment_f
!
-! Purpose: Sets alignment properties of a file access property list.
+! Purpose: Sets alignment properties of a file access property list.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! threshold - threshold value
+! threshold - threshold value
! alignment - alignment value
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_alignment_f(prp_id, threshold, alignment, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: threshold ! Threshold value
INTEGER(HSIZE_T), INTENT(IN) :: alignment ! alignment value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1504,35 +1504,35 @@
END SUBROUTINE h5pset_alignment_f
!----------------------------------------------------------------------
-! Name: h5pget_alignment_f
+! Name: h5pget_alignment_f
!
-! Purpose: Retrieves the current settings for alignment
-! properties from a file access property list.
+! Purpose: Retrieves the current settings for alignment
+! properties from a file access property list.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! threshold - threshold value
+! Outputs:
+! threshold - threshold value
! alignment - alignment value
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_alignment_f(prp_id, threshold, alignment, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: threshold ! Threshold value
INTEGER(HSIZE_T), INTENT(OUT) :: alignment ! alignment value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1556,41 +1556,41 @@
END SUBROUTINE h5pget_alignment_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_core_f
+! Name: h5pset_fapl_core_f
!
-! Purpose: Modifies the file access property list to use the
-! H5FD_CORE driver.
+! Purpose: Modifies the file access property list to use the
+! H5FD_CORE driver.
!
! Inputs: prp_id - file access property list identifier
-! increment - size, in bytes, of memory increments
-! backing_store - boolean flag indicating whether to write
-! the file contents to disk when the file is closed.
-! Outputs:
-! hdferr: - error code
+! increment - size, in bytes, of memory increments
+! backing_store - boolean flag indicating whether to write
+! the file contents to disk when the file is closed.
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_core_f(prp_id, increment, backing_store, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(IN) :: increment ! File block size in bytes.
LOGICAL, INTENT(IN) :: backing_store ! flag to indicate that
- ! entire file contents are flushed to a file
+ ! entire file contents are flushed to a file
! with the same name as this core file.
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER :: backing_store_flag
+ INTEGER :: backing_store_flag
! INTEGER, EXTERNAL :: h5pset_fapl_core_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1601,9 +1601,9 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_CORE_C'::h5pset_fapl_core_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER(SIZE_T), INTENT(IN) :: increment
- INTEGER :: backing_store_flag
+ INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(SIZE_T), INTENT(IN) :: increment
+ INTEGER :: backing_store_flag
END FUNCTION h5pset_fapl_core_c
END INTERFACE
backing_store_flag = 0
@@ -1612,41 +1612,41 @@
END SUBROUTINE h5pset_fapl_core_f
!----------------------------------------------------------------------
-! Name: h5pget_fapl_core_f
+! Name: h5pget_fapl_core_f
!
-! Purpose: Queries core file driver properties.
+! Purpose: Queries core file driver properties.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! increment - size, in bytes, of memory increments
-! backing_store - boolean flag indicating whether to write
-! the file contents to disk when the file is closed.
-! hdferr: - error code
+! Outputs:
+! increment - size, in bytes, of memory increments
+! backing_store - boolean flag indicating whether to write
+! the file contents to disk when the file is closed.
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fapl_core_f(prp_id, increment, backing_store, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: increment ! File block size in bytes.
LOGICAL, INTENT(OUT) :: backing_store ! flag to indicate that
- ! entire file contents are flushed to a file
+ ! entire file contents are flushed to a file
! with the same name as this core file.
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER :: backing_store_flag
+ INTEGER :: backing_store_flag
! INTEGER, EXTERNAL :: h5pget_fapl_core_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1657,9 +1657,9 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_FAPL_CORE_C'::h5pget_fapl_core_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER(SIZE_T), INTENT(OUT) :: increment
- INTEGER :: backing_store_flag
+ INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(SIZE_T), INTENT(OUT) :: increment
+ INTEGER :: backing_store_flag
END FUNCTION h5pget_fapl_core_c
END INTERFACE
@@ -1669,39 +1669,39 @@
END SUBROUTINE h5pget_fapl_core_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_family_f
+! Name: h5pset_fapl_family_f
!
-! Purpose: Sets the file access property list to use the family driver.
+! Purpose: Sets the file access property list to use the family driver.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! memb_size - size in bytes of each file member
-! memb_plist - identifier of the file access property
+! memb_size - size in bytes of each file member
+! memb_plist - identifier of the file access property
! list to be used for each family member
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_family_f(prp_id, memb_size, memb_plist , hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: memb_size ! Logical size, in bytes,
!of each family member
- INTEGER(HID_T), INTENT(IN) :: memb_plist !Identifier of the file
- !access property list for
+ INTEGER(HID_T), INTENT(IN) :: memb_plist !Identifier of the file
+ !access property list for
!each member of the family
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1724,40 +1724,40 @@
END SUBROUTINE h5pset_fapl_family_f
!----------------------------------------------------------------------
-! Name: h5pget_fapl_family_f
+! Name: h5pget_fapl_family_f
!
-! Purpose: Returns file access property list information.
+! Purpose: Returns file access property list information.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! memb_size - size in bytes of each file member
-! memb_plist - identifier of the file access property
+! Outputs:
+! memb_size - size in bytes of each file member
+! memb_plist - identifier of the file access property
! list to be used for each family member
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fapl_family_f(prp_id, memb_size, memb_plist , hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: memb_size ! Logical size, in bytes,
!of each family member
- INTEGER(HID_T), INTENT(OUT) :: memb_plist !Identifier of the file
- !access property list for
+ INTEGER(HID_T), INTENT(OUT) :: memb_plist !Identifier of the file
+ !access property list for
!each member of the family
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1780,45 +1780,45 @@
END SUBROUTINE h5pget_fapl_family_f
!----------------------------------------------------------------------
-! Name: h5pset_cache_f
+! Name: h5pset_cache_f
!
-! Purpose: Sets the meta data cache and raw data chunk
+! Purpose: Sets the meta data cache and raw data chunk
! cache parameters
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! mdc_nelmts - number of elements (objects) in the meta
-! data cache
-! rdcc_nelmts - number of elements (objects) in the raw
-! data chunk cache
-! rdcc_nbytes - total size of the raw data chunk cache, in bytes
+! mdc_nelmts - number of elements (objects) in the meta
+! data cache
+! rdcc_nelmts - number of elements (objects) in the raw
+! data chunk cache
+! rdcc_nbytes - total size of the raw data chunk cache, in bytes
! rdcc_w0 - preemption policy (0 or 1)
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_cache_f(prp_id, mdc_nelmts,rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: mdc_nelmts !Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(IN) :: rdcc_nelmts !Number of elements (objects)
! in the meta data cache
- INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes !Total size of the raw data
- !chunk cache, in bytes
+ INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes !Total size of the raw data
+ !chunk cache, in bytes
REAL, INTENT(IN) :: rdcc_w0 !Preemption policy
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1832,8 +1832,8 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_CACHE_C'::h5pset_cache_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: mdc_nelmts
- INTEGER(SIZE_T), INTENT(IN) :: rdcc_nelmts
+ INTEGER, INTENT(IN) :: mdc_nelmts
+ INTEGER(SIZE_T), INTENT(IN) :: rdcc_nelmts
INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes
REAL, INTENT(IN) :: rdcc_w0
END FUNCTION h5pset_cache_c
@@ -1843,48 +1843,48 @@
END SUBROUTINE h5pset_cache_f
!----------------------------------------------------------------------
-! Name: h5pget_cache_f
+! Name: h5pget_cache_f
!
-! Purpose: Queries the meta data cache and raw data chunk cache
-! parameters.
+! Purpose: Queries the meta data cache and raw data chunk cache
+! parameters.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! mdc_nelmts - number of elements (objects) in the meta
-! data cache
-! rdcc_nelmts - number of elements (objects) in the raw
-! data chunk cache
-! rdcc_nbytes - total size of the raw data chunk cache, in bytes
+! Outputs:
+! mdc_nelmts - number of elements (objects) in the meta
+! data cache
+! rdcc_nelmts - number of elements (objects) in the raw
+! data chunk cache
+! rdcc_nbytes - total size of the raw data chunk cache, in bytes
! rdcc_w0 - preemption policy (0 or 1)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
! Bug fix: type of the rdcc_nelmts parameter should be INTEGER
-! instead of INTEGER(SIZE_T) October 10, 2003
+! instead of INTEGER(SIZE_T) October 10, 2003
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_cache_f(prp_id, mdc_nelmts, rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: mdc_nelmts !Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nelmts !Number of elements (objects)
! in the meta data cache
- INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes !Total size of the raw data
- !chunk cache, in bytes
+ INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes !Total size of the raw data
+ !chunk cache, in bytes
REAL, INTENT(OUT) :: rdcc_w0 !Preemption policy
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1899,8 +1899,8 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_CACHE_C'::h5pget_cache_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(OUT) :: mdc_nelmts
- INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nelmts
+ INTEGER, INTENT(OUT) :: mdc_nelmts
+ INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nelmts
INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes
REAL, INTENT(OUT) :: rdcc_w0
END FUNCTION h5pget_cache_c
@@ -1910,44 +1910,44 @@
END SUBROUTINE h5pget_cache_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_split_f
+! Name: h5pset_fapl_split_f
!
-! Purpose: Emulates the old split file driver.
+! Purpose: Emulates the old split file driver.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! meta_ext - name of the extension for the metafile
+! meta_ext - name of the extension for the metafile
! filename
-! meta_plist - identifier of the meta file access property
+! meta_plist - identifier of the meta file access property
! list
! raw_ext - name extension for the raw file filename
! raw_plist - identifier of the raw file access property list
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_split_f(prp_id, meta_ext, meta_plist, raw_ext, raw_plist, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: meta_ext !Name of the extension for
!the metafile filename
INTEGER(HID_T), INTENT(IN) :: meta_plist ! Identifier of the meta file
! access property list
CHARACTER(LEN=*), INTENT(IN) :: raw_ext !Name extension for the raw file filename
- INTEGER(HID_T), INTENT(IN) :: raw_plist !Identifier of the raw file
+ INTEGER(HID_T), INTENT(IN) :: raw_plist !Identifier of the raw file
!access property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: meta_len, raw_len
@@ -1964,10 +1964,10 @@
!DEC$ATTRIBUTES reference :: meta_ext
!DEC$ATTRIBUTES reference :: raw_ext
INTEGER(HID_T), INTENT(IN) :: prp_id
- CHARACTER(LEN=*), INTENT(IN) :: meta_ext
+ CHARACTER(LEN=*), INTENT(IN) :: meta_ext
INTEGER(HID_T), INTENT(IN) :: meta_plist
CHARACTER(LEN=*), INTENT(IN) :: raw_ext
- INTEGER(HID_T), INTENT(IN) :: raw_plist
+ INTEGER(HID_T), INTENT(IN) :: raw_plist
INTEGER :: meta_len, raw_len
END FUNCTION h5pset_fapl_split_c
END INTERFACE
@@ -1978,36 +1978,36 @@
END SUBROUTINE h5pset_fapl_split_f
!----------------------------------------------------------------------
-! Name: h5pget_split_f
+! Name: h5pget_split_f
!
! Purpose: NOT AVAILABLE
!
-! Inputs:
-! Outputs:
-! hdferr: - error code
+! Inputs:
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
! SUBROUTINE h5pget_split_f(prp_id, meta_ext_size, meta_ext, meta_plist,raw_ext_size,&
-! raw_ext, raw_plist, hdferr)
+! raw_ext, raw_plist, hdferr)
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
! INTEGER(SIZE_T), INTENT(IN) :: meta_ext_size ! Number of characters of the meta
! file extension to be copied to the
! meta_ext buffer
-
+
! CHARACTER(LEN=*), INTENT(OUT) :: meta_ext !Name of the extension for
!the metafile filename
! INTEGER(HID_T), INTENT(OUT) :: meta_plist ! Identifier of the meta file
@@ -2016,7 +2016,7 @@
! file extension to be copied to the
! raw_ext buffer
! CHARACTER(LEN=*), INTENT(OUT) :: raw_ext !Name extension for the raw file filename
-! INTEGER(HID_T), INTENT(OUT) :: raw_plist !Identifier of the raw file
+! INTEGER(HID_T), INTENT(OUT) :: raw_plist !Identifier of the raw file
!access property list
! INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2026,35 +2026,35 @@
! END SUBROUTINE h5pget_split_f
!----------------------------------------------------------------------
-! Name: h5pset_gc_references_f
+! Name: h5pset_gc_references_f
!
-! Purpose: Sets garbage collecting references flag.
+! Purpose: Sets garbage collecting references flag.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! gc_reference - flag for stting garbage collection on
+! gc_reference - flag for stting garbage collection on
! and off (1 or 0)
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
-
+
SUBROUTINE h5pset_gc_references_f (prp_id, gc_reference, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: gc_reference !the flag for garbage collecting
! references for the file
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2077,34 +2077,34 @@
END SUBROUTINE h5pset_gc_references_f
!----------------------------------------------------------------------
-! Name: h5pget_gc_references_f
+! Name: h5pget_gc_references_f
!
-! Purpose: Returns garbage collecting references setting.
+! Purpose: Returns garbage collecting references setting.
!
-! Inputs:
+! Inputs:
! prp_id - file access property list identifier
-! Outputs:
-! gc_reference - flag for stting garbage collection on
+! Outputs:
+! gc_reference - flag for stting garbage collection on
! and off (1 or 0)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_gc_references_f (prp_id, gc_reference, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: gc_reference !the flag for garbage collecting
! references for the file
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2127,38 +2127,38 @@
END SUBROUTINE h5pget_gc_references_f
!----------------------------------------------------------------------
-! Name: h5pset_layout_f
+! Name: h5pset_layout_f
!
-! Purpose: Sets the type of storage used store the raw data
-! for a dataset.
+! Purpose: Sets the type of storage used store the raw data
+! for a dataset.
!
-! Inputs:
+! Inputs:
! prp_id - data creation property list identifier
! layout - type of storage layout for raw data
! possible values are:
! H5D_COMPACT_F
! H5D_CONTIGUOUS_F
! H5D_CHUNKED_F
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_layout_f (prp_id, layout, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: layout !Type of storage layout for raw data
!possible values are:
!H5D_COMPACT_F
@@ -2184,37 +2184,37 @@
END SUBROUTINE h5pset_layout_f
!----------------------------------------------------------------------
-! Name: h5pget_layout_f
+! Name: h5pget_layout_f
!
-! Purpose: Returns the layout of the raw data for a dataset.
+! Purpose: Returns the layout of the raw data for a dataset.
!
-! Inputs:
+! Inputs:
! prp_id - data creation property list identifier
-! Outputs:
+! Outputs:
! layout - type of storage layout for raw data
! possible values are:
! H5D_COMPACT_F
! H5D_CONTIGUOUS_F
! H5D_CHUNKED_F
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_layout_f (prp_id, layout, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: layout !Type of storage layout for raw data
!possible values are:
!H5D_COMPACT_F(0)
@@ -2240,36 +2240,36 @@
END SUBROUTINE h5pget_layout_f
!----------------------------------------------------------------------
-! Name: h5pset_filter_f
+! Name: h5pset_filter_f
!
-! Purpose: Adds a filter to the filter pipeline.
+! Purpose: Adds a filter to the filter pipeline.
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
-! filter - filter to be added to the pipeline
+! filter - filter to be added to the pipeline
! flags - bit vector specifying certain general
! properties of the filter
! cd_nelmts - number of elements in cd_values
! cd_values - auxiliary data for the filter
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! February, 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter !Filter to be added to the pipeline.
INTEGER, INTENT(IN) :: flags !Bit vector specifying certain general
!properties of the filter.
@@ -2287,11 +2287,11 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FILTER_C'::h5pset_filter_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: filter
- INTEGER, INTENT(IN) :: flags
- INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts
- INTEGER, DIMENSION(*), INTENT(IN) :: cd_values
+ INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER, INTENT(IN) :: filter
+ INTEGER, INTENT(IN) :: flags
+ INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts
+ INTEGER, DIMENSION(*), INTENT(IN) :: cd_values
END FUNCTION h5pset_filter_c
END INTERFACE
@@ -2299,34 +2299,34 @@
END SUBROUTINE h5pset_filter_f
!----------------------------------------------------------------------
-! Name: h5pget_nfilters_f
+! Name: h5pget_nfilters_f
!
-! Purpose: Returns the number of filters in the pipeline.
+! Purpose: Returns the number of filters in the pipeline.
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
-! Outputs:
+! Outputs:
! nfilters - number of filters in the pipeline
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_nfilters_f (prp_id, nfilters, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: nfilters !the number of filters in the pipeline
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2348,43 +2348,43 @@
END SUBROUTINE h5pget_nfilters_f
!----------------------------------------------------------------------
-! Name: h5pget_filter_f
+! Name: h5pget_filter_f
!
! Purpose: Returns information about a filter in a pipeline
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
-! Outputs:
+! Outputs:
! identifier
-! filter - filter to be added to the pipeline
+! filter - filter to be added to the pipeline
! flags - bit vector specifying certain general
! properties of the filter
! cd_nelmts - number of elements in cd_values
! cd_values - auxiliary data for the filter
! namelen - number of characters in the name buffer
! name - buffer to retrieve filter name
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_filter_f(prp_id, filter_number, flags, cd_nelmts, cd_values, namelen, name, filter_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter_number !Sequence number within the filter
- !pipeline of the filter for which
+ !pipeline of the filter for which
!information is sought
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values !Auxiliary data for the filter.
INTEGER, INTENT(OUT) :: flags !Bit vector specifying certain general
@@ -2392,7 +2392,7 @@
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts !Number of elements in cd_values.
INTEGER(SIZE_T), INTENT(IN) :: namelen !Anticipated number of characters in name.
CHARACTER(LEN=*), INTENT(OUT) :: name !Name of the filter
- INTEGER, INTENT(OUT) :: filter_id ! filter identification number
+ INTEGER, INTENT(OUT) :: filter_id ! filter identification number
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2409,9 +2409,9 @@
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: name
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: filter_number
+ INTEGER, INTENT(IN) :: filter_number
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values
- INTEGER, INTENT(OUT) :: flags
+ INTEGER, INTENT(OUT) :: flags
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts
INTEGER(SIZE_T), INTENT(IN) :: namelen
CHARACTER(LEN=*), INTENT(OUT) :: name
@@ -2419,47 +2419,47 @@
END FUNCTION h5pget_filter_c
END INTERFACE
- hdferr = h5pget_filter_c(prp_id, filter_number, flags, cd_nelmts, &
+ hdferr = h5pget_filter_c(prp_id, filter_number, flags, cd_nelmts, &
cd_values, namelen, name, filter_id )
END SUBROUTINE h5pget_filter_f
!----------------------------------------------------------------------
-! Name: h5pset_external_f
+! Name: h5pset_external_f
!
-! Purpose: Adds an external file to the list of external files.
+! Purpose: Adds an external file to the list of external files.
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
! name - name of external file
-! offset - offset in bytes from the beginning of the
+! offset - offset in bytes from the beginning of the
! file to the location in the file
! where the data starts
-! bytes - size of the external file data.
-! Outputs:
-! hdferr: - error code
+! bytes - size of the external file data.
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_external_f(prp_id, name, offset,bytes, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name !Name of an external file
- INTEGER, INTENT(IN) :: offset !Offset, in bytes, from the beginning
- !of the file to the location in the file
+ INTEGER, INTENT(IN) :: offset !Offset, in bytes, from the beginning
+ !of the file to the location in the file
!where the data starts.
- INTEGER(HSIZE_T), INTENT(IN) :: bytes ! Number of bytes reserved in the
+ INTEGER(HSIZE_T), INTENT(IN) :: bytes ! Number of bytes reserved in the
!file for the data
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2488,35 +2488,35 @@
END SUBROUTINE h5pset_external_f
!----------------------------------------------------------------------
-! Name: h5pget_external_count_f
+! Name: h5pget_external_count_f
!
-! Purpose: Returns the number of external files for a dataset.
+! Purpose: Returns the number of external files for a dataset.
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
-! Outputs:
-! count - number of external files for the
+! Outputs:
+! count - number of external files for the
! specified dataset
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_external_count_f (prp_id, count, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER, INTENT(OUT) :: count !number of external files for the
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER, INTENT(OUT) :: count !number of external files for the
!specified dataset
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pget_external_count_c
@@ -2528,7 +2528,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_EXTERNAL_COUNT_C'::h5pget_external_count_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER, INTENT(OUT) :: count
END FUNCTION h5pget_external_count_c
END INTERFACE
@@ -2537,35 +2537,35 @@
END SUBROUTINE h5pget_external_count_f
!----------------------------------------------------------------------
-! Name: h5pget_external_f
+! Name: h5pget_external_f
!
-! Purpose: Returns information about an external file.
+! Purpose: Returns information about an external file.
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
-! Outputs:
-! idx - external file index
+! Outputs:
+! idx - external file index
! name_size - maximum size of name array
-! name - name of the external file
+! name - name of the external file
! name - name of external file
-! offset - offset in bytes from the beginning of the
+! offset - offset in bytes from the beginning of the
! file to the location in the file
! where the data starts
! bytes - size of the external file data
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
@@ -2573,12 +2573,12 @@
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: idx !External file index.
- INTEGER(SIZE_T), INTENT(IN) :: name_size !Maximum length of name array
+ INTEGER(SIZE_T), INTENT(IN) :: name_size !Maximum length of name array
CHARACTER(LEN=*), INTENT(OUT) :: name !Name of an external file
- INTEGER, INTENT(OUT) :: offset !Offset, in bytes, from the beginning
- !of the file to the location in the file
+ INTEGER, INTENT(OUT) :: offset !Offset, in bytes, from the beginning
+ !of the file to the location in the file
!where the data starts.
- INTEGER(HSIZE_T), INTENT(OUT) :: bytes ! Number of bytes reserved in the
+ INTEGER(HSIZE_T), INTENT(OUT) :: bytes ! Number of bytes reserved in the
!file for the data
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2593,7 +2593,7 @@
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: name
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: idx
+ INTEGER, INTENT(IN) :: idx
INTEGER(SIZE_T), INTENT(IN) :: name_size
CHARACTER(LEN=*), INTENT(OUT) :: name
INTEGER, INTENT(OUT) :: offset
@@ -2605,41 +2605,41 @@
END SUBROUTINE h5pget_external_f
!----------------------------------------------------------------------
-! Name: h5pset_btree_ratios_f
+! Name: h5pset_btree_ratios_f
!
-! Purpose: Sets B-tree split ratios for a dataset transfer
-! property list.
+! Purpose: Sets B-tree split ratios for a dataset transfer
+! property list.
!
-! Inputs:
-! prp_id - the dataset transfer property list
-! identifier
-! left - the B-tree split ratio for left-most nodes
+! Inputs:
+! prp_id - the dataset transfer property list
+! identifier
+! left - the B-tree split ratio for left-most nodes
! middle - the B-tree split ratio for all other nodes
! right - the B-tree split ratio for right-most nodes
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_btree_ratios_f(prp_id, left, middle, right, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(IN) :: left !The B-tree split ratio for left-most nodes.
- REAL, INTENT(IN) :: middle !The B-tree split ratio for all other nodes
- REAL, INTENT(IN) :: right !The B-tree split ratio for right-most
- !nodes and lone nodes.
+ REAL, INTENT(IN) :: middle !The B-tree split ratio for all other nodes
+ REAL, INTENT(IN) :: right !The B-tree split ratio for right-most
+ !nodes and lone nodes.
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2663,40 +2663,40 @@
END SUBROUTINE h5pset_btree_ratios_f
!----------------------------------------------------------------------
-! Name: h5pget_btree_ratios_f
+! Name: h5pget_btree_ratios_f
!
! Purpose: Gets B-tree split ratios for a dataset transfer property list
!
-! Inputs:
-! prp_id - the dataset transfer property list
-! identifier
-! Outputs:
-! left - the B-tree split ratio for left-most nodes
+! Inputs:
+! prp_id - the dataset transfer property list
+! identifier
+! Outputs:
+! left - the B-tree split ratio for left-most nodes
! middle - the B-tree split ratio for all other nodes
! right - the B-tree split ratio for right-most nodes
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_btree_ratios_f(prp_id, left, middle, right, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(OUT) :: left !The B-tree split ratio for left-most nodes.
- REAL, INTENT(OUT) :: middle !The B-tree split ratio for all other nodes
- REAL, INTENT(OUT) :: right !The B-tree split ratio for right-most
- !nodes and lone nodes.
+ REAL, INTENT(OUT) :: middle !The B-tree split ratio for all other nodes
+ REAL, INTENT(OUT) :: right !The B-tree split ratio for right-most
+ !nodes and lone nodes.
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2721,38 +2721,38 @@
END SUBROUTINE h5pget_btree_ratios_f
!----------------------------------------------------------------------
-! Name: h5pget_fclose_degree_f
+! Name: h5pget_fclose_degree_f
!
! Purpose: Returns the degree for the file close behavior.
!
-! Inputs:
+! Inputs:
! fapl_id - file access property list identifier
-! Outputs:
+! Outputs:
! degree - one of the following:
! Possible values are:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
! H5F_CLOSE_STRONG_F
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! September 26, 2002
+! September 26, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
INTEGER, INTENT(OUT) :: degree ! Possible values
- ! are:
+ ! are:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
@@ -2774,15 +2774,15 @@
END FUNCTION h5pget_fclose_degree_c
END INTERFACE
- hdferr = h5pget_fclose_degree_c(fapl_id, degree)
+ hdferr = h5pget_fclose_degree_c(fapl_id, degree)
END SUBROUTINE h5pget_fclose_degree_f
!----------------------------------------------------------------------
-! Name: h5pset_fclose_degree_f
+! Name: h5pset_fclose_degree_f
!
! Purpose: Sets the degree for the file close behavior.
!
-! Inputs:
+! Inputs:
! fapl_id - file access property list identifier
! degree - one of the following:
! Possible values are:
@@ -2790,26 +2790,26 @@
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
! H5F_CLOSE_STRONG_F
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! September 26, 2002
+! September 26, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
INTEGER, INTENT(IN) :: degree ! Possible values
- ! are:
+ ! are:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
@@ -2828,38 +2828,38 @@
END FUNCTION h5pset_fclose_degree_c
END INTERFACE
- hdferr = h5pset_fclose_degree_c(fapl_id, degree)
+ hdferr = h5pset_fclose_degree_c(fapl_id, degree)
END SUBROUTINE h5pset_fclose_degree_f
!----------------------------------------------------------------------
-! Name: h5pequal_f
+! Name: h5pequal_f
!
! Purpose: Checks if two property lists are eqaul
!
-! Inputs:
+! Inputs:
! plist1_id - property list identifier
! plist2_id - property list identifier
-! Outputs:
+! Outputs:
! flag - flag, possible values
! .TRUE. or .FALSE.
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1, flag is set to .FALSE.
+! Failure: -1, flag is set to .FALSE.
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! September 30, 2002
+! September 30, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pequal_f(plist1_id, plist2_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist1_id ! Property list identifier
- INTEGER(HID_T), INTENT(IN) :: plist2_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist1_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist2_id ! Property list identifier
LOGICAL, INTENT(OUT) :: flag ! Flag
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: c_flag
@@ -2877,38 +2877,38 @@
END INTERFACE
flag = .FALSE.
- hdferr = h5pequal_c(plist1_id, plist2_id, c_flag)
+ hdferr = h5pequal_c(plist1_id, plist2_id, c_flag)
if (c_flag .GT. 0) flag = .TRUE.
END SUBROUTINE h5pequal_f
!----------------------------------------------------------------------
-! Name: h5pset_buffer_f
+! Name: h5pset_buffer_f
!
! Purpose: Sets sixe for conversion buffer
!
-! Inputs:
+! Inputs:
! plist_id - data transfer property list identifier
-! size - buffer size
-! Outputs:
-! hdferr: - error code
+! size - buffer size
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 2, 2002
+! October 2, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_buffer_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
- INTEGER(HSIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
- ! buffer is allocated and freed by
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
+ INTEGER(HSIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
+ ! buffer is allocated and freed by
! the library.
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2923,37 +2923,37 @@
END FUNCTION h5pset_buffer_c
END INTERFACE
- hdferr = h5pset_buffer_c(plist_id, size)
+ hdferr = h5pset_buffer_c(plist_id, size)
END SUBROUTINE h5pset_buffer_f
!----------------------------------------------------------------------
-! Name: h5pget_buffer_f
+! Name: h5pget_buffer_f
!
! Purpose: Gets size for conversion buffer
!
-! Inputs:
+! Inputs:
! plist_id - data transfer property list identifier
-! Outputs:
-! size - buffer size
-! hdferr: - error code
+! Outputs:
+! size - buffer size
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 2, 2002
+! October 2, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_buffer_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
- INTEGER(HSIZE_T), INTENT(OUT) :: size ! Buffer size in bytes;
- ! buffer is allocated and freed by
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
+ INTEGER(HSIZE_T), INTENT(OUT) :: size ! Buffer size in bytes;
+ ! buffer is allocated and freed by
! the library.
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2968,7 +2968,7 @@
END FUNCTION h5pget_buffer_c
END INTERFACE
- hdferr = h5pget_buffer_c(plist_id, size)
+ hdferr = h5pget_buffer_c(plist_id, size)
END SUBROUTINE h5pget_buffer_f
!----------------------------------------------------------------------
@@ -2976,34 +2976,34 @@
!
! Purpose: Check if fill value is defined.
!
-! Inputs:
+! Inputs:
! plist_id - dataset creation property list identifier
-! Outputs:
+! Outputs:
! flag - fill value status flag
! Possible values are:
! H5D_FILL_VALUE_ERROR_F
! H5D_FILL_VALUE_UNDEFINED_F
! H5D_FILL_VALUE_DEFAULT_F
! H5D_FILL_VALUE_USER_DEFINED_F
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pfill_value_defined_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
- INTEGER, INTENT(OUT) :: hdferr
+ INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5pfill_value_defined_c(plist_id, flag)
@@ -3016,7 +3016,7 @@
END FUNCTION h5pfill_value_defined_c
END INTERFACE
- hdferr = h5pfill_value_defined_c(plist_id, flag)
+ hdferr = h5pfill_value_defined_c(plist_id, flag)
END SUBROUTINE h5pfill_value_defined_f
!----------------------------------------------------------------------
@@ -3024,7 +3024,7 @@
!
! Purpose: Set space allocation time for dataset during creation.
!
-! Inputs:
+! Inputs:
! plist_id - dataset creation property list identifier
! flag - allocation time flag
! Possible values are:
@@ -3033,26 +3033,26 @@
! H5D_ALLOC_TIME_EARLY_F
! H5D_ALLOC_TIME_LATE_F
! H5D_ALLOC_TIME_INCR_F
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_alloc_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: flag
- INTEGER, INTENT(OUT) :: hdferr
+ INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5pset_alloc_time_c(plist_id, flag)
@@ -3065,7 +3065,7 @@
END FUNCTION h5pset_alloc_time_c
END INTERFACE
- hdferr = h5pset_alloc_time_c(plist_id, flag)
+ hdferr = h5pset_alloc_time_c(plist_id, flag)
END SUBROUTINE h5pset_alloc_time_f
!----------------------------------------------------------------------
@@ -3073,9 +3073,9 @@
!
! Purpose: Get space allocation time for dataset during creation.
!
-! Inputs:
+! Inputs:
! plist_id - dataset creation property list identifier
-! Outputs:
+! Outputs:
! flag - allocation time flag
! Possible values are:
! H5D_ALLOC_TIME_ERROR_F
@@ -3083,25 +3083,25 @@
! H5D_ALLOC_TIME_EARLY_F
! H5D_ALLOC_TIME_LATE_F
! H5D_ALLOC_TIME_INCR_F
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_alloc_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
- INTEGER, INTENT(OUT) :: hdferr
+ INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5pget_alloc_time_c(plist_id, flag)
@@ -3114,7 +3114,7 @@
END FUNCTION h5pget_alloc_time_c
END INTERFACE
- hdferr = h5pget_alloc_time_c(plist_id, flag)
+ hdferr = h5pget_alloc_time_c(plist_id, flag)
END SUBROUTINE h5pget_alloc_time_f
!----------------------------------------------------------------------
@@ -3122,33 +3122,33 @@
!
! Purpose: Set fill value writing time for dataset
!
-! Inputs:
+! Inputs:
! plist_id - dataset creation property list identifier
! flag - fill time flag
! Possible values are:
! H5D_FILL_TIME_ERROR_F
! H5D_FILL_TIME_ALLOC_F
! H5D_FILL_TIME_NEVER_F
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fill_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: flag
- INTEGER, INTENT(OUT) :: hdferr
+ INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5pset_fill_time_c(plist_id, flag)
@@ -3161,7 +3161,7 @@
END FUNCTION h5pset_fill_time_c
END INTERFACE
- hdferr = h5pset_fill_time_c(plist_id, flag)
+ hdferr = h5pset_fill_time_c(plist_id, flag)
END SUBROUTINE h5pset_fill_time_f
!----------------------------------------------------------------------
@@ -3169,10 +3169,10 @@
!
! Purpose: Get fill value writing time for dataset
!
-! Inputs:
+! Inputs:
! plist_id - dataset creation property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
@@ -3184,18 +3184,18 @@
! NONE
!
! Programmer: Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fill_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
- INTEGER, INTENT(OUT) :: hdferr
+ INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5pget_fill_time_c(plist_id, flag)
@@ -3208,36 +3208,36 @@
END FUNCTION h5pget_fill_time_c
END INTERFACE
- hdferr = h5pget_fill_time_c(plist_id, flag)
+ hdferr = h5pget_fill_time_c(plist_id, flag)
END SUBROUTINE h5pget_fill_time_f
!----------------------------------------------------------------------
-! Name: h5pset_meta_block_size_f
+! Name: h5pset_meta_block_size_f
!
-! Purpose: Sets the minimum size of metadata block allocations
+! Purpose: Sets the minimum size of metadata block allocations
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
! size - metatdata block size
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_meta_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
- INTEGER(HSIZE_T), INTENT(IN) :: size ! Block size in bytes;
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(HSIZE_T), INTENT(IN) :: size ! Block size in bytes;
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -3251,36 +3251,36 @@
END FUNCTION h5pset_meta_block_size_c
END INTERFACE
- hdferr = h5pset_meta_block_size_c(plist_id, size)
+ hdferr = h5pset_meta_block_size_c(plist_id, size)
END SUBROUTINE h5pset_meta_block_size_f
!----------------------------------------------------------------------
-! Name: h5pget_meta_block_size_f
+! Name: h5pget_meta_block_size_f
!
-! Purpose: Gets the minimum size of metadata block allocations
+! Purpose: Gets the minimum size of metadata block allocations
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
-! Outputs:
+! Outputs:
! size - metatdata block size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_meta_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
- INTEGER(HSIZE_T), INTENT(OUT) :: size ! Block size in bytes;
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(HSIZE_T), INTENT(OUT) :: size ! Block size in bytes;
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -3294,36 +3294,36 @@
END FUNCTION h5pget_meta_block_size_c
END INTERFACE
- hdferr = h5pget_meta_block_size_c(plist_id, size)
+ hdferr = h5pget_meta_block_size_c(plist_id, size)
END SUBROUTINE h5pget_meta_block_size_f
!----------------------------------------------------------------------
-! Name: h5pset_sieve_buf_size_f
+! Name: h5pset_sieve_buf_size_f
!
! Purpose: Sets the maximum size of the data sieve buffer
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
! size - sieve buffer size
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_sieve_buf_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
- INTEGER(SIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(SIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -3337,36 +3337,36 @@
END FUNCTION h5pset_sieve_buf_size_c
END INTERFACE
- hdferr = h5pset_sieve_buf_size_c(plist_id, size)
+ hdferr = h5pset_sieve_buf_size_c(plist_id, size)
END SUBROUTINE h5pset_sieve_buf_size_f
!----------------------------------------------------------------------
-! Name: h5pget_sieve_buf_size_f
+! Name: h5pget_sieve_buf_size_f
!
! Purpose: Gets the maximum size of the data sieve buffer
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
-! Outputs:
+! Outputs:
! size - sieve buffer size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_sieve_buf_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
- INTEGER(SIZE_T), INTENT(OUT) :: size ! Buffer size in bytes
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(SIZE_T), INTENT(OUT) :: size ! Buffer size in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -3380,35 +3380,35 @@
END FUNCTION h5pget_sieve_buf_size_c
END INTERFACE
- hdferr = h5pget_sieve_buf_size_c(plist_id, size)
+ hdferr = h5pget_sieve_buf_size_c(plist_id, size)
END SUBROUTINE h5pget_sieve_buf_size_f
!----------------------------------------------------------------------
-! Name: h5pset_small_data_block_size_f
+! Name: h5pset_small_data_block_size_f
!
! Purpose: Sets the minimum size of "small" raw data block
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
! size - small raw data block size
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_small_data_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Small raw data block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3423,35 +3423,35 @@
END FUNCTION h5pset_small_data_block_size_c
END INTERFACE
- hdferr = h5pset_small_data_block_size_c(plist_id, size)
+ hdferr = h5pset_small_data_block_size_c(plist_id, size)
END SUBROUTINE h5pset_small_data_block_size_f
!----------------------------------------------------------------------
-! Name: h5pget_small_data_block_size_f
+! Name: h5pget_small_data_block_size_f
!
! Purpose: Gets the minimum size of "small" raw data block
!
-! Inputs:
+! Inputs:
! plist_id - file access property list identifier
-! Outputs:
+! Outputs:
! size - small raw data block size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_small_data_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Small raw data block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3466,35 +3466,35 @@
END FUNCTION h5pget_small_data_block_size_c
END INTERFACE
- hdferr = h5pget_small_data_block_size_c(plist_id, size)
+ hdferr = h5pget_small_data_block_size_c(plist_id, size)
END SUBROUTINE h5pget_small_data_block_size_f
!----------------------------------------------------------------------
-! Name: h5pset_hyper_vector_size_f
+! Name: h5pset_hyper_vector_size_f
!
! Purpose: Set the number of "I/O" vectors (vector size)
!
-! Inputs:
+! Inputs:
! plist_id - dataset transfer property list identifier
! size - vector size
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_hyper_vector_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
INTEGER(SIZE_T), INTENT(IN) :: size ! Vector size
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3509,35 +3509,35 @@
END FUNCTION h5pset_hyper_vector_size_c
END INTERFACE
- hdferr = h5pset_hyper_vector_size_c(plist_id, size)
+ hdferr = h5pset_hyper_vector_size_c(plist_id, size)
END SUBROUTINE h5pset_hyper_vector_size_f
!----------------------------------------------------------------------
-! Name: h5pget_hyper_vector_size_f
+! Name: h5pget_hyper_vector_size_f
!
! Purpose: Get the number of "I/O" vectors (vector size)
!
-! Inputs:
+! Inputs:
! plist_id - dataset transfer property list identifier
-! Outputs:
+! Outputs:
! size - vector size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_hyper_vector_size_f(plist_id, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: size ! Vector size
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3552,36 +3552,36 @@
END FUNCTION h5pget_hyper_vector_size_c
END INTERFACE
- hdferr = h5pget_hyper_vector_size_c(plist_id, size)
+ hdferr = h5pget_hyper_vector_size_c(plist_id, size)
END SUBROUTINE h5pget_hyper_vector_size_f
!----------------------------------------------------------------------
-! Name: h5pset_integer
+! Name: h5pset_integer
!
! Purpose: Sets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
! value - value to set property to
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_integer(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
INTEGER, INTENT(IN) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3610,28 +3610,28 @@
!
! Purpose: Sets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
! value - value to set property to
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_real(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
REAL, INTENT(IN) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3661,28 +3661,28 @@
!
! Purpose: Sets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
! value - value to set property to
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_char(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ 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
@@ -3711,32 +3711,32 @@
END SUBROUTINE h5pset_char
!----------------------------------------------------------------------
-! Name: h5pget_integer
+! Name: h5pget_integer
!
! Purpose: Gets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
-! Outputs:
+! Outputs:
! value - value of property
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_integer(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
INTEGER, INTENT(OUT) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3765,28 +3765,28 @@
!
! Purpose: Gets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
-! Outputs:
+! Outputs:
! value - value of property
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_real(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
REAL, INTENT(OUT) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3816,28 +3816,28 @@
!
! Purpose: Gets a property list value
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to modify
! name - name of property to modify
-! Outputs:
+! Outputs:
! value - value of property
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_char(prp_id, name, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ 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
@@ -3866,32 +3866,32 @@
END SUBROUTINE h5pget_char
!----------------------------------------------------------------------
-! Name: h5pexist_f
+! Name: h5pexist_f
!
-! Purpose: Queries whether a property name exists in a property list or class.
+! Purpose: Queries whether a property name exists in a property list or class.
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to query
! name - name of property to check for
-! Outputs:
+! Outputs:
! flag - logical flag
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pexist_f(prp_id, name, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
LOGICAL, INTENT(OUT) :: flag ! .TRUE. if exists, .FALSE.
! otherwise
@@ -3920,32 +3920,32 @@
END SUBROUTINE h5pexist_f
!----------------------------------------------------------------------
-! Name: h5pget_size_f
+! Name: h5pget_size_f
!
! Purpose: Queries the size of a property value in bytes.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier to query
! name - name of property to query
-! Outputs:
+! Outputs:
! size - size of property in bytes
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_size_f(prp_id, name, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to query
INTEGER(SIZE_T), INTENT(OUT) :: size ! Size in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3969,31 +3969,31 @@
END SUBROUTINE h5pget_size_f
!----------------------------------------------------------------------
-! Name: h5pget_npros_f
+! Name: h5pget_npros_f
!
! Purpose: Queries number of properties in property list or class
!
-! Inputs:
+! Inputs:
! prp_id - iproperty list identifier to query
-! Outputs:
+! Outputs:
! nprops - number of properties in property object
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_nprops_f(prp_id, nprops, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: nprops ! iNumber of properties
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -4011,13 +4011,13 @@
END SUBROUTINE h5pget_nprops_f
!----------------------------------------------------------------------
-! Name: h5pget_class_name_f
+! Name: h5pget_class_name_f
!
! Purpose: Queries the name of a class.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier to query
-! Outputs:
+! Outputs:
! name - name of a class
! size - Actual length of the class name
! If provided buffer "name" is smaller,
@@ -4025,23 +4025,23 @@
! provided user buffer
! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications: Returned the size of name as an argument
+! Modifications: Returned the size of name as an argument
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_class_name_f(prp_id, name, size, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer to retireve class name
-
+
INTEGER, INTENT(OUT) :: size ! Actual length of the class name
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4068,34 +4068,34 @@
END SUBROUTINE h5pget_class_name_f
!----------------------------------------------------------------------
-! Name: h5pget_class_parent_f
+! Name: h5pget_class_parent_f
!
-! Purpose: Retrieves the parent class of a genric property class.
+! Purpose: Retrieves the parent class of a genric property class.
!
-! Inputs:
+! Inputs:
! prp_id - property list identifier to query
-! Outputs:
+! Outputs:
! parent_id - identifier of the parent class
-! hdferr: - error code
-!
+! hdferr: - error code
+!
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_class_parent_f(prp_id, parent_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(OUT) :: parent_id ! Parent class property list
- ! identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(OUT) :: parent_id ! Parent class property list
+ ! identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -4112,33 +4112,33 @@
END SUBROUTINE h5pget_class_parent_f
!----------------------------------------------------------------------
-! Name: h5pisa_class_f
+! Name: h5pisa_class_f
!
-! Purpose: Determines whether a property list is a member of a class.
+! Purpose: Determines whether a property list is a member of a class.
!
-! Inputs:
-! plist - property list identifier
+! Inputs:
+! plist - property list identifier
! pclass - identifier of the property class
-! Outputs:
+! Outputs:
! flag - .TRUE. if a member, .FALSE. otherwise
-! hdferr: - error code
-!
+! hdferr: - error code
+!
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pisa_class_f(plist, pclass, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: pclass ! Class identifier
LOGICAL, INTENT(OUT) :: flag ! logical flag
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -4162,35 +4162,35 @@
END SUBROUTINE h5pisa_class_f
!----------------------------------------------------------------------
-! Name: h5pcopy_prop_f
+! Name: h5pcopy_prop_f
!
! Purpose: Copies a property from one list or class to another.
!
-! Inputs:
+! Inputs:
! dst_id - Identifier of the destination property list
-! src_id - Identifier of the source property list
+! src_id - Identifier of the source property list
! name - name of the property to copy
-! Outputs:
-! hdferr: - error code
-!
-! Success: 0
-! Failure: -1
+! Outputs:
+! hdferr: - error code
+!
+! Success: 0
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pcopy_prop_f(dst_id, src_id, name, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: dst_id ! Destination property list
- ! identifier
- INTEGER(HID_T), INTENT(IN) :: src_id ! Source property list identifier
+ INTEGER(HID_T), INTENT(IN) :: dst_id ! Destination property list
+ ! identifier
+ INTEGER(HID_T), INTENT(IN) :: src_id ! Source property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Property name
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4213,28 +4213,28 @@
END SUBROUTINE h5pcopy_prop_f
!----------------------------------------------------------------------
-! Name: h5premove_f
+! Name: h5premove_f
!
-! Purpose: Removes a property from a property list.
+! Purpose: Removes a property from a property list.
!
-! Inputs:
+! Inputs:
! plid - Property list identofoer
! name - name of the property to remove
-! Outputs:
-! hdferr: - error code
-!
-! Success: 0
-! Failure: -1
+! Outputs:
+! hdferr: - error code
+!
+! Success: 0
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5premove_f(plid, name, hdferr)
@@ -4251,7 +4251,7 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PREMOVE_C'::h5premove_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: name
- INTEGER(HID_T), INTENT(IN) :: plid
+ INTEGER(HID_T), INTENT(IN) :: plid
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
END FUNCTION h5premove_c
@@ -4261,28 +4261,28 @@
END SUBROUTINE h5premove_f
!----------------------------------------------------------------------
-! Name: h5punregister_f
+! Name: h5punregister_f
!
-! Purpose: Removes a property from a property list class.
+! Purpose: Removes a property from a property list class.
!
-! Inputs:
+! Inputs:
! class - Property list class identifier
! name - name of the property to remove
-! Outputs:
-! hdferr: - error code
-!
-! Success: 0
-! Failure: -1
+! Outputs:
+! hdferr: - error code
+!
+! Success: 0
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5punregister_f(class, name, hdferr)
@@ -4309,27 +4309,27 @@
END SUBROUTINE h5punregister_f
!----------------------------------------------------------------------
-! Name: h5pclose_class_f
+! Name: h5pclose_class_f
!
-! Purpose: Closes an existing property list class.
+! Purpose: Closes an existing property list class.
!
-! Inputs:
+! Inputs:
! class - Property list class identifier
-! Outputs:
-! hdferr: - error code
-!
-! Success: 0
-! Failure: -1
+! Outputs:
+! hdferr: - error code
+!
+! Success: 0
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pclose_class_f(class, hdferr)
@@ -4350,12 +4350,12 @@
END SUBROUTINE h5pclose_class_f
!----------------------------------------------------------------------
-! Name: h5pcreate_class_f
+! Name: h5pcreate_class_f
!
! Purpose: Create a new property list class
!
-! Inputs:
+! Inputs:
! parent - Property list identifier of the parent class
! Possible values include:
! H5P_ROOT_F
@@ -4365,35 +4365,35 @@
! H5P_DATASET_XFER_F
! H5P_FILE_MOUNT_F
! name - name of the class we are creating
-! Outputs:
+! Outputs:
! class - porperty list class identifier
-! hdferr: - error code
-!
-! Success: 0
-! Failure: -1
+! hdferr: - error code
+!
+! Success: 0
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pcreate_class_f(parent, name, class, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: parent ! parent property list class
+ INTEGER(HID_T), INTENT(IN) :: parent ! parent property list class
! identifier
- CHARACTER(LEN=*), INTENT(IN) :: name ! name of property tocreate
+ 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
INTEGER :: name_len
INTERFACE
INTEGER FUNCTION h5pcreate_class_c(parent, name, name_len,&
- class)
+ class)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PCREATE_CLASS_C'::h5pcreate_class_c
@@ -4415,33 +4415,33 @@
!
! Purpose: Registers a permanent property with a property list class.
!
-! Inputs:
-! class - property list class to register
+! 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
+! value - default value for property in newly
! created property lists
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pregister_integer(class, name, size, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
+ 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(SIZE_T), INTENT(IN) :: size ! Size of the property value
INTEGER, INTENT(IN) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4456,7 +4456,7 @@
INTEGER(HID_T), INTENT(IN) :: class
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
INTEGER, INTENT(IN) :: value
END FUNCTION h5pregister_integer_c
END INTERFACE
@@ -4470,33 +4470,33 @@
!
! Purpose: Registers a permanent property with a property list class.
!
-! Inputs:
-! class - property list class to register
+! 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
+! value - default value for property in newly
! created property lists
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pregister_real(class, name, size, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
+ 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(SIZE_T), INTENT(IN) :: size ! size of the property value
REAL, INTENT(IN) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4511,7 +4511,7 @@
INTEGER(HID_T), INTENT(IN) :: class
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
REAL, INTENT(IN) :: value
END FUNCTION h5pregister_real_c
END INTERFACE
@@ -4525,33 +4525,33 @@
!
! Purpose: Registers a permanent property with a property list class.
!
-! Inputs:
-! class - property list class to register
+! 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
+! value - default value for property in newly
! created property lists
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pregister_char(class, name, size, value, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
+ 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(SIZE_T), INTENT(IN) :: size ! size of the property value
CHARACTER(LEN=*), INTENT(IN) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4569,7 +4569,7 @@
INTEGER(HID_T), INTENT(IN) :: class
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
CHARACTER(LEN=*), INTENT(IN) :: value
INTEGER, INTENT(IN) :: value_len
END FUNCTION h5pregisterc_c
@@ -4585,31 +4585,31 @@
!
! Purpose: Registers a temporary property with a property list class.
!
-! Inputs:
+! 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
+! value - initial value for the property
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pinsert_integer(plist, name, size, value, hdferr)
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(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) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4624,7 +4624,7 @@
INTEGER(HID_T), INTENT(IN) :: plist
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
INTEGER, INTENT(IN) :: value
END FUNCTION h5pinsert_integer_c
END INTERFACE
@@ -4638,32 +4638,32 @@
!
! Purpose: Registers a temporary property with a property list class.
!
-! Inputs:
+! 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
+! value - initial value for the property
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pinsert_real(plist, name, size, value, hdferr)
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(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) :: value ! Property value
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: name_len
@@ -4678,7 +4678,7 @@
INTEGER(HID_T), INTENT(IN) :: plist
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
REAL, INTENT(IN) :: value
END FUNCTION h5pinsert_real_c
END INTERFACE
@@ -4693,32 +4693,32 @@
!
! Purpose: Registers a temporary property with a property list class.
!
-! Inputs:
+! 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
+! value - initial value for the property
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! October 10, 2002
+! October 10, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pinsert_char(plist, name, size, value, hdferr)
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
+ 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
INTEGER :: name_len
@@ -4735,7 +4735,7 @@
INTEGER(HID_T), INTENT(IN) :: plist
CHARACTER(LEN=*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
- INTEGER(SIZE_T), INTENT(IN) :: size
+ INTEGER(SIZE_T), INTENT(IN) :: size
CHARACTER(LEN=*), INTENT(IN) :: value
INTEGER, INTENT(IN) :: value_len
END FUNCTION h5pinsertc_c
@@ -4747,31 +4747,31 @@
END SUBROUTINE h5pinsert_char
!----------------------------------------------------------------------
-! Name: h5pset_shuffle_f
+! Name: h5pset_shuffle_f
!
! Purpose: Sets shuffling filter
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! March 12, 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_shuffle_f(prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_shuffle_c
@@ -4791,34 +4791,34 @@
END SUBROUTINE h5pset_shuffle_f
!----------------------------------------------------------------------
-! Name: h5pset_edc_check_f
+! Name: h5pset_edc_check_f
!
-! Purpose: Enables/disables error detecting
+! Purpose: Enables/disables error detecting
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
! flag - EDC flag; possible values:
! H5Z_DISABLE_EDC_F
! H5Z_ENABLE_EDC_F
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! March 13, 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_edc_check_f(prp_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: flag ! Checksum filter flag
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -4832,7 +4832,7 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_EDC_CHECK_C'::h5pset_edc_check_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: flag
+ INTEGER, INTENT(IN) :: flag
END FUNCTION h5pset_edc_check_c
END INTERFACE
hdferr = h5pset_edc_check_c(prp_id, flag)
@@ -4840,31 +4840,31 @@
END SUBROUTINE h5pset_edc_check_f
!----------------------------------------------------------------------
-! Name: h5pget_edc_check_f
+! Name: h5pget_edc_check_f
!
-! Purpose: Queries error detecting
+! Purpose: Queries error detecting
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! March 13, 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_edc_check_f(prp_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property list identifier
INTEGER, INTENT(OUT) :: flag ! Checksum filter flag
! May have one of the following values:
! H5Z_ERROR_EDC_F
@@ -4890,32 +4890,32 @@
END SUBROUTINE h5pget_edc_check_f
!----------------------------------------------------------------------
-! Name: h5pset_fletcher32_f
+! Name: h5pset_fletcher32_f
!
-! Purpose: Sets Fletcher32 checksum of EDC for a dataset creation
+! Purpose: Sets Fletcher32 checksum of EDC for a dataset creation
! property list.
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! March 13, 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fletcher32_f(prp_id, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5pset_fletcher32_c
@@ -4935,32 +4935,32 @@
END SUBROUTINE h5pset_fletcher32_f
!----------------------------------------------------------------------
-! Name: h5pset_family_offset_f
+! Name: h5pset_family_offset_f
!
! Purpose: Sets offset for family file driver.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
! offset - file offset
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! 19 March 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_family_offset_f(prp_id, offset, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: offset ! Offset in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -4974,7 +4974,7 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAMILY_OFFSET_C'::h5pset_family_offset_c
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER(HSIZE_T), INTENT(IN) :: offset
+ INTEGER(HSIZE_T), INTENT(IN) :: offset
END FUNCTION h5pset_family_offset_c
END INTERFACE
hdferr = h5pset_family_offset_c(prp_id, offset)
@@ -4982,35 +4982,35 @@
END SUBROUTINE h5pset_family_offset_f
!----------------------------------------------------------------------
-! Name: h5pset_fapl_multi_l
+! Name: h5pset_fapl_multi_l
!
-! Purpose: Sets up use of the multi-file driver.
+! Purpose: Sets up use of the multi-file driver.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
! mem_map - mapping array
! memb_fapl - property list for each memory usage type
! memb_name - names of member file
-! relax - flag
-! Outputs:
-! hdferr: - error code
+! relax - flag
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! 20 March 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_multi_l(prp_id, memb_map, memb_fapl, memb_name, memb_addr, relax, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_map
INTEGER(HID_T), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_name
@@ -5034,7 +5034,7 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_MULTI_C'::h5pset_fapl_multi_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: memb_name
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_map
INTEGER(HID_T), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_name
@@ -5051,36 +5051,36 @@
enddo
flag = 0
if (relax) flag = 1
- hdferr = h5pset_fapl_multi_c(prp_id, memb_map, memb_fapl, memb_name, lenm, maxlen, memb_addr, flag)
+ hdferr = h5pset_fapl_multi_c(prp_id, memb_map, memb_fapl, memb_name, lenm, maxlen, memb_addr, flag)
END SUBROUTINE h5pset_fapl_multi_l
!----------------------------------------------------------------------
-! Name: h5pset_fapl_multi_s
+! Name: h5pset_fapl_multi_s
!
-! Purpose: Sets up use of the multi-file driver.
+! Purpose: Sets up use of the multi-file driver.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! relax - flag
-! Outputs:
-! hdferr: - error code
+! relax - flag
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! 31 March 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_multi_s(prp_id, relax, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
LOGICAL, INTENT(IN) :: relax
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: flag
@@ -5089,61 +5089,61 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pset_fapl_multi_sc(prp_id,flag)
+ INTEGER FUNCTION h5pset_fapl_multi_sc(prp_id,flag)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_MULTI_SC'::h5pset_fapl_multi_sc
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, INTENT(IN) :: flag
END FUNCTION h5pset_fapl_multi_sc
END INTERFACE
flag = 0
if (relax) flag = 1
- hdferr = h5pset_fapl_multi_sc(prp_id, flag)
+ hdferr = h5pset_fapl_multi_sc(prp_id, flag)
END SUBROUTINE h5pset_fapl_multi_s
!----------------------------------------------------------------------
-! Name: h5pget_fapl_multi_f
+! Name: h5pget_fapl_multi_f
!
-! Purpose: Sets up use of the multi-file driver.
+! Purpose: Sets up use of the multi-file driver.
!
-! Inputs:
+! Inputs:
! prp_id - file creation property list identifier
-! Outputs:
+! Outputs:
! mem_map - mapping array
! memb_fapl - property list for each memory usage type
! memb_name - names of member file
-! relax - flag
-! hdferr: - error code
+! relax - flag
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! maxlen_out - maximum length for memb_name array element
+! maxlen_out - maximum length for memb_name array element
!
! Programmer: Elena Pourmal
! 24 March 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, memb_addr, relax, hdferr, maxlen_out)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_map
INTEGER(HID_T), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_name
!INTEGER(HADDR_T), DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_addr
REAL, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_addr
- INTEGER, OPTIONAL, INTENT(OUT) :: maxlen_out
+ INTEGER, OPTIONAL, INTENT(OUT) :: maxlen_out
LOGICAL, INTENT(OUT) :: relax
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1) :: lenm
INTEGER :: maxlen
- INTEGER :: c_maxlen_out
+ INTEGER :: c_maxlen_out
INTEGER :: flag
INTEGER :: i
@@ -5158,14 +5158,14 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_FAPL_MULTI_C'::h5pget_fapl_multi_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: memb_name
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(H5FD_MEM_NTYPES_F), INTENT(OUT) :: memb_map
INTEGER(HID_T), DIMENSION(H5FD_MEM_NTYPES_F), INTENT(OUT) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(H5FD_MEM_NTYPES_F), INTENT(OUT) :: memb_name
REAL, DIMENSION(H5FD_MEM_NTYPES_F), INTENT(OUT) :: memb_addr
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1) :: lenm
INTEGER :: maxlen
- INTEGER :: c_maxlen_out
+ INTEGER :: c_maxlen_out
INTEGER, INTENT(OUT) :: flag
END FUNCTION h5pget_fapl_multi_c
END INTERFACE
@@ -5173,40 +5173,40 @@
do i=0, H5FD_MEM_NTYPES_F-1
lenm(i) = LEN_TRIM(memb_name(i))
enddo
- hdferr = h5pget_fapl_multi_c(prp_id, memb_map, memb_fapl, memb_name, lenm, maxlen, memb_addr, flag, c_maxlen_out)
+ hdferr = h5pget_fapl_multi_c(prp_id, memb_map, memb_fapl, memb_name, lenm, maxlen, memb_addr, flag, c_maxlen_out)
relax = .TRUE.
- if(flag .eq. 0) relax = .FALSE.
+ if(flag .eq. 0) relax = .FALSE.
if(present(maxlen_out)) maxlen_out = c_maxlen_out
END SUBROUTINE h5pget_fapl_multi_f
!----------------------------------------------------------------------
-! Name: h5pset_szip_f
+! Name: h5pset_szip_f
!
! Purpose: Sets up use of szip compression
!
-! Inputs:
+! Inputs:
! prp_id - dataset creation property list identifier
! options_mask
! pixels_per_block - szip parameters
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! April 10 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5pset_szip_f(prp_id, options_mask, pixels_per_block, hdferr)
+ SUBROUTINE h5pset_szip_f(prp_id, options_mask, pixels_per_block, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
- ! list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
+ ! list identifier
INTEGER, INTENT(IN) :: options_mask
INTEGER, INTENT(IN) :: pixels_per_block
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -5215,50 +5215,50 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pset_szip_c(prp_id, options_mask, pixels_per_block)
+ INTEGER FUNCTION h5pset_szip_c(prp_id, options_mask, pixels_per_block)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_SZIP_C'::h5pset_szip_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, INTENT(IN) :: options_mask
INTEGER, INTENT(IN) :: pixels_per_block
END FUNCTION h5pset_szip_c
END INTERFACE
- hdferr = h5pset_szip_c(prp_id, options_mask, pixels_per_block)
+ hdferr = h5pset_szip_c(prp_id, options_mask, pixels_per_block)
END SUBROUTINE h5pset_szip_f
!----------------------------------------------------------------------
-! Name: h5pall_filters_avail_f
+! Name: h5pall_filters_avail_f
!
! Purpose: Checks if all filters set in the dataset creation
! property list are available
!
-! Inputs:
+! Inputs:
! prp_id - data creation property list identifier
-! Outputs:
+! Outputs:
! flag - .TRUE. if all filters are available
! .FALSE. otherwise
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! April 10 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pall_filters_avail_f(prp_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
- ! list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
+ ! list identifier
LOGICAL, INTENT(OUT) :: flag
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: status
@@ -5267,30 +5267,30 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pall_filters_avail_c(prp_id, status)
+ INTEGER FUNCTION h5pall_filters_avail_c(prp_id, status)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PALL_FILTERS_AVAIL_C'::h5pall_filters_avail_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, INTENT(OUT) :: status
END FUNCTION h5pall_filters_avail_c
END INTERFACE
flag = .TRUE.
- hdferr = h5pall_filters_avail_c(prp_id, status)
+ hdferr = h5pall_filters_avail_c(prp_id, status)
if (status .eq. 0 ) flag = .FALSE.
END SUBROUTINE h5pall_filters_avail_f
!----------------------------------------------------------------------
-! Name: h5pget_filter_by_id_f
+! Name: h5pget_filter_by_id_f
!
! Purpose: Returns information about a filter in a pipeline
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
-! Outputs:
+! Outputs:
! filter_id - filter identifier
! flags - bit vector specifying certain general
! properties of the filter
@@ -5298,23 +5298,23 @@
! cd_values - auxiliary data for the filter
! namelen - number of characters in the name buffer
! name - buffer to retrieve filter name
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! April 10 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_filter_by_id_f(prp_id, filter_id, flags, cd_nelmts, cd_values, namelen, name, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter_id ! Filter identifier
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts !Number of elements in cd_values.
@@ -5339,50 +5339,50 @@
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: name
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: filter_id
+ INTEGER, INTENT(IN) :: filter_id
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values
- INTEGER, INTENT(OUT) :: flags
+ INTEGER, INTENT(OUT) :: flags
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts
INTEGER(SIZE_T), INTENT(IN) :: namelen
CHARACTER(LEN=*), INTENT(OUT) :: name
END FUNCTION h5pget_filter_by_id_c
END INTERFACE
- hdferr = h5pget_filter_by_id_c(prp_id, filter_id, flags, cd_nelmts, &
+ hdferr = h5pget_filter_by_id_c(prp_id, filter_id, flags, cd_nelmts, &
cd_values, namelen, name)
END SUBROUTINE h5pget_filter_by_id_f
!----------------------------------------------------------------------
-! Name: h5pmodify_filter_f
+! Name: h5pmodify_filter_f
!
-! Purpose: Adds a filter to the filter pipeline.
+! Purpose: Adds a filter to the filter pipeline.
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
! filter - filter to be modified
! flags - bit vector specifying certain general
! properties of the filter
! cd_nelmts - number of elements in cd_values
! cd_values - auxiliary data for the filter
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
! April 10 2003
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pmodify_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter !Filter to be modified
INTEGER, INTENT(IN) :: flags !Bit vector specifying certain general
!properties of the filter.
@@ -5400,11 +5400,11 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PMODIFY_FILTER_C'::h5pmodify_filter_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: filter
- INTEGER, INTENT(IN) :: flags
- INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts
- INTEGER, DIMENSION(*), INTENT(IN) :: cd_values
+ INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER, INTENT(IN) :: filter
+ INTEGER, INTENT(IN) :: flags
+ INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts
+ INTEGER, DIMENSION(*), INTENT(IN) :: cd_values
END FUNCTION h5pmodify_filter_c
END INTERFACE
@@ -5412,27 +5412,27 @@
END SUBROUTINE h5pmodify_filter_f
!----------------------------------------------------------------------
-! Name: h5premove_filter_f
+! Name: h5premove_filter_f
!
-! Purpose: Delete one or more filters from the filter pipeline.
+! Purpose: Delete one or more filters from the filter pipeline.
!
-! Inputs:
-! prp_id - data creation or transfer property list
+! Inputs:
+! prp_id - data creation or transfer property list
! identifier
! filter - filter to be removed
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Quincey Koziol
! January 27 2004
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5premove_filter_f(prp_id, filter, hdferr)
@@ -5451,8 +5451,8 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PREMOVE_FILTER_C'::h5premove_filter_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: filter
+ INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER, INTENT(IN) :: filter
END FUNCTION h5premove_filter_c
END INTERFACE
@@ -5460,29 +5460,29 @@
END SUBROUTINE h5premove_filter_f
!----------------------------------------------------------------------
-! Name: H5Pget_attr_phase_change_f
+! Name: H5Pget_attr_phase_change_f
!
-! Purpose: Retrieves attribute storage phase change thresholds
+! Purpose: Retrieves attribute storage phase change thresholds
!
-! Inputs:
+! Inputs:
! ocpl_id - Object (dataset or group) creation property list identifier
-! Outputs:
+! Outputs:
! max_compact - Maximum number of attributes to be stored in compact storage
! (Default: 8)
! min_dense - Minimum number of attributes to be stored in dense storage
! (Default: 6)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
@@ -5505,34 +5505,34 @@
INTEGER(HID_T), INTENT(IN) :: ocpl_id
INTEGER, INTENT(OUT) :: max_compact
INTEGER, INTENT(OUT) :: min_dense
-
+
END FUNCTION h5pget_attr_phase_change_c
END INTERFACE
-
+
hdferr = h5pget_attr_phase_change_c(ocpl_id, max_compact, min_dense)
END SUBROUTINE h5pget_attr_phase_change_f
!----------------------------------------------------------------------
-! Name: H5Pset_attr_creation_order_f
+! Name: H5Pset_attr_creation_order_f
!
! Purpose: Sets tracking and indexing of attribute creation order
!
-! Inputs:
+! Inputs:
! ocpl_id - Object creation property list identifier
! crt_order_flags - Flags specifying whether to track and index attribute creation order
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_attr_creation_order_f(ocpl_id, crt_order_flags , hdferr)
@@ -5552,41 +5552,41 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: ocpl_id
INTEGER, INTENT(IN) :: crt_order_flags
-
+
END FUNCTION H5Pset_attr_creation_order_c
END INTERFACE
-
+
hdferr = H5Pset_attr_creation_order_c(ocpl_id, crt_order_flags)
END SUBROUTINE h5pset_attr_creation_order_f
-
+
!----------------------------------------------------------------------
-! Name: H5Pset_shared_mesg_nindexes_f
+! Name: H5Pset_shared_mesg_nindexes_f
!
-! Purpose: Sets number of shared object header message indexes
+! Purpose: Sets number of shared object header message indexes
!
-! Inputs:
+! Inputs:
! plist_id - file creation property list
! nindexes - Number of shared object header message indexes to be available in files created with this property list
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_shared_mesg_nindexes_f( plist_id, nindexes, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! file creation property list
- INTEGER, INTENT(IN) :: nindexes ! Number of shared object header message indexes
+ INTEGER, INTENT(IN) :: nindexes ! Number of shared object header message indexes
! available in files created WITH this property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
!
@@ -5598,41 +5598,41 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_SHARED_MESG_NINDEXES_C'::h5pset_shared_mesg_nindexes_c
!DEC$ENDIF
-
+
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: nindexes
-
+
END FUNCTION H5pset_shared_mesg_nindexes_c
END INTERFACE
-
- hdferr = h5pset_shared_mesg_nindexes_c(plist_id, nindexes)
+
+ hdferr = h5pset_shared_mesg_nindexes_c(plist_id, nindexes)
END SUBROUTINE h5pset_shared_mesg_nindexes_f
-
+
!----------------------------------------------------------------------
! Name: H5Pset_shared_mesg_index_f
!
! Purpose: Configures the specified shared object header message index
!
-! Inputs:
+! Inputs:
! fcpl_id - File creation property list identifier.
! index_num - Index being configured.
! mesg_type_flags - Types of messages that should be stored in this index.
! min_mesg_size - Minimum message size.
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_shared_mesg_index_f(fcpl_id, index_num, mesg_type_flags, min_mesg_size, hdferr)
@@ -5652,19 +5652,19 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_SHARED_MESG_INDEX_C'::h5pset_shared_mesg_index_c
!DEC$ENDIF
-
- INTEGER(HID_T), INTENT(IN) :: fcpl_id
+
+ INTEGER(HID_T), INTENT(IN) :: fcpl_id
INTEGER, INTENT(IN) :: index_num
INTEGER, INTENT(IN) :: mesg_type_flags
INTEGER, INTENT(IN) :: min_mesg_size
-
+
END FUNCTION H5pset_shared_mesg_index_c
END INTERFACE
-
- hdferr = h5pset_shared_mesg_index_c(fcpl_id, index_num, mesg_type_flags, min_mesg_size)
+
+ hdferr = h5pset_shared_mesg_index_c(fcpl_id, index_num, mesg_type_flags, min_mesg_size)
END SUBROUTINE h5pset_shared_mesg_index_f
-
+
!----------------------------------------------------------------------
! Name: H5Pget_attr_creation_order_f
!
@@ -5675,24 +5675,24 @@
!
! Outputs:
! crt_order_flags - Flags specifying whether to track and index attribute creation order
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_attr_creation_order_f(ocpl_id, crt_order_flags, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (group or dataset) creation property list identifier
- INTEGER, INTENT(OUT) :: crt_order_flags ! Flags specifying whether to track and index attribute creation order
+ INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (group or dataset) creation property list identifier
+ INTEGER, INTENT(OUT) :: crt_order_flags ! Flags specifying whether to track and index attribute creation order
INTEGER, INTENT(OUT) :: hdferr ! Error code
!
! MS FORTRAN needs explicit interface for C functions called here.
@@ -5706,7 +5706,7 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: ocpl_id
INTEGER, INTENT(OUT) :: crt_order_flags
-
+
END FUNCTION H5pget_attr_creation_order_c
END INTERFACE
@@ -5725,18 +5725,18 @@
! high - The latest version of the library that will be used for writing objects.
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 18, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_libver_bounds_f(fapl_id, low, high, hdferr)
@@ -5763,7 +5763,7 @@
INTEGER(HID_T), INTENT(IN) :: fapl_id
INTEGER, INTENT(IN) :: low
INTEGER, INTENT(IN) :: high
-
+
END FUNCTION H5pset_libver_bounds_c
END INTERFACE
@@ -5772,7 +5772,7 @@
END SUBROUTINE h5pset_libver_bounds_f
!----------------------------------------------------------------------
-! Name: H5Pset_link_creation_order_f
+! Name: H5Pset_link_creation_order_f
!
! Purpose: Sets creation order tracking and indexing for links in a group.
!
@@ -5781,18 +5781,18 @@
! crt_order_flags - Creation order flag(s)
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 18, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_link_creation_order_f(gcpl_id, crt_order_flags, hdferr)
@@ -5812,7 +5812,7 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(IN) :: crt_order_flags
-
+
END FUNCTION H5pset_link_creation_order_c
END INTERFACE
@@ -5825,23 +5825,23 @@
!
! Purpose: Queries the settings for conversion between compact and dense groups.
!
-! Inputs:
+! Inputs:
! gcpl_id - Group creation property list identifier
-! Outputs:
+! Outputs:
! max_compact - Maximum number of attributes to be stored in compact storage
! min_dense - Minimum number of attributes to be stored in dense storage
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 20, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr)
@@ -5862,7 +5862,7 @@
INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(OUT) :: max_compact
INTEGER, INTENT(OUT) :: min_dense
-
+
END FUNCTION h5pget_link_phase_change_c
END INTERFACE
@@ -5870,33 +5870,33 @@
END SUBROUTINE h5pget_link_phase_change_f
!----------------------------------------------------------------------
-! Name: H5Pget_obj_track_times_f
+! Name: H5Pget_obj_track_times_f
!
! Purpose: Returns whether times are tracked for an object.
!
-! Inputs:
+! Inputs:
! plist_id - property list id
! flag - object timestamp setting
! .TRUE.,.FALSE.
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 22, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_obj_track_times_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property
- ! list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property
+ ! list identifier
LOGICAL, INTENT(OUT) :: flag ! Object timestamp setting
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: status
@@ -5904,27 +5904,27 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pget_obj_track_times_c(plist_id, status)
+ INTEGER FUNCTION h5pget_obj_track_times_c(plist_id, status)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_OBJ_TRACK_TIMES_C'::h5pget_obj_track_times_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier
INTEGER, INTENT(OUT) :: status
END FUNCTION h5pget_obj_track_times_c
END INTERFACE
flag = .TRUE.
- hdferr = h5pget_obj_track_times_c(plist_id, status)
+ hdferr = h5pget_obj_track_times_c(plist_id, status)
IF(status.EQ.0) flag = .FALSE.
END SUBROUTINE h5pget_obj_track_times_f
!----------------------------------------------------------------------
-! Name: H5Pset_obj_track_times_f
+! Name: H5Pset_obj_track_times_f
!
! Purpose: Set whether the birth, access, modification & change times for
! an object are stored.
-!
+!
! Birth time is the time the object was created. Access time is
! the last time that metadata or raw data was read from this
! object. Modification time is the last time the data for
@@ -5933,34 +5933,34 @@
! time is the last time the metadata for this object was written
! (adding/modifying/deleting an attribute on an object, extending
! the size of a dataset, etc).
-!
+!
! If these times are not tracked, they will be reported as
! 12:00 AM UDT, Jan. 1, 1970 (i.e. 0 seconds past the UNIX
! epoch) when queried.
!
-! Inputs:
+! Inputs:
! plist_id - property list id
! flag - object timestamp setting
! .TRUE.,.FALSE.
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 22, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_obj_track_times_f(plist_id, flag, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property
- ! list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property
+ ! list identifier
LOGICAL, INTENT(IN) :: flag ! Object timestamp setting
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: status
@@ -5968,12 +5968,12 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pset_obj_track_times_c(plist_id, status)
+ INTEGER FUNCTION h5pset_obj_track_times_c(plist_id, status)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_OBJ_TRACK_TIMES_C'::h5pset_obj_track_times_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier
INTEGER, INTENT(IN) :: status
END FUNCTION h5pset_obj_track_times_c
END INTERFACE
@@ -5990,38 +5990,38 @@
!
! Purpose: Specifies in property list whether to create missing intermediate groups.
!
-! Inputs:
+! Inputs:
! lcpl_id - Link creation property list identifier
-! crt_intermed_group - crt_intermed_group specifying whether
-! to create intermediate groups upon the creation
+! crt_intermed_group - crt_intermed_group specifying whether
+! to create intermediate groups upon the creation
! of an object
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! February 22, 2008
!
-! Modifications:
+! Modifications:
!
! Comment: The long subroutine name (>31) on older f90 compilers causes problems
-! so had to shorten the name
+! so had to shorten the name
!--------------------------------------------------------------------------------------
SUBROUTINE h5pset_create_inter_group_f(lcpl_id, crt_intermed_group, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: lcpl_id ! Link creation property list identifier
- INTEGER, INTENT(IN) :: crt_intermed_group ! specifying whether to create intermediate groups
+ INTEGER, INTENT(IN) :: crt_intermed_group ! specifying whether to create intermediate groups
! upon the creation of an object
INTEGER, INTENT(OUT) :: hdferr ! Error code
!
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5pset_create_inter_group_c(lcpl_id, crt_intermed_group)
+ INTEGER FUNCTION h5pset_create_inter_group_c(lcpl_id, crt_intermed_group)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_CREATE_INTER_GROUP_C'::h5pset_create_inter_group_c
@@ -6045,18 +6045,18 @@
!
! Outputs:
! crt_order_flags - Creation order flag(s)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 3, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_link_creation_order_f(gcpl_id, crt_order_flags, hdferr)
@@ -6076,7 +6076,7 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(OUT) :: crt_order_flags
-
+
END FUNCTION H5pget_link_creation_order_c
END INTERFACE
@@ -6085,7 +6085,7 @@
END SUBROUTINE h5pget_link_creation_order_f
!----------------------------------------------------------------------
-! Name: H5Pset_char_encoding
+! Name: H5Pset_char_encoding
!
! Purpose: Sets the character encoding used to encode a string.
!
@@ -6096,24 +6096,24 @@
! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 3, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_char_encoding_f(plist_id, encoding, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier
-
+
INTEGER, INTENT(IN) :: encoding ! String encoding character set:
! H5T_CSET_ASCII_F -> US ASCII
! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding
@@ -6130,7 +6130,7 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: encoding
-
+
END FUNCTION H5pset_char_encoding_c
END INTERFACE
@@ -6139,7 +6139,7 @@
END SUBROUTINE h5pset_char_encoding_f
!----------------------------------------------------------------------
-! Name: H5Pget_char_encoding
+! Name: H5Pget_char_encoding
!
! Purpose: Retrieves the character encoding used to create a string
!
@@ -6150,24 +6150,24 @@
! encoding - Valid values for encoding are:
! H5T_CSET_ASCII_F -> US ASCII
! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 3, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_char_encoding_f(plist_id, encoding, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier
-
+
INTEGER, INTENT(OUT) :: encoding ! Valid values for encoding are:
! H5T_CSET_ASCII_F -> US ASCII
! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding
@@ -6184,7 +6184,7 @@
!DEC$ENDIF
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: encoding
-
+
END FUNCTION H5pget_char_encoding_c
END INTERFACE
@@ -6193,17 +6193,17 @@
END SUBROUTINE h5pget_char_encoding_f
!----------------------------------------------------------------------
-! Name: h5pset_copy_object_f
+! Name: h5pset_copy_object_f
!
! Purpose: Sets properties to be used when an object is copied.
!
-! Inputs:
+! Inputs:
! ocp_plist_id - Object copy property list identifier
! copy_options - Copy option(s) to be set
-! Outputs:
-! hdferr - error code
+! Outputs:
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
@@ -6212,7 +6212,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_copy_object_f(ocp_plist_id, copy_options, hdferr)
@@ -6220,7 +6220,7 @@
INTEGER(HID_T), INTENT(IN) :: ocp_plist_id ! Object copy property list identifier
INTEGER, INTENT(IN) :: copy_options ! Copy option(s) to be set, valid options are:
! H5O_COPY_SHALLOW_HIERARCHY_F
- ! H5O_COPY_EXPAND_SOFT_LINK_F
+ ! H5O_COPY_EXPAND_SOFT_LINK_F
! H5O_COPY_EXPAND_EXT_LINK_F
! H5O_COPY_EXPAND_REFERENCE_F
! H5O_COPY_WITHOUT_ATTR_FLAG_F
@@ -6239,21 +6239,21 @@
INTEGER, INTENT(IN) :: copy_options
END FUNCTION h5pset_copy_object_c
END INTERFACE
- hdferr = h5pset_copy_object_c(ocp_plist_id, copy_options)
+ hdferr = h5pset_copy_object_c(ocp_plist_id, copy_options)
END SUBROUTINE h5pset_copy_object_f
!----------------------------------------------------------------------
-! Name: h5pget_copy_object_f
+! Name: h5pget_copy_object_f
!
! Purpose: Retrieves the properties to be used when an object is copied.
!
-! Inputs:
+! Inputs:
! ocp_plist_id - Object copy property list identifier
-! Outputs:
+! Outputs:
! copy_options - Copy option(s) to be get
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
@@ -6262,7 +6262,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_copy_object_f(ocp_plist_id, copy_options, hdferr)
@@ -6270,7 +6270,7 @@
INTEGER(HID_T), INTENT(IN) :: ocp_plist_id ! Object copy property list identifier
INTEGER, INTENT(OUT) :: copy_options ! valid copy options returned are:
! H5O_COPY_SHALLOW_HIERARCHY_F
- ! H5O_COPY_EXPAND_SOFT_LINK_F
+ ! H5O_COPY_EXPAND_SOFT_LINK_F
! H5O_COPY_EXPAND_EXT_LINK_F
! H5O_COPY_EXPAND_REFERENCE_F
! H5O_COPY_WITHOUT_ATTR_FLAG_F
@@ -6288,22 +6288,22 @@
INTEGER, INTENT(OUT) :: copy_options
END FUNCTION h5pget_copy_object_c
END INTERFACE
- hdferr = h5pget_copy_object_c(ocp_plist_id, copy_options)
+ hdferr = h5pget_copy_object_c(ocp_plist_id, copy_options)
END SUBROUTINE h5pget_copy_object_f
!----------------------------------------------------------------------
-! Name: h5pget_data_transform_f
+! Name: h5pget_data_transform_f
!
! Purpose: Retrieves a data transform expression.
!
-! Inputs:
+! Inputs:
! plist_id - Identifier of the property list or class
-! Outputs:
+! Outputs:
! expression - buffer to hold transform expression
! hdferr - error code
! Success: Actual lenght of the expression
-! If provided buffer "expression" is
-! smaller, than expression will be
+! If provided buffer "expression" is
+! smaller, than expression will be
! truncated to fit into
! provided user buffer
! Failure: -1
@@ -6328,7 +6328,7 @@
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: expression_len
INTEGER(SIZE_T) :: size_default
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -6339,8 +6339,8 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_DATA_TRANSFORM_C'::h5pget_data_transform_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: expression
- INTEGER(HID_T), INTENT(IN) :: plist_id
- CHARACTER(LEN=*), INTENT(OUT) :: expression
+ INTEGER(HID_T), INTENT(IN) :: plist_id
+ CHARACTER(LEN=*), INTENT(OUT) :: expression
INTEGER(SIZE_T) :: size_default
INTEGER :: expression_len
END FUNCTION h5pget_data_transform_c
@@ -6356,14 +6356,14 @@
END SUBROUTINE h5pget_data_transform_f
!----------------------------------------------------------------------
-! Name: h5pset_data_transform_f
+! Name: h5pset_data_transform_f
!
! Purpose: Sets a data transform expression.
!
-! Inputs:
-! plist_id - Identifier of the property list or class
+! Inputs:
+! plist_id - Identifier of the property list or class
! expression - buffer to hold transform expression
-! Outputs:
+! Outputs:
! hdferr - error code
! Success: 0
! Failure: -1
@@ -6375,7 +6375,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_data_transform_f(plist_id, expression, hdferr)
@@ -6394,7 +6394,7 @@
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_DATA_TRANSFORM_C'::h5pset_data_transform_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: expression
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
CHARACTER(LEN=*), INTENT(IN) :: expression
INTEGER :: expression_len
END FUNCTION h5pset_data_transform_c
@@ -6406,11 +6406,11 @@
END SUBROUTINE h5pset_data_transform_f
!----------------------------------------------------------------------
-! Name: H5Pget_local_heap_size_hint_f
+! Name: H5Pget_local_heap_size_hint_f
!
! Purpose: Queries the local heap size hint for original-style groups.
!
-! Inputs:
+! Inputs:
! gcpl_id - Group creation property list identifier
! Outputs:
! size_hint - Hint for size of local heap
@@ -6425,7 +6425,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_local_heap_size_hint_f(gcpl_id, size_hint, hdferr)
@@ -6452,13 +6452,13 @@
END SUBROUTINE h5pget_local_heap_size_hint_f
!----------------------------------------------------------------------
-! Name: H5Pget_est_link_info_f
+! Name: H5Pget_est_link_info_f
!
! Purpose: Queries data required to estimate required local heap or object header size.
!
-! Inputs:
+! Inputs:
! gcpl_id - Group creation property list identifier
-! Outputs:
+! Outputs:
! est_num_entries - Estimated number of links to be inserted into group
! est_name_len - Estimated average length of link names
! hdferr - error code
@@ -6472,12 +6472,12 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_est_link_info_f(gcpl_id, est_num_entries, est_name_len, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
INTEGER, INTENT(OUT) :: est_num_entries ! Estimated number of links to be inserted into group
INTEGER, INTENT(OUT) :: est_name_len ! Estimated average length of link names
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -6490,7 +6490,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_EST_LINK_INFO_C'::h5pget_est_link_info_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: gcpl_id
+ INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(OUT) :: est_num_entries
INTEGER, INTENT(OUT) :: est_name_len
END FUNCTION h5pget_est_link_info_c
@@ -6501,11 +6501,11 @@
END SUBROUTINE h5pget_est_link_info_f
!----------------------------------------------------------------------
-! Name: H5Pset_local_heap_size_hint_f
+! Name: H5Pset_local_heap_size_hint_f
!
! Purpose: Sets the local heap size hint for original-style groups.
!
-! Inputs:
+! Inputs:
! gcpl_id - Group creation property list identifier
! size_hint - Hint for size of local heap
! Outputs:
@@ -6520,7 +6520,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_local_heap_size_hint_f(gcpl_id, size_hint, hdferr)
@@ -6547,12 +6547,12 @@
END SUBROUTINE h5pset_local_heap_size_hint_f
!----------------------------------------------------------------------
-! Name: h5pset_est_link_info_f
+! Name: h5pset_est_link_info_f
!
! Purpose: Sets estimated number of links and length of link names in a group.
!
-! Inputs:
-! gcpl_id - Group creation property list identifier
+! Inputs:
+! gcpl_id - Group creation property list identifier
! est_num_entries - Estimated number of links to be inserted into group
! est_name_len - Estimated average length of link names
! Outputs:
@@ -6567,12 +6567,12 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_est_link_info_f(gcpl_id, est_num_entries, est_name_len, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
+ INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
INTEGER, INTENT(IN) :: est_num_entries ! Estimated number of links to be inserted into group
INTEGER, INTENT(IN) :: est_name_len ! Estimated average length of link names
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -6585,7 +6585,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_EST_LINK_INFO_C'::h5pset_est_link_info_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: gcpl_id
+ INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(IN) :: est_num_entries
INTEGER, INTENT(IN) :: est_name_len
END FUNCTION h5pset_est_link_info_c
@@ -6600,23 +6600,23 @@
!
! Purpose: Sets the parameters for conversion between compact and dense groups.
!
-! Inputs:
-! gcpl_id - Group creation property list identifier
+! Inputs:
+! gcpl_id - Group creation property list identifier
! max_compact - Maximum number of attributes to be stored in compact storage
! min_dense - Minimum number of attributes to be stored in dense storage
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 21, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr)
@@ -6637,7 +6637,7 @@
INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER, INTENT(IN) :: max_compact
INTEGER, INTENT(IN) :: min_dense
-
+
END FUNCTION h5pset_link_phase_change_c
END INTERFACE
@@ -6649,28 +6649,28 @@
!
! Purpose: Sets up use of the direct I/O driver.
!
-! Inputs:
+! Inputs:
! fapl_id - File access property list identifier
! alignment - Required memory alignment boundary
! block_size - File system block size
! cbuf_size - Copy buffer size
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 21, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdferr)
- IMPLICIT NONE
+ IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(IN) :: alignment ! Required memory alignment boundary!
INTEGER(SIZE_T), INTENT(IN) :: block_size ! File system block size
@@ -6685,7 +6685,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_DIRECT_C'::h5pset_fapl_direct_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: fapl_id
+ INTEGER(HID_T), INTENT(IN) :: fapl_id
INTEGER(SIZE_T), INTENT(IN) :: alignment
INTEGER(SIZE_T), INTENT(IN) :: block_size
INTEGER(SIZE_T), INTENT(IN) :: cbuf_size
@@ -6700,28 +6700,28 @@
!
! Purpose: Gets up use of the direct I/O driver.
!
-! Inputs:
+! Inputs:
! fapl_id - File access property list identifier
! Outputs:
! alignment - Required memory alignment boundary
! block_size - File system block size
! cbuf_size - Copy buffer size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! March 21, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdferr)
- IMPLICIT NONE
+ IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: alignment ! Required memory alignment boundary!
INTEGER(SIZE_T), INTENT(OUT) :: block_size ! File system block size
@@ -6736,7 +6736,7 @@
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_FAPL_DIRECT_C'::h5pget_fapl_direct_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: fapl_id
+ INTEGER(HID_T), INTENT(IN) :: fapl_id
INTEGER(SIZE_T), INTENT(OUT) :: alignment
INTEGER(SIZE_T), INTENT(OUT) :: block_size
INTEGER(SIZE_T), INTENT(OUT) :: cbuf_size
@@ -6747,29 +6747,29 @@
END SUBROUTINE h5pget_fapl_direct_f
!----------------------------------------------------------------------
-! Name: H5Pset_attr_phase_change_f
+! Name: H5Pset_attr_phase_change_f
!
! Purpose: Sets attribute storage phase change thresholds.
!
-! Inputs:
+! Inputs:
! ocpl_id - Object (dataset or group) creation property list identifier
-! Outputs:
+! Outputs:
! max_compact - Maximum number of attributes to be stored in compact storage
! (Default: 8)
! min_dense - Minimum number of attributes to be stored in dense storage
! (Default: 6)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
@@ -6792,21 +6792,21 @@
INTEGER(HID_T), INTENT(IN) :: ocpl_id
INTEGER, INTENT(IN) :: max_compact
INTEGER, INTENT(IN) :: min_dense
-
+
END FUNCTION h5pset_attr_phase_change_c
END INTERFACE
-
+
hdferr = h5pset_attr_phase_change_c(ocpl_id, max_compact, min_dense)
END SUBROUTINE h5pset_attr_phase_change_f
!----------------------------------------------------------------------
-! Name: H5Pset_nbit_f
+! Name: H5Pset_nbit_f
!
! Purpose: Sets up the use of the N-Bit filter.
!
-! Inputs:
+! Inputs:
! plist_id - Dataset creation property list identifier.
! Outputs:
! hdferr - error code
@@ -6820,7 +6820,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_nbit_f(plist_id, hdferr)
@@ -6845,11 +6845,11 @@
END SUBROUTINE h5pset_nbit_f
!----------------------------------------------------------------------
-! Name: h5pset_scaleoffset_f
+! Name: h5pset_scaleoffset_f
!
! Purpose: Sets up the use of the Scale-Offset filter.
!
-! Inputs:
+! Inputs:
! plist_id - Dataset creation property list identifier.
! scale_type - Flag indicating compression method.
! scale_factor - Parameter related to scale.
@@ -6865,7 +6865,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_scaleoffset_f(plist_id, scale_type, scale_factor, hdferr)
@@ -6894,11 +6894,11 @@
END SUBROUTINE h5pset_scaleoffset_f
!----------------------------------------------------------------------
-! Name: h5pset_nlinks_f
+! Name: h5pset_nlinks_f
!
! Purpose: Sets maximum number of soft or user-defined link traversals.
!
-! Inputs:
+! Inputs:
! lapl_id - File access property list identifier
! nlinks - Maximum number of links to traverse
!
@@ -6914,7 +6914,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pset_nlinks_f(lapl_id, nlinks, hdferr)
@@ -6922,7 +6922,7 @@
INTEGER(HID_T), INTENT(IN) :: lapl_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(IN) :: nlinks ! Maximum number of links to traverse
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -6935,17 +6935,17 @@
INTEGER(SIZE_T), INTENT(IN) :: nlinks
END FUNCTION h5pset_nlinks_c
END INTERFACE
-
+
hdferr = h5pset_nlinks_c(lapl_id, nlinks)
-
+
END SUBROUTINE h5pset_nlinks_f
!----------------------------------------------------------------------
-! Name: h5pget_nlinks_f
+! Name: h5pget_nlinks_f
!
! Purpose: Gets maximum number of soft or user-defined link traversals.
!
-! Inputs:
+! Inputs:
! lapl_id - File access property list identifier
! nlinks - Maximum number of links to traverse
!
@@ -6961,7 +6961,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5pget_nlinks_f(lapl_id, nlinks, hdferr)
@@ -6969,7 +6969,7 @@
INTEGER(HID_T), INTENT(IN) :: lapl_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: nlinks ! Maximum number of links to traverse
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -6982,9 +6982,9 @@
INTEGER(SIZE_T), INTENT(OUT) :: nlinks
END FUNCTION h5pget_nlinks_c
END INTERFACE
-
+
hdferr = h5pget_nlinks_c(lapl_id, nlinks)
-
+
END SUBROUTINE h5pget_nlinks_f
!----------------------------------------------------------------------
@@ -6992,35 +6992,35 @@
!
! Purpose: Determines whether property is set to enable creating missing intermediate groups.
!
-! Inputs:
+! Inputs:
! lcpl_id - Link creation property list identifier
-! crt_intermed_group - Specifying whether to create intermediate groups upon
+! crt_intermed_group - Specifying whether to create intermediate groups upon
! the creation of an object
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! April 4, 2008
!
-! Modifications:
+! Modifications:
!
! Comment: The long subroutine name (>31) on older f90 compilers causes problems
-! so had to shorten the name
+! so had to shorten the name
!--------------------------------------------------------------------------------------
SUBROUTINE h5pget_create_inter_group_f(lcpl_id, crt_intermed_group, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: lcpl_id ! Link creation property list identifier
- INTEGER, INTENT(IN) :: crt_intermed_group ! Flag specifying whether to create intermediate groups
+ INTEGER, INTENT(IN) :: crt_intermed_group ! Flag specifying whether to create intermediate groups
! upon creation of an object
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
- INTEGER FUNCTION h5pget_create_inter_group_c(lcpl_id, crt_intermed_group)
+ INTEGER FUNCTION h5pget_create_inter_group_c(lcpl_id, crt_intermed_group)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5PGET_CREATE_INTER_GROUP_C'::h5pget_create_inter_group_c
@@ -7055,35 +7055,35 @@
! of one means fully read chunks are always preempted before
! other chunks.
!
-! Inputs:
+! Inputs:
! dapl_id - Dataset access property list identifier.
! rdcc_nslots - The number of chunk slots in the raw data chunk cache for this dataset.
! rdcc_nbytes - The total size of the raw data chunk cache for this dataset.
! rdcc_w0 - The chunk preemption policy for this dataset.
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! April 13, 2009
!
-! Modifications:
+! Modifications:
!--------------------------------------------------------------------------------------
SUBROUTINE h5pset_chunk_cache_f(dapl_id, rdcc_nslots, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dapl_id ! Dataset access property list identifier.
- INTEGER(SIZE_T), INTENT(IN) :: rdcc_nslots ! The number of chunk slots in the raw data
+ INTEGER(SIZE_T), INTENT(IN) :: rdcc_nslots ! The number of chunk slots in the raw data
! chunk cache for this dataset.
- INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes ! The total size of the raw data chunk cache
+ INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes ! The total size of the raw data chunk cache
! for this dataset.
REAL, INTENT(IN) :: rdcc_w0 ! The chunk preemption policy for this dataset.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-
+
INTERFACE
INTEGER FUNCTION h5pset_chunk_cache_c(dapl_id, rdcc_nslots, rdcc_nbytes, rdcc_w0)
@@ -7113,32 +7113,32 @@
! not been set on this property list, the default values for a
! file access property list are returned.
!
-! Inputs:
+! Inputs:
! dapl_id - Dataset access property list identifier.
-! Outputs:
-! rdcc_nslots - Number of chunk slots in the raw data chunk cache hash table.
-! rdcc_nbytes - Total size of the raw data chunk cache, in bytes.
-! rdcc_w0 - Preemption policy.
-! hdferr: - error code
+! Outputs:
+! rdcc_nslots - Number of chunk slots in the raw data chunk cache hash table.
+! rdcc_nbytes - Total size of the raw data chunk cache, in bytes.
+! rdcc_w0 - Preemption policy.
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: M.S. Breitenfeld
! April 13, 2009
!
-! Modifications:
+! Modifications:
!--------------------------------------------------------------------------------------
SUBROUTINE h5pget_chunk_cache_f(dapl_id, rdcc_nslots, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dapl_id ! Dataset access property list identifier.
INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nslots ! Number of chunk slots in the raw data chunk cache hash table.
- INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes ! Total size of the raw data chunk cache, in bytes.
+ INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes ! Total size of the raw data chunk cache, in bytes.
REAL, INTENT(OUT) :: rdcc_w0 ! Preemption policy.
INTEGER, INTENT(OUT) :: hdferr ! error code
-
+
INTERFACE
INTEGER FUNCTION h5pget_chunk_cache_c(dapl_id, rdcc_nslots, rdcc_nbytes, rdcc_w0)
USE H5GLOBAL