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.F902582
1 files changed, 1291 insertions, 1291 deletions
diff --git a/fortran/src/H5Pff.F90 b/fortran/src/H5Pff.F90
index 883e49a..7e06cf3 100644
--- a/fortran/src/H5Pff.F90
+++ b/fortran/src/H5Pff.F90
@@ -141,7 +141,7 @@ MODULE H5P
BIND(C, NAME='h5pget_c')
IMPORT :: c_char, c_ptr
IMPORT :: HID_T
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: name
INTEGER :: name_len
TYPE(C_PTR), VALUE :: value
@@ -178,12 +178,12 @@ MODULE H5P
CONTAINS
-!****s* H5P/h5pcreate_f
+!****s* H5P/h5pcreate_f
! NAME
-! h5pcreate_f
+! h5pcreate_f
!
! PURPOSE
-! Creates a new property as an instance of a property
+! Creates a new property as an instance of a property
! list class.
!
! INPUTS
@@ -208,18 +208,18 @@ CONTAINS
!
! OUTPUTS
! prp_id - property list identifier
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
! Fortran90 Interface:
SUBROUTINE h5pcreate_f(class, prp_id, hdferr)
@@ -238,15 +238,15 @@ CONTAINS
END FUNCTION h5pcreate_c
END INTERFACE
- hdferr = h5pcreate_c(class, prp_id)
+ hdferr = h5pcreate_c(class, prp_id)
END SUBROUTINE h5pcreate_f
-!****s* H5P/h5pset_preserve_f
+!****s* H5P/h5pset_preserve_f
! NAME
-! h5pset_preserve_f
+! h5pset_preserve_f
!
! PURPOSE
-! Sets the dataset transfer property list status to
+! Sets the dataset transfer property list status to
! TRUE or FALSE for initializing compound datatype
! members during write/read operations.
!
@@ -262,20 +262,20 @@ CONTAINS
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! 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
+! port). March 14, 2001
+!
+! Datatype of the flag parameter is changed from
! INTEGER to LOGICAL June 4, 2003
!
! Fortran90 Interface:
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
@@ -295,12 +295,12 @@ CONTAINS
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
-!****s* H5P/h5pget_preserve_f
+!****s* H5P/h5pget_preserve_f
! NAME
-! h5pget_preserve_f
+! h5pget_preserve_f
!
! PURPOSE
! Checks status of the dataset transfer property list.
@@ -310,26 +310,26 @@ CONTAINS
!
! OUTPUTS
! flag - status flag
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! 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
-!
+!
+! Datatype of the flag parameter is changed from
+! INTEGER to LOGICAL
+! June 4, 2003
+!
! Fortran90 Interface:
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
@@ -347,15 +347,15 @@ CONTAINS
INTEGER :: flag_c
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
-!****s* H5P/h5pget_class_f
+!****s* H5P/h5pget_class_f
! NAME
-! h5pget_class_f
+! h5pget_class_f
!
! PURPOSE
! Returns the property list class for a property list.
@@ -365,24 +365,24 @@ CONTAINS
!
! OUTPUTS
! classtype - property list class
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
! Fortran90 Interface:
SUBROUTINE h5pget_class_f(prp_id, classtype, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- INTEGER(HID_T), INTENT(OUT) :: classtype ! The type of the property list
+ INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
+ INTEGER(HID_T), INTENT(OUT) :: classtype ! The type of the property list
! to be created.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
@@ -394,42 +394,42 @@ CONTAINS
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER(HID_T), INTENT(OUT) :: classtype
+ INTEGER(HID_T), 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
-!****s* H5P/h5pcopy_f
+!****s* H5P/h5pcopy_f
! NAME
-! h5pcopy_f
+! h5pcopy_f
!
! PURPOSE
-! Copies an existing property list to create a new
+! Copies an existing property list to create a new
! property list
!
! INPUTS
! prp_id - property list identifier
! OUTPUTS
! new_prp_id - new property list identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
! port). March 14, 2001
!
! Fortran90 Interface:
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(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: new_prp_id ! Identifier of property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
@@ -444,38 +444,38 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: new_prp_id
END FUNCTION h5pcopy_c
END INTERFACE
-
+
hdferr = h5pcopy_c(prp_id, new_prp_id)
END SUBROUTINE h5pcopy_f
-!****s* H5P/h5pclose_f
+!****s* H5P/h5pclose_f
! NAME
-! h5pclose_f
+! h5pclose_f
!
! PURPOSE
-! Terminates access to a property list.
+! Terminates access to a property list.
!
! INPUTS
-! prp_id - identifier of the property list to
-! terminate access to.
+! prp_id - identifier of the property list to
+! terminate access to.
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -484,45 +484,45 @@ CONTAINS
BIND(C,NAME='h5pclose_c')
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
END FUNCTION h5pclose_c
END INTERFACE
-
+
hdferr = h5pclose_c(prp_id)
END SUBROUTINE h5pclose_f
-!****s* H5P/h5pset_chunk_f
+!****s* H5P/h5pset_chunk_f
! NAME
-! h5pset_chunk_f
+! h5pset_chunk_f
!
! PURPOSE
-! Sets the size of the chunks used to store
-! a chunked layout dataset.
+! Sets the size of the chunks used to store
+! a chunked layout dataset.
!
! 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
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -538,16 +538,16 @@ CONTAINS
INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(IN) :: dims
END FUNCTION h5pset_chunk_c
END INTERFACE
-
+
hdferr = h5pset_chunk_c(prp_id, ndims, dims)
END SUBROUTINE h5pset_chunk_f
-!****s* H5P/h5pget_chunk_f
+!****s* H5P/h5pget_chunk_f
! NAME
-! h5pget_chunk_f
+! h5pget_chunk_f
!
! PURPOSE
-! Retrieves the size of chunks for the raw data of a
+! Retrieves the size of chunks for the raw data of a
! chunked layout dataset
!
! INPUTS
@@ -555,26 +555,26 @@ CONTAINS
! ndims - size of dims array
! OUTPUTS
! dims - array with dimension sizes for each chunk
-! hdferr - error code
+! hdferr - error code
! Success: number of chunk dimensions
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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:
@@ -596,19 +596,19 @@ CONTAINS
hdferr = h5pget_chunk_c(prp_id, ndims, dims)
END SUBROUTINE h5pget_chunk_f
-!****s* H5P/h5pset_deflate_f
+!****s* H5P/h5pset_deflate_f
! NAME
-! h5pset_deflate_f
+! h5pset_deflate_f
!
! PURPOSE
-! Sets compression method and compression level.
+! Sets compression method and compression level.
!
! INPUTS
! prp_id - property list identifier
! level - compression level
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
@@ -617,15 +617,15 @@ CONTAINS
! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
! port). March 14, 2001
-!
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -643,15 +643,15 @@ CONTAINS
END FUNCTION h5pset_deflate_c
END INTERFACE
hdferr = h5pset_deflate_c(prp_id, level)
-
+
END SUBROUTINE h5pset_deflate_f
-!****s* H5P/h5pget_version_f
+!****s* H5P/h5pget_version_f
! NAME
-! h5pget_version_f
+! h5pget_version_f
!
! PURPOSE
-! Retrieves the version information of various objects
+! Retrieves the version information of various objects
! for a file creation property list
!
! INPUTS
@@ -661,24 +661,24 @@ CONTAINS
! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
-! Fortran90 Interface:
+! port). March 14, 2001
+!
+! Fortran90 Interface:
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
@@ -698,19 +698,19 @@ CONTAINS
IMPORT :: HID_T
IMPLICIT NONE
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
END INTERFACE
-
+
hdferr = h5pget_version_c(prp_id, boot, freelist, stab, shhdr)
END SUBROUTINE h5pget_version_f
-!****s* H5P/h5pset_userblock_f
+!****s* H5P/h5pset_userblock_f
! NAME
-! h5pset_userblock_f
+! h5pset_userblock_f
!
! PURPOSE
! Sets user block size
@@ -720,24 +720,24 @@ CONTAINS
! size - size of the user-block in bytes
!
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
+! port). March 14, 2001
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -754,38 +754,38 @@ CONTAINS
hdferr = h5pset_userblock_c(prp_id, size)
END SUBROUTINE h5pset_userblock_f
-!****s* H5P/h5pget_userblock_f
+!****s* H5P/h5pget_userblock_f
! NAME
-! h5pget_userblock_f
+! h5pget_userblock_f
!
! PURPOSE
! Gets user block size.
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! OUTPUTS
-!
+!
! block_size - size of the user block in bytes
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -801,41 +801,41 @@ CONTAINS
hdferr = h5pget_userblock_c(prp_id, block_size)
END SUBROUTINE h5pget_userblock_f
-!****s* H5P/h5pset_sizes_f
+!****s* H5P/h5pset_sizes_f
! NAME
-! h5pset_sizes_f
+! h5pset_sizes_f
!
! PURPOSE
-! Sets the byte size of the offsets and lengths used
+! Sets the byte size of the offsets and lengths used
! to address objects in an HDF5 file.
!
! 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
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -844,50 +844,50 @@ CONTAINS
BIND(C,NAME='h5pset_sizes_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
END INTERFACE
-
+
hdferr = h5pset_sizes_c(prp_id, sizeof_addr, sizeof_size)
END SUBROUTINE h5pset_sizes_f
-!****s* H5P/h5pget_sizes_f
+!****s* H5P/h5pget_sizes_f
! NAME
-! h5pget_sizes_f
+! h5pget_sizes_f
!
! PURPOSE
-! Retrieves the size of the offsets and lengths used
+! Retrieves the size of the offsets and lengths used
! in an HDF5 file
!
! INPUTS
! prp_id - file creation property list identifier
! OUTPUTS
-!
-! 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
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -896,49 +896,49 @@ CONTAINS
BIND(C,NAME='h5pget_sizes_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
END INTERFACE
-
+
hdferr = h5pget_sizes_c(prp_id, sizeof_addr, sizeof_size)
END SUBROUTINE h5pget_sizes_f
-!****s* H5P/h5pset_sym_k_f
+!****s* H5P/h5pset_sym_k_f
! NAME
-! h5pset_sym_k_f
+! h5pset_sym_k_f
!
! PURPOSE
-! Sets the size of parameters used to control the
+! Sets the size of parameters used to control the
!symbol table nodes
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! ik - symbol table tree rank
! lk - symbol table node size
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -947,46 +947,46 @@ CONTAINS
BIND(C,NAME='h5pset_sym_k_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
END INTERFACE
-
+
hdferr = h5pset_sym_k_c(prp_id, ik, lk)
END SUBROUTINE h5pset_sym_k_f
-!****s* H5P/h5pget_sym_k_f
+!****s* H5P/h5pget_sym_k_f
! NAME
-! h5pget_sym_k_f
+! 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
-!
+!
! prp_id - file creation property list identifier
! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -997,45 +997,45 @@ CONTAINS
BIND(C,NAME='h5pget_sym_k_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
END INTERFACE
-
+
hdferr = h5pget_sym_k_c(prp_id, ik, lk)
END SUBROUTINE h5pget_sym_k_f
-!****s* H5P/h5pset_istore_k_f
+!****s* H5P/h5pset_istore_k_f
! NAME
-! h5pset_istore_k_f
+! h5pset_istore_k_f
!
! PURPOSE
-! Sets the size of the parameter used to control the
+! Sets the size of the parameter used to control the
! B-trees for indexing chunked datasets
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! ik - 1/2 rank of chunked storage B-tree
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1049,40 +1049,40 @@ CONTAINS
INTEGER, INTENT(IN) :: ik
END FUNCTION h5pset_istore_k_c
END INTERFACE
-
+
hdferr = h5pset_istore_k_c(prp_id, ik)
END SUBROUTINE h5pset_istore_k_f
-!****s* H5P/h5pget_istore_k_f
+!****s* H5P/h5pget_istore_k_f
! NAME
-! h5pget_istore_k_f
+! h5pget_istore_k_f
!
! PURPOSE
-! Queries the 1/2 rank of an indexed storage B-tree.
+! Queries the 1/2 rank of an indexed storage B-tree.
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! OUTPUTS
-!
+!
! ik - 1/2 rank of chunked storage B-tree
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1096,41 +1096,41 @@ CONTAINS
INTEGER, INTENT(OUT) :: ik
END FUNCTION h5pget_istore_k_c
END INTERFACE
-
+
hdferr = h5pget_istore_k_c(prp_id, ik)
END SUBROUTINE h5pget_istore_k_f
-!****s* H5P/h5pget_driver_f
+!****s* H5P/h5pget_driver_f
! NAME
-! h5pget_driver_f
+! h5pget_driver_f
!
! PURPOSE
-! Returns low-lever driver identifier.
+! Returns low-lever driver identifier.
!
! INPUTS
-!
-! prp_id - file access or data transfer property
-! list identifier.
+!
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1144,39 +1144,39 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: driver
END FUNCTION h5pget_driver_c
END INTERFACE
-
+
hdferr = h5pget_driver_c(prp_id, driver)
END SUBROUTINE h5pget_driver_f
-!****s* H5P/h5pset_fapl_stdio_f
+!****s* H5P/h5pset_fapl_stdio_f
! NAME
-! h5pset_fapl_stdio_f
+! h5pset_fapl_stdio_f
!
! PURPOSE
-! Sets the standard I/O driver.
+! Sets the standard I/O driver.
!
! INPUTS
-!
+!
! prp_id - file access property list identifier
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -1188,34 +1188,34 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: prp_id
END FUNCTION h5pset_fapl_stdio_c
END INTERFACE
-
+
hdferr = h5pset_fapl_stdio_c(prp_id)
END SUBROUTINE h5pset_fapl_stdio_f
-!****s* H5P/h5pget_stdio_f
+!****s* H5P/h5pget_stdio_f
! NAME
-! h5pget_stdio_f
+! h5pget_stdio_f
!
! PURPOSE
! NOT AVAILABLE
!
! INPUTS
-!
+!
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! SOURCE
! SUBROUTINE h5pget_stdio_f (prp_id, io, hdferr)
!
@@ -1231,35 +1231,35 @@ CONTAINS
! hdferr = h5pget_stdio_c(prp_id, io)
! END SUBROUTINE h5pget_stdio_f
-!****s* H5P/h5pset_fapl_sec2_f
+!****s* H5P/h5pset_fapl_sec2_f
! NAME
-! h5pset_fapl_sec2_f
+! h5pset_fapl_sec2_f
!
! PURPOSE
-! Sets the sec2 driver.
+! Sets the sec2 driver.
!
! INPUTS
-!
+!
! prp_id - file access property list identifier
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -1268,38 +1268,38 @@ CONTAINS
BIND(C,NAME='h5pset_fapl_sec2_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
-
+
hdferr = h5pset_fapl_sec2_c(prp_id)
END SUBROUTINE h5pset_fapl_sec2_f
-!****s* H5P/h5pget_sec2_f
+!****s* H5P/h5pget_sec2_f
! NAME
-! h5pget_sec2_f
+! h5pget_sec2_f
!
! PURPOSE
! NOT AVAILABLE
!
! INPUTS
-!
+!
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
-! SOURCE! SUBROUTINE h5pget_sec2_f (prp_id, sec2, hdferr)
+! port). March 14, 2001
+!
+! SOURCE! 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
@@ -1312,37 +1312,37 @@ CONTAINS
! hdferr = h5pget_sec2_c(prp_id, sec2)
! END SUBROUTINE h5pget_sec2_f
-!****s* H5P/h5pset_alignment_f
+!****s* H5P/h5pset_alignment_f
! NAME
-! h5pset_alignment_f
+! h5pset_alignment_f
!
! PURPOSE
-! Sets alignment properties of a file access property list.
+! Sets alignment properties of a file access property list.
!
! INPUTS
-!
+!
! prp_id - file access property list identifier
-! threshold - threshold value
+! threshold - threshold value
! alignment - alignment value
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -1358,41 +1358,41 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(IN) :: alignment
END FUNCTION h5pset_alignment_c
END INTERFACE
-
+
hdferr = h5pset_alignment_c(prp_id, threshold, alignment)
END SUBROUTINE h5pset_alignment_f
-!****s* H5P/h5pget_alignment_f
+!****s* H5P/h5pget_alignment_f
! NAME
-! h5pget_alignment_f
+! h5pget_alignment_f
!
! PURPOSE
-! Retrieves the current settings for alignment
-! properties from a file access property list.
+! Retrieves the current settings for alignment
+! properties from a file access property list.
!
! INPUTS
! prp_id - file access property list identifier
!
! OUTPUTS
-! threshold - threshold value
+! threshold - threshold value
! alignment - alignment value
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -1408,44 +1408,44 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(OUT) :: alignment
END FUNCTION h5pget_alignment_c
END INTERFACE
-
+
hdferr = h5pget_alignment_c(prp_id, threshold, alignment)
END SUBROUTINE h5pget_alignment_f
-!****s* H5P/h5pset_fapl_core_f
+!****s* H5P/h5pset_fapl_core_f
! NAME
-! h5pset_fapl_core_f
+! h5pset_fapl_core_f
!
! PURPOSE
-! Modifies the file access property list to use the
-! H5FD_CORE driver.
+! 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.
+! 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
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1456,9 +1456,9 @@ CONTAINS
BIND(C,NAME='h5pset_fapl_core_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
@@ -1466,96 +1466,96 @@ CONTAINS
hdferr = h5pset_fapl_core_c(prp_id, increment, backing_store_flag)
END SUBROUTINE h5pset_fapl_core_f
-!****s* H5P/h5pget_fapl_core_f
+!****s* H5P/h5pget_fapl_core_f
! NAME
-! h5pget_fapl_core_f
+! h5pget_fapl_core_f
!
! PURPOSE
-! Queries core file driver properties.
+! Queries core file driver properties.
!
! 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
+!
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
- INTEGER :: backing_store_flag
+ INTEGER :: backing_store_flag
INTERFACE
INTEGER FUNCTION h5pget_fapl_core_c(prp_id, increment, backing_store_flag) &
BIND(C,NAME='h5pget_fapl_core_c')
IMPORT :: HID_T,SIZE_T
IMPLICIT NONE
- 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
-
+
hdferr = h5pget_fapl_core_c(prp_id, increment, backing_store_flag)
backing_store =.FALSE.
IF (backing_store_flag .EQ. 1) backing_store =.TRUE.
END SUBROUTINE h5pget_fapl_core_f
-!****s* H5P/ h5pset_fapl_family_f
+!****s* H5P/ h5pset_fapl_family_f
! NAME
-! h5pset_fapl_family_f
+! h5pset_fapl_family_f
!
! PURPOSE
-! Sets the file access property list to use the family driver.
+! Sets the file access property list to use the family driver.
!
! 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
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1574,39 +1574,39 @@ CONTAINS
hdferr = h5pset_fapl_family_c(prp_id, memb_size, memb_plist)
END SUBROUTINE h5pset_fapl_family_f
-!****s* H5P/h5pget_fapl_family_f
+!****s* H5P/h5pget_fapl_family_f
! NAME
-! h5pget_fapl_family_f
+! h5pget_fapl_family_f
!
! PURPOSE
-! Returns file access property list information.
+! Returns file access property list information.
!
! 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
+! 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
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1621,52 +1621,52 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: memb_plist
END FUNCTION h5pget_fapl_family_c
END INTERFACE
-
+
hdferr = h5pget_fapl_family_c(prp_id, memb_size, memb_plist)
END SUBROUTINE h5pget_fapl_family_f
-!****s* H5P/h5pset_cache_f
+!****s* H5P/h5pset_cache_f
! NAME
-! h5pset_cache_f
+! h5pset_cache_f
!
! PURPOSE
-! Sets the meta data cache and raw data chunk
+! Sets the meta data cache and raw data chunk
! cache parameters
!
! 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
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1677,8 +1677,8 @@ CONTAINS
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
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
@@ -1687,50 +1687,50 @@ CONTAINS
hdferr = h5pset_cache_c(prp_id, mdc_nelmts, rdcc_nelmts, rdcc_nbytes, rdcc_w0 )
END SUBROUTINE h5pset_cache_f
-!****s* H5P/h5pget_cache_f
+!****s* H5P/h5pget_cache_f
! NAME
-! h5pget_cache_f
+! h5pget_cache_f
!
! PURPOSE
-! Queries the meta data cache and raw data chunk cache
-! parameters.
+! Queries the meta data cache and raw data chunk cache
+! parameters.
!
! 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
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! 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
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1741,58 +1741,58 @@ CONTAINS
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
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
END INTERFACE
-
+
hdferr = h5pget_cache_c(prp_id, mdc_nelmts,rdcc_nelmts, rdcc_nbytes, rdcc_w0 )
END SUBROUTINE h5pget_cache_f
-!****s* H5P/h5pset_fapl_split_f
+!****s* H5P/h5pset_fapl_split_f
! NAME
-! h5pset_fapl_split_f
+! h5pset_fapl_split_f
!
! PURPOSE
-! Emulates the old split file driver.
+! Emulates the old split file driver.
!
! 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
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -1805,10 +1805,10 @@ CONTAINS
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id
- CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: meta_ext
+ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: meta_ext
INTEGER(HID_T), INTENT(IN) :: meta_plist
CHARACTER(KIND=C_CHAR), DIMENSION(*), 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
@@ -1818,30 +1818,30 @@ CONTAINS
hdferr = h5pset_fapl_split_c(prp_id,meta_len,meta_ext,meta_plist,raw_len,raw_ext,raw_plist)
END SUBROUTINE h5pset_fapl_split_f
-!****s* H5P/h5pget_split_f
+!****s* H5P/h5pget_split_f
! NAME
-! h5pget_split_f
+! h5pget_split_f
!
! PURPOSE
! NOT AVAILABLE
!
! INPUTS
-!
+!
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! SOURCE
! SUBROUTINE h5pget_split_f(prp_id, meta_ext_size, meta_ext, meta_plist,raw_ext_size,&
! raw_ext, raw_plist, hdferr)
@@ -1870,37 +1870,37 @@ CONTAINS
! raw_ext_size, raw_ext, raw_plist )
! END SUBROUTINE h5pget_split_f
-!****s* H5P/h5pset_gc_references_f
+!****s* H5P/h5pset_gc_references_f
! NAME
-! h5pset_gc_references_f
+! h5pset_gc_references_f
!
! PURPOSE
-! Sets garbage collecting references flag.
+! Sets garbage collecting references flag.
!
! 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
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
-! Fortran90 Interface:
+! port). March 14, 2001
+!
+! Fortran90 Interface:
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
@@ -1919,37 +1919,37 @@ CONTAINS
hdferr = h5pset_gc_references_c(prp_id, gc_reference)
END SUBROUTINE h5pset_gc_references_f
-!****s* H5P/h5pget_gc_references_f
+!****s* H5P/h5pget_gc_references_f
! NAME
-! h5pget_gc_references_f
+! h5pget_gc_references_f
!
! PURPOSE
-! Returns garbage collecting references setting.
+! Returns garbage collecting references setting.
!
! INPUTS
-!
+!
! prp_id - file access property list identifier
! OUTPUTS
-!
-! gc_reference - flag for stting garbage collection on
+!
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -1964,20 +1964,20 @@ CONTAINS
INTEGER, INTENT(OUT) :: gc_reference
END FUNCTION h5pget_gc_references_c
END INTERFACE
-
+
hdferr = h5pget_gc_references_c(prp_id, gc_reference)
END SUBROUTINE h5pget_gc_references_f
-!****s* H5P/h5pset_layout_f
+!****s* H5P/h5pset_layout_f
! NAME
-! h5pset_layout_f
+! h5pset_layout_f
!
! PURPOSE
-! Sets the type of storage used store the raw data
-! for a dataset.
+! Sets the type of storage used store the raw data
+! for a dataset.
!
! INPUTS
-!
+!
! prp_id - data creation property list identifier
! layout - type of storage layout for raw data
! possible values are:
@@ -1985,24 +1985,24 @@ CONTAINS
! H5D_CONTIGUOUS_F
! H5D_CHUNKED_F
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -2020,44 +2020,44 @@ CONTAINS
INTEGER, INTENT(IN) :: layout
END FUNCTION h5pset_layout_c
END INTERFACE
-
+
hdferr = h5pset_layout_c(prp_id, layout)
END SUBROUTINE h5pset_layout_f
-!****s* H5P/h5pget_layout_f
+!****s* H5P/h5pget_layout_f
! NAME
-! h5pget_layout_f
+! h5pget_layout_f
!
! PURPOSE
-! Returns the layout of the raw data for a dataset.
+! Returns the layout of the raw data for a dataset.
!
! INPUTS
-!
+!
! prp_id - data creation property list identifier
! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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)
@@ -2075,31 +2075,31 @@ CONTAINS
INTEGER, INTENT(OUT) :: layout
END FUNCTION h5pget_layout_c
END INTERFACE
-
+
hdferr = h5pget_layout_c(prp_id, layout)
END SUBROUTINE h5pget_layout_f
-!****s* H5P/h5pset_filter_f
+!****s* H5P/h5pset_filter_f
! NAME
-! h5pset_filter_f
+! h5pset_filter_f
!
! PURPOSE
-! Adds a filter to the filter pipeline.
+! Adds a filter to the filter pipeline.
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! 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
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -2108,7 +2108,7 @@ CONTAINS
! Fortran90 Interface:
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.
@@ -2122,48 +2122,48 @@ CONTAINS
BIND(C,NAME='h5pset_filter_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
-
+
hdferr = h5pset_filter_c(prp_id, filter, flags, cd_nelmts, cd_values )
END SUBROUTINE h5pset_filter_f
-!****s* H5P/h5pget_nfilters_f
+!****s* H5P/h5pget_nfilters_f
! NAME
-! h5pget_nfilters_f
+! h5pget_nfilters_f
!
! PURPOSE
-! Returns the number of filters in the pipeline.
+! Returns the number of filters in the pipeline.
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! prp_id - data creation or transfer property list
! identifier
! OUTPUTS
-!
+!
! nfilters - number of filters in the pipeline
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -2177,26 +2177,26 @@ CONTAINS
INTEGER, INTENT(OUT) :: nfilters
END FUNCTION h5pget_nfilters_c
END INTERFACE
-
+
hdferr = h5pget_nfilters_c(prp_id, nfilters)
END SUBROUTINE h5pget_nfilters_f
-!****s* H5P/h5pget_filter_f
+!****s* H5P/h5pget_filter_f
! NAME
-! h5pget_filter_f
+! h5pget_filter_f
!
! PURPOSE
! Returns information about a filter in a pipeline
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! prp_id - data creation or transfer property list
! identifier
! filter_number - sequence number within the filter
-! pipeline of the filter for which
+! pipeline of the filter for which
! information is sought
! OUTPUTS
-!
+!
! filter_id - filter identification number
! flags - bit vector specifying certain general
! properties of the filter
@@ -2204,25 +2204,25 @@ CONTAINS
! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
@@ -2230,7 +2230,7 @@ CONTAINS
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
! 0 on success and -1 on failure
!*****
@@ -2247,60 +2247,60 @@ CONTAINS
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
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(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: name
INTEGER, INTENT(OUT) :: filter_id
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
-!****s* H5P/h5pset_external_f
+!****s* H5P/h5pset_external_f
! NAME
-! h5pset_external_f
+! h5pset_external_f
!
! PURPOSE
-! Adds an external file to the list of external files.
+! Adds an external file to the list of external files.
!
! 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.
+! bytes - size of the external file data.
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
! port). March 14, 2001
!
! Changed type of 'offset' from integer to off_t -- MSB January 9, 2012
-!
+!
! Fortran90 Interface:
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(OFF_T), INTENT(IN) :: offset ! Offset, in bytes, from the beginning
- ! of the file to the location in the file
+ INTEGER(OFF_T), 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
! 0 on success and -1 on failure
@@ -2320,43 +2320,43 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(IN) :: bytes
END FUNCTION h5pset_external_c
END INTERFACE
-
+
namelen = LEN(name)
hdferr = h5pset_external_c(prp_id, name, namelen, offset, bytes)
END SUBROUTINE h5pset_external_f
-!****s* H5P/h5pget_external_count_f
+!****s* H5P/h5pget_external_count_f
! NAME
-! h5pget_external_count_f
+! h5pget_external_count_f
!
! PURPOSE
-! Returns the number of external files for a dataset.
+! Returns the number of external files for a dataset.
!
! INPUTS
-!
+!
! prp_id - dataset creation property list identifier
! OUTPUTS
-!
-! count - number of external files for the
+!
+! count - number of external files for the
! specified dataset
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -2366,60 +2366,60 @@ CONTAINS
BIND(C,NAME='h5pget_external_count_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
-
+
hdferr = h5pget_external_count_c(prp_id, count)
END SUBROUTINE h5pget_external_count_f
-!****s* H5P/h5pget_external_f
+!****s* H5P/h5pget_external_f
! NAME
-! h5pget_external_f
+! h5pget_external_f
!
! PURPOSE
-! Returns information about an external file.
+! Returns information about an external file.
!
! INPUTS
-!
+!
! prp_id - dataset creation property list identifier
! OUTPUTS
-!
-! idx - external file index
+!
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
! port). March 14, 2001
!
! Changed type of 'offset' from integer to off_t -- MSB January 9, 2012
-!
+!
! Fortran90 Interface:
SUBROUTINE h5pget_external_f(prp_id, idx, name_size, name, offset,bytes, hdferr)
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(OFF_T), INTENT(OUT) :: offset ! Offset, in bytes, from the beginning
- ! of the file to the location in the file
+ INTEGER(OFF_T), 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
! 0 on success and -1 on failure
@@ -2431,54 +2431,54 @@ CONTAINS
IMPORT :: HID_T, SIZE_T, HSIZE_T, OFF_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id
- INTEGER, INTENT(IN) :: idx
+ INTEGER, INTENT(IN) :: idx
INTEGER(SIZE_T), INTENT(IN) :: name_size
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: name
INTEGER(OFF_T), INTENT(OUT) :: offset
INTEGER(HSIZE_T), INTENT(OUT) :: bytes
END FUNCTION h5pget_external_c
END INTERFACE
-
+
hdferr = h5pget_external_c(prp_id, idx, name_size, name, offset, bytes)
END SUBROUTINE h5pget_external_f
-!****s* H5P/h5pset_btree_ratios_f
+!****s* H5P/h5pset_btree_ratios_f
! NAME
-! h5pset_btree_ratios_f
+! h5pset_btree_ratios_f
!
! PURPOSE
-! Sets B-tree split ratios for a dataset transfer
-! property list.
+! 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
+!
+! 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
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -2493,7 +2493,7 @@ CONTAINS
REAL, INTENT(IN) :: right
END FUNCTION h5pset_btree_ratios_c
END INTERFACE
-
+
hdferr = h5pset_btree_ratios_c(prp_id, left, middle, right)
END SUBROUTINE h5pset_btree_ratios_f
@@ -2505,34 +2505,34 @@ CONTAINS
! Gets B-tree split ratios for a dataset transfer property list
!
! INPUTS
-!
-! prp_id - the dataset transfer property list
-! identifier
+!
+! prp_id - the dataset transfer property list
+! identifier
! OUTPUTS
-!
-! left - the B-tree split ratio for left-most nodes
+!
+! 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
!
! AUTHOR
! Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
! HISTORY
-! Explicit Fortran interfaces were added for
+! Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 14, 2001
-!
+! port). March 14, 2001
+!
! Fortran90 Interface:
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
+ 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
! 0 on success and -1 on failure
@@ -2548,43 +2548,43 @@ CONTAINS
REAL, INTENT(OUT) :: right
END FUNCTION h5pget_btree_ratios_c
END INTERFACE
-
+
hdferr = h5pget_btree_ratios_c(prp_id, left, middle, right)
END SUBROUTINE h5pget_btree_ratios_f
-!****s* H5P/h5pget_fclose_degree_f
+!****s* H5P/h5pget_fclose_degree_f
! NAME
-! h5pget_fclose_degree_f
+! h5pget_fclose_degree_f
!
! PURPOSE
! Returns the degree for the file close behavior.
!
! INPUTS
-!
+!
! fapl_id - File access property list identifier
! OUTPUTS
-!
+!
! degree - 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
!
! AUTHOR
! Elena Pourmal
-! September 26, 2002
+! September 26, 2002
!
! HISTORY
-!
-!
+!
+!
! Fortran90 Interface:
SUBROUTINE h5pget_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
- INTEGER, INTENT(OUT) :: degree ! Possible values are:
+ INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
+ INTEGER, INTENT(OUT) :: degree ! Possible values are:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
@@ -2601,19 +2601,19 @@ CONTAINS
INTEGER, INTENT(OUT) :: degree
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
-!****s* H5P/h5pset_fclose_degree_f
+!****s* H5P/h5pset_fclose_degree_f
! NAME
-! h5pset_fclose_degree_f
+! h5pset_fclose_degree_f
!
! PURPOSE
! Sets the degree for the file close behavior.
!
! INPUTS
-!
+!
! fapl_id - file access property list identifier
! degree - Possible values are:
! H5F_CLOSE_DEFAULT_F
@@ -2621,19 +2621,19 @@ CONTAINS
! H5F_CLOSE_SEMI_F
! H5F_CLOSE_STRONG_F
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! September 26, 2002
+! September 26, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pset_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
- INTEGER, INTENT(IN) :: degree ! Possible values are:
+ INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
+ INTEGER, INTENT(IN) :: degree ! Possible values are:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
@@ -2651,43 +2651,43 @@ CONTAINS
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
-!****s* H5P/h5pequal_f
+!****s* H5P/h5pequal_f
! NAME
-! h5pequal_f
+! h5pequal_f
!
! PURPOSE
! Checks if two property lists are eqaul
!
! INPUTS
-!
+!
! plist1_id - property list identifier
! plist2_id - property list identifier
! 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.
!
! AUTHOR
! Elena Pourmal
-! September 30, 2002
+! September 30, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
INTEGER :: c_flag
-
+
INTERFACE
INTEGER FUNCTION h5pequal_c(plist1_id, plist2_id, c_flag) &
BIND(C,NAME='h5pequal_c')
@@ -2700,36 +2700,36 @@ CONTAINS
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
!****s* H5P/h5pset_buffer_f
! NAME
-! h5pset_buffer_f
+! h5pset_buffer_f
!
! PURPOSE
! Sets sixe for conversion buffer
!
! INPUTS
! plist_id - data transfer property list identifier
-! size - buffer size
+! size - buffer size
! OUTPUTS
-!
-! hdferr: - error code
+!
+! hdferr: - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 2, 2002
+! October 2, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -2745,36 +2745,36 @@ CONTAINS
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
!****s* H5P/h5pget_buffer_f
! NAME
-! h5pget_buffer_f
+! h5pget_buffer_f
!
! PURPOSE
! Gets size for conversion buffer
!
! INPUTS
-!
+!
! plist_id - data transfer property list identifier
! OUTPUTS
-!
-! size - buffer size
-! hdferr - error code
+!
+! size - buffer size
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 2, 2002
+! October 2, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -2790,7 +2790,7 @@ CONTAINS
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
!****s* H5P/h5pfill_value_defined_f
@@ -2801,17 +2801,17 @@ CONTAINS
! Check if fill value is defined.
!
! INPUTS
-!
+!
! plist_id - dataset creation property list identifier
! 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
!
@@ -2841,7 +2841,7 @@ CONTAINS
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
!****s* H5P/h5pset_alloc_time_f
@@ -2852,7 +2852,7 @@ CONTAINS
! Set space allocation time for dataset during creation.
!
! INPUTS
-!
+!
! plist_id - dataset creation property list identifier
! flag - allocation time flag:
! H5D_ALLOC_TIME_ERROR_F
@@ -2861,14 +2861,14 @@ CONTAINS
! H5D_ALLOC_TIME_LATE_F
! H5D_ALLOC_TIME_INCR_F
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pset_alloc_time_f(plist_id, flag, hdferr)
@@ -2882,8 +2882,8 @@ CONTAINS
! H5D_ALLOC_TIME_INCR_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
-
+!*****
+
INTERFACE
INTEGER FUNCTION h5pset_alloc_time_c(plist_id, flag) &
BIND(C,NAME='h5pset_alloc_time_c')
@@ -2893,8 +2893,8 @@ CONTAINS
INTEGER, INTENT(IN) :: flag
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
!****s* H5P/h5pget_alloc_time_f
@@ -2905,23 +2905,23 @@ CONTAINS
! Get space allocation time for dataset during creation.
!
! INPUTS
-!
+!
! plist_id - dataset creation property list identifier
! OUTPUTS
-!
+!
! flag - allocation time flag:
! H5D_ALLOC_TIME_ERROR_F
! H5D_ALLOC_TIME_DEFAULT_F
! 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
!
! AUTHOR
! Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pget_alloc_time_f(plist_id, flag, hdferr)
@@ -2946,8 +2946,8 @@ CONTAINS
INTEGER, INTENT(OUT) :: flag
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
!****s* H5P/h5pset_fill_time_f
@@ -2958,21 +2958,21 @@ CONTAINS
! Set fill value writing time for dataset
!
! INPUTS
-!
+!
! plist_id - dataset creation property list identifier
! flag - fill time flag:
! H5D_FILL_TIME_ERROR_F
! H5D_FILL_TIME_ALLOC_F
! H5D_FILL_TIME_NEVER_F
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pset_fill_time_f(plist_id, flag, hdferr)
@@ -2984,7 +2984,7 @@ CONTAINS
! H5D_FILL_TIME_NEVER_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pset_fill_time_c(plist_id, flag) &
@@ -2995,8 +2995,8 @@ CONTAINS
INTEGER, INTENT(IN) :: flag
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
!****s* H5P/h5pget_fill_time_f
@@ -3007,11 +3007,11 @@ CONTAINS
! Get fill value writing time for dataset
!
! INPUTS
-!
+!
! plist_id - dataset creation property list identifier
! OUTPUTS
-!
-! hdferr: - error code
+!
+! hdferr: - error code
! Success: 0
! Failure: -1
! OPTIONAL PARAMETERS
@@ -3022,7 +3022,7 @@ CONTAINS
! H5D_FILL_TIME_NEVER_F
! AUTHOR
! Elena Pourmal
-! October 4, 2002
+! October 4, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pget_fill_time_f(plist_id, flag, hdferr)
@@ -3034,8 +3034,8 @@ CONTAINS
! H5D_FILL_TIME_NEVER_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
-
+!*****
+
INTERFACE
INTEGER FUNCTION h5pget_fill_time_c(plist_id, flag) &
BIND(C,NAME='h5pget_fill_time_c')
@@ -3045,36 +3045,36 @@ CONTAINS
INTEGER, INTENT(OUT) :: flag
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
-!****s* H5P/ h5pset_meta_block_size_f
+!****s* H5P/ h5pset_meta_block_size_f
! NAME
-! h5pset_meta_block_size_f
+! h5pset_meta_block_size_f
!
! PURPOSE
-! Sets the minimum size of metadata block allocations
+! Sets the minimum size of metadata block allocations
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! size - metatdata block size
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -3087,78 +3087,78 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(IN) :: size
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
-!****s* H5P/h5pget_meta_block_size_f
+!****s* H5P/h5pget_meta_block_size_f
! NAME
-! h5pget_meta_block_size_f
+! h5pget_meta_block_size_f
!
! PURPOSE
-! Gets the minimum size of metadata block allocations
+! Gets the minimum size of metadata block allocations
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! OUTPUTS
-!
+!
! size - metatdata block size
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
INTERFACE
INTEGER FUNCTION h5pget_meta_block_size_c(plist_id, size) &
BIND(C,NAME='h5pget_meta_block_size_c')
- IMPORT :: HID_T, HSIZE_T
+ IMPORT :: HID_T, HSIZE_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER(HSIZE_T), INTENT(OUT) :: size
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
-!****s* H5P/h5pset_sieve_buf_size_f
+!****s* H5P/h5pset_sieve_buf_size_f
! NAME
-! h5pset_sieve_buf_size_f
+! h5pset_sieve_buf_size_f
!
! PURPOSE
! Sets the maximum size of the data sieve buffer
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! size - sieve buffer size
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -3171,36 +3171,36 @@ CONTAINS
INTEGER(SIZE_T), INTENT(IN) :: size
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
!****s* H5P/h5pget_sieve_buf_size_f
! NAME
-! h5pget_sieve_buf_size_f
+! h5pget_sieve_buf_size_f
!
! PURPOSE
! Gets the maximum size of the data sieve buffer
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! OUTPUTS
-!
+!
! size - sieve buffer size
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -3213,35 +3213,35 @@ CONTAINS
INTEGER(SIZE_T), INTENT(OUT) :: size
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
-!****s* H5P/h5pset_small_data_block_size_f
+!****s* H5P/h5pset_small_data_block_size_f
! NAME
-! h5pset_small_data_block_size_f
+! h5pset_small_data_block_size_f
!
! PURPOSE
! Sets the minimum size of "small" raw data block
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! size - small raw data block size
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -3256,34 +3256,34 @@ CONTAINS
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
-!****s* H5P/h5pget_small_data_block_size_f
+!****s* H5P/h5pget_small_data_block_size_f
! NAME
-! h5pget_small_data_block_size_f
+! h5pget_small_data_block_size_f
!
! PURPOSE
! Gets the minimum size of "small" raw data block
!
! INPUTS
-!
+!
! plist_id - file access property list identifier
! OUTPUTS
-!
+!
! size - small raw data block size
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -3297,35 +3297,35 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(OUT) :: size
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
-!****s* H5P/h5pset_hyper_vector_size_f
+!****s* H5P/h5pset_hyper_vector_size_f
! NAME
-! h5pset_hyper_vector_size_f
+! h5pset_hyper_vector_size_f
!
! PURPOSE
! Set the number of "I/O" vectors (vector size)
!
! INPUTS
-!
+!
! plist_id - dataset transfer property list identifier
! size - vector size
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -3339,35 +3339,35 @@ CONTAINS
INTEGER(SIZE_T), INTENT(IN) :: size
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
-!****s* H5P/ h5pget_hyper_vector_size_f
+!****s* H5P/ h5pget_hyper_vector_size_f
! NAME
-! h5pget_hyper_vector_size_f
+! h5pget_hyper_vector_size_f
!
! PURPOSE
! Get the number of "I/O" vectors (vector size)
!
! INPUTS
-!
+!
! plist_id - dataset transfer property list identifier
! OUTPUTS
-!
+!
! size - vector size
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 7, 2002
+! October 7, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -3382,42 +3382,42 @@ CONTAINS
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
-!****s* H5P/h5pexist_f
+!****s* H5P/h5pexist_f
! NAME
-! h5pexist_f
+! h5pexist_f
!
! PURPOSE
-! Queries whether a property name exists in a property list or class.
+! Queries whether a property name exists in a property list or class.
!
! INPUTS
-!
+!
! prp_id - property list identifier to query
! name - name of property to check for
! OUTPUTS
-!
+!
! flag - logical flag
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
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
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
!*****
INTEGER :: name_len
-
+
INTERFACE
INTEGER FUNCTION h5pexist_c(prp_id, name, name_len) &
BIND(C,NAME='h5pexist_c')
@@ -3438,43 +3438,43 @@ CONTAINS
ENDIF
END SUBROUTINE h5pexist_f
-!****s* H5P/h5pget_size_f
+!****s* H5P/h5pget_size_f
!
! NAME
-! h5pget_size_f
+! h5pget_size_f
!
! PURPOSE
! Queries the size of a property value in bytes.
!
! INPUTS
-!
+!
! prp_id - property list identifier to query
! name - name of property to query
! OUTPUTS
-!
+!
! size - size of property in bytes
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! HISTORY
-!
-!
+!
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
INTEGER :: name_len
-
+
INTERFACE
INTEGER FUNCTION h5pget_size_c(prp_id, name, name_len, size) &
BIND(C,NAME='h5pget_size_c')
@@ -3491,31 +3491,31 @@ CONTAINS
hdferr = h5pget_size_c(prp_id, name , name_len, size)
END SUBROUTINE h5pget_size_f
-!****s* H5P/h5pget_npros_f
+!****s* H5P/h5pget_npros_f
! NAME
-! h5pget_npros_f
+! h5pget_npros_f
!
! PURPOSE
! Queries number of properties in property list or class
!
! INPUTS
-!
+!
! prp_id - iproperty list identifier to query
! OUTPUTS
-!
+!
! nprops - number of properties in property object
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
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 ! Number of properties
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
@@ -3532,18 +3532,18 @@ CONTAINS
hdferr = h5pget_nprops_c(prp_id, nprops)
END SUBROUTINE h5pget_nprops_f
-!****s* H5P/h5pget_class_name_f
+!****s* H5P/h5pget_class_name_f
! NAME
-! h5pget_class_name_f
+! h5pget_class_name_f
!
! PURPOSE
! Queries the name of a class.
!
! INPUTS
-!
+!
! prp_id - property list identifier to query
! OUTPUTS
-!
+!
! name - name of a class
! size - Actual length of the class name
! NOTE: If provided buffer "name" is smaller,
@@ -3551,26 +3551,26 @@ CONTAINS
! provided user buffer.
! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! HISTORY
-! Returned the size of name as an argument
-!
+! Returned the size of name as an argument
+!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
INTEGER :: name_len
-
+
INTERFACE
INTEGER FUNCTION h5pget_class_name_c(prp_id, name, name_len) &
BIND(C,NAME='h5pget_class_name_c')
@@ -3582,42 +3582,42 @@ CONTAINS
INTEGER, INTENT(IN) :: name_len
END FUNCTION h5pget_class_name_c
END INTERFACE
-
+
name_len = LEN(name)
size = h5pget_class_name_c(prp_id, name, name_len)
-
+
hdferr = 0
IF(size.LT.0) hdferr = -1
-
+
END SUBROUTINE h5pget_class_name_f
-!****s* H5P/h5pget_class_parent_f
+!****s* H5P/h5pget_class_parent_f
! NAME
-! h5pget_class_parent_f
+! h5pget_class_parent_f
!
! PURPOSE
-! Retrieves the parent class of a genric property class.
+! Retrieves the parent class of a genric property class.
!
! INPUTS
-!
+!
! prp_id - property list identifier to query
! OUTPUTS
-!
+!
! parent_id - identifier of the parent class
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -3633,32 +3633,32 @@ CONTAINS
hdferr = h5pget_class_parent_c(prp_id, parent_id)
END SUBROUTINE h5pget_class_parent_f
-!****s* H5P/h5pisa_class_f
+!****s* H5P/h5pisa_class_f
! NAME
-! h5pisa_class_f
+! h5pisa_class_f
!
! PURPOSE
-! Determines whether a property list is a member of a class.
+! Determines whether a property list is a member of a class.
!
! INPUTS
-!
-! plist - property list identifier
+!
+! plist - property list identifier
! pclass - identifier of the property class
! OUTPUTS
-!
+!
! flag - .TRUE. if a member, .FALSE. otherwise
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
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
@@ -3681,40 +3681,40 @@ CONTAINS
ENDIF
END SUBROUTINE h5pisa_class_f
-!****s* H5P/h5pcopy_prop_f
+!****s* H5P/h5pcopy_prop_f
! NAME
-! h5pcopy_prop_f
+! h5pcopy_prop_f
!
! PURPOSE
! Copies a property from one list or class to another.
!
! 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
+! Success: 0
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
INTEGER :: name_len
-
+
INTERFACE
INTEGER FUNCTION h5pcopy_prop_c(dst_id, src_id, name, name_len) &
BIND(C,NAME='h5pcopy_prop_c')
@@ -3731,27 +3731,27 @@ CONTAINS
hdferr = h5pcopy_prop_c(dst_id, src_id, name , name_len)
END SUBROUTINE h5pcopy_prop_f
-!****s* H5P/h5premove_f
+!****s* H5P/h5premove_f
! NAME
-! h5premove_f
+! h5premove_f
!
! PURPOSE
-! Removes a property from a property list.
+! Removes a property from a property list.
!
! INPUTS
-!
+!
! plid - Property list identofoer
! name - name of the property to remove
! OUTPUTS
-!
+!
! hdferr: - error code
-! Success: 0
-! Failure: -1
+! Success: 0
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
SUBROUTINE h5premove_f(plid, name, hdferr)
@@ -3762,14 +3762,14 @@ CONTAINS
! 0 on success and -1 on failure
!*****
INTEGER :: name_len
-
+
INTERFACE
INTEGER FUNCTION h5premove_c(plid, name, name_len) &
BIND(C,NAME='h5premove_c')
IMPORT :: C_CHAR
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plid
+ INTEGER(HID_T), INTENT(IN) :: plid
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: name
INTEGER, INTENT(IN) :: name_len
END FUNCTION h5premove_c
@@ -3778,26 +3778,26 @@ CONTAINS
hdferr = h5premove_c(plid, name , name_len)
END SUBROUTINE h5premove_f
-!****s* H5P/h5punregister_f
+!****s* H5P/h5punregister_f
! NAME
-! h5punregister_f
+! h5punregister_f
!
! PURPOSE
-! Removes a property from a property list class.
+! Removes a property from a property list class.
!
! INPUTS
-!
+!
! class - Property list class identifier
! name - name of the property to remove
! OUTPUTS
-!
+!
! hdferr: - error code
-! Success: 0
-! Failure: -1
+! Success: 0
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
SUBROUTINE h5punregister_f(class, name, hdferr)
@@ -3824,25 +3824,25 @@ CONTAINS
hdferr = h5punregister_c(class, name , name_len)
END SUBROUTINE h5punregister_f
-!****s* H5P/h5pclose_class_f
+!****s* H5P/h5pclose_class_f
! NAME
-! h5pclose_class_f
+! h5pclose_class_f
!
! PURPOSE
! Closes an existing property list class.
!
! INPUTS
-!
+!
! class - Property list class identifier
! OUTPUTS
-!
-! hdferr - error code
-! Success: 0
-! Failure: -1
+!
+! hdferr - error code
+! Success: 0
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
-! October 9, 2002
+! October 9, 2002
!
! Fortran90 Interface:
SUBROUTINE h5pclose_class_f(class, hdferr)
@@ -3862,9 +3862,9 @@ CONTAINS
hdferr = h5pclose_class_c(class)
END SUBROUTINE h5pclose_class_f
-!****s* H5P/h5pset_shuffle_f
+!****s* H5P/h5pset_shuffle_f
! NAME
-! h5pset_shuffle_f
+! h5pset_shuffle_f
!
! PURPOSE
! Sets shuffling filter
@@ -3872,9 +3872,9 @@ CONTAINS
! INPUTS
! prp_id - dataset creation property list identifier
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -3883,7 +3883,7 @@ CONTAINS
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -3896,26 +3896,26 @@ CONTAINS
END FUNCTION h5pset_shuffle_c
END INTERFACE
hdferr = h5pset_shuffle_c(prp_id)
-
+
END SUBROUTINE h5pset_shuffle_f
-!****s* H5P/h5pset_edc_check_f
+!****s* H5P/h5pset_edc_check_f
! NAME
-! h5pset_edc_check_f
+! h5pset_edc_check_f
!
! PURPOSE
-! Enables/disables error detecting
+! Enables/disables error detecting
!
! 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
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -3924,7 +3924,7 @@ CONTAINS
! Fortran90 Interface:
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
! 0 on success and -1 on failure
@@ -3935,27 +3935,27 @@ CONTAINS
IMPORT :: HID_T
IMPLICIT NONE
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)
-
+
END SUBROUTINE h5pset_edc_check_f
!****s* H5P/h5pget_edc_check_f
! NAME
-! h5pget_edc_check_f
+! h5pget_edc_check_f
!
! PURPOSE
-! Queries error detecting
+! Queries error detecting
!
! INPUTS
-!
+!
! prp_id - dataset creation property list identifier
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -3964,7 +3964,7 @@ CONTAINS
! Fortran90 Interface:
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
@@ -3984,24 +3984,24 @@ CONTAINS
END FUNCTION h5pget_edc_check_c
END INTERFACE
hdferr = h5pget_edc_check_c(prp_id, flag)
-
+
END SUBROUTINE h5pget_edc_check_f
!****s* H5P/h5pset_fletcher32_f
! NAME
-! h5pset_fletcher32_f
+! h5pset_fletcher32_f
!
! PURPOSE
-! Sets Fletcher32 checksum of EDC for a dataset creation
+! Sets Fletcher32 checksum of EDC for a dataset creation
! property list.
!
! INPUTS
-!
+!
! prp_id - dataset creation property list identifier
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4010,7 +4010,7 @@ CONTAINS
! Fortran90 Interface:
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
! 0 on success and -1 on failure
!*****
@@ -4028,19 +4028,19 @@ CONTAINS
!****s* H5P/ h5pset_family_offset_f
! NAME
-! h5pset_family_offset_f
+! h5pset_family_offset_f
!
! PURPOSE
! Sets offset for family file driver.
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! offset - file offset
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4049,42 +4049,42 @@ CONTAINS
! Fortran90 Interface:
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
! 0 on success and -1 on failure
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pset_family_offset_c(prp_id, offset) &
BIND(C,NAME='h5pset_family_offset_c')
IMPORT :: HID_T, HSIZE_T
IMPLICIT NONE
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)
-
+
END SUBROUTINE h5pset_family_offset_f
!****s* H5P/h5pset_fapl_multi_l
! NAME
-! h5pset_fapl_multi_l
+! h5pset_fapl_multi_l
!
! PURPOSE
-! Sets up use of the multi-file driver.
+! Sets up use of the multi-file driver.
!
! 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
+! relax - flag
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4097,10 +4097,10 @@ CONTAINS
INTEGER, DIMENSION(*), INTENT(IN) :: memb_map
INTEGER(HID_T), DIMENSION(*), INTENT(IN) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(*), INTENT(IN) :: memb_name
- REAL, DIMENSION(*), INTENT(IN) :: memb_addr
+ REAL, DIMENSION(*), INTENT(IN) :: memb_addr
LOGICAL, INTENT(IN) :: relax
INTEGER, INTENT(OUT) :: hdferr
-!*****
+!*****
INTEGER, DIMENSION(1:H5FD_MEM_NTYPES_F) :: lenm
INTEGER :: maxlen
INTEGER :: flag = 0
@@ -4113,7 +4113,7 @@ CONTAINS
IMPORT :: C_CHAR
IMPORT :: HID_T
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(*), INTENT(IN) :: memb_map
INTEGER(HID_T), DIMENSION(*), INTENT(IN) :: memb_fapl
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: memb_name
@@ -4132,21 +4132,21 @@ CONTAINS
hdferr = h5pset_fapl_multi_c(prp_id, memb_map, memb_fapl, memb_name, lenm, maxlen, memb_addr, flag)
END SUBROUTINE h5pset_fapl_multi_l
-!****s* H5P/h5pset_fapl_multi_s
+!****s* H5P/h5pset_fapl_multi_s
! NAME
-! h5pset_fapl_multi_s
+! h5pset_fapl_multi_s
!
! PURPOSE
-! Sets up use of the multi-file driver.
+! Sets up use of the multi-file driver.
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
-! relax - flag
+! relax - flag
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4155,11 +4155,11 @@ CONTAINS
! Fortran90 Interface:
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
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: flag
INTERFACE
@@ -4167,37 +4167,37 @@ CONTAINS
BIND(C,NAME='h5pset_fapl_multi_sc')
IMPORT :: HID_T
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, 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
-!****s* H5P/h5pget_fapl_multi_f
+!****s* H5P/h5pget_fapl_multi_f
! NAME
-! h5pget_fapl_multi_f
+! h5pget_fapl_multi_f
!
! PURPOSE
-! Sets up use of the multi-file driver.
+! Sets up use of the multi-file driver.
!
! INPUTS
-!
+!
! prp_id - file creation property list identifier
! 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
!
! OPTIONAL PARAMETERS
-! maxlen_out - maximum length for memb_name array element
+! maxlen_out - maximum length for memb_name array element
!
! AUTHOR
! Elena Pourmal
@@ -4206,19 +4206,19 @@ CONTAINS
! Fortran90 Interface:
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(*), INTENT(OUT) :: memb_map
INTEGER(HID_T), DIMENSION(*), INTENT(OUT) :: memb_fapl
CHARACTER(LEN=*), DIMENSION(*), INTENT(OUT) :: memb_name
REAL, DIMENSION(*), 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
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER, DIMENSION(1:H5FD_MEM_NTYPES_F) :: lenm
INTEGER :: maxlen
- INTEGER :: c_maxlen_out
+ INTEGER :: c_maxlen_out
INTEGER :: flag
INTEGER :: i
!
@@ -4229,14 +4229,14 @@ CONTAINS
IMPORT :: C_CHAR
IMPORT :: HID_T
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(*), INTENT(OUT) :: memb_map
INTEGER(HID_T), DIMENSION(*), INTENT(OUT) :: memb_fapl
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: memb_name
REAL, DIMENSION(*), INTENT(OUT) :: memb_addr
INTEGER, DIMENSION(*) :: lenm
INTEGER :: maxlen
- INTEGER :: c_maxlen_out
+ INTEGER :: c_maxlen_out
INTEGER, INTENT(OUT) :: flag
END FUNCTION h5pget_fapl_multi_c
END INTERFACE
@@ -4246,20 +4246,20 @@ CONTAINS
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)
-
+
relax = .TRUE.
IF(flag .EQ. 0) relax = .FALSE.
IF(PRESENT(maxlen_out)) maxlen_out = c_maxlen_out
END SUBROUTINE h5pget_fapl_multi_f
-!****s* H5P/h5pset_szip_f
+!****s* H5P/h5pset_szip_f
! NAME
-! h5pset_szip_f
+! h5pset_szip_f
!
! PURPOSE
! Sets up use of szip compression
!
! INPUTS
-!
+!
! prp_id - dataset creation property list identifier
! options_mask - A bit-mask conveying the desired SZIP options.
! Current valid values in Fortran are:
@@ -4267,25 +4267,25 @@ CONTAINS
! H5_SZIP_NN_OM_F
! pixels_per_block - szip parameters
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
! April 10 2003
!
! Fortran90 Interface:
- 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 ! A bit-mask conveying the desired
! SZIP options
! Current valid values in Fortran are:
! H5_SZIP_EC_OM_F
! H5_SZIP_NN_OM_F
- INTEGER, INTENT(IN) :: pixels_per_block ! The number of pixels or data elements
+ INTEGER, INTENT(IN) :: pixels_per_block ! The number of pixels or data elements
! in each data block
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
@@ -4295,33 +4295,33 @@ CONTAINS
BIND(C,NAME='h5pset_szip_c')
IMPORT :: HID_T
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, 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
-!****s* H5P/h5pall_filters_avail_f
+!****s* H5P/h5pall_filters_avail_f
! NAME
-! h5pall_filters_avail_f
+! h5pall_filters_avail_f
!
! PURPOSE
! Checks if all filters set in the dataset creation
! property list are available
!
! INPUTS
-!
+!
! prp_id - data creation property list identifier
! OUTPUTS
-!
+!
! flag - .TRUE. if all filters are available
! .FALSE. otherwise
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4330,13 +4330,13 @@ CONTAINS
! Fortran90 Interface:
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 ! .TRUE. if all filters are available
! .FALSE. otherwise
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: status
INTERFACE
@@ -4349,24 +4349,24 @@ CONTAINS
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
!****s* H5P/h5pget_filter_by_id_f
! NAME
-! h5pget_filter_by_id_f
+! h5pget_filter_by_id_f
!
! PURPOSE
! Returns information about a filter in a pipeline
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! prp_id - data creation or transfer property list
! identifier
! OUTPUTS
-!
+!
! filter_id - filter identifier
! flags - bit vector specifying certain general
! properties of the filter
@@ -4374,9 +4374,9 @@ CONTAINS
! 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
!
! AUTHOR
! Elena Pourmal
@@ -4385,7 +4385,7 @@ CONTAINS
! Fortran90 Interface:
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.
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values ! Auxiliary data for the filter.
@@ -4404,29 +4404,29 @@ CONTAINS
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
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(KIND=C_CHAR), DIMENSION(*), 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
!****s* H5P/h5pmodify_filter_f
! NAME
-! h5pmodify_filter_f
+! h5pmodify_filter_f
!
! PURPOSE
-! Adds a filter to the filter pipeline.
+! Adds a filter to the filter pipeline.
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! prp_id - data creation or transfer property list
! identifier
! filter - filter to be modified
! flags - bit vector specifying certain general
@@ -4434,9 +4434,9 @@ CONTAINS
! cd_nelmts - number of elements in cd_values
! cd_values - auxiliary data for the filter
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Elena Pourmal
@@ -4445,7 +4445,7 @@ CONTAINS
! Fortran90 Interface:
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
@@ -4459,33 +4459,33 @@ CONTAINS
BIND(C,NAME='h5pmodify_filter_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
-
+
hdferr = h5pmodify_filter_c(prp_id, filter, flags, cd_nelmts, cd_values )
END SUBROUTINE h5pmodify_filter_f
-!****s* H5P/h5premove_filter_f
+!****s* H5P/h5premove_filter_f
! NAME
-! h5premove_filter_f
+! h5premove_filter_f
!
! PURPOSE
-! Delete one or more filters from the filter pipeline.
+! Delete one or more filters from the filter pipeline.
!
! INPUTS
-!
-! prp_id - data creation or transfer property list
+!
+! prp_id - data creation or transfer property list
! identifier
! filter - filter to be removed
! OUTPUTS
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! Quincey Koziol
@@ -4505,39 +4505,39 @@ CONTAINS
BIND(C,NAME='h5premove_filter_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
-
+
hdferr = h5premove_filter_c(prp_id, filter)
END SUBROUTINE h5premove_filter_f
!****s* H5P/H5Pget_attr_phase_change_f
! NAME
-! H5Pget_attr_phase_change_f
+! H5Pget_attr_phase_change_f
!
! PURPOSE
-! Retrieves attribute storage phase change thresholds
+! Retrieves attribute storage phase change thresholds
!
! INPUTS
-!
+!
! ocpl_id - Object (dataset or group) creation property list identifier
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! January, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pget_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (dataset or group) creation property list identifier
@@ -4563,28 +4563,28 @@ CONTAINS
hdferr = h5pget_attr_phase_change_c(ocpl_id, max_compact, min_dense)
END SUBROUTINE h5pget_attr_phase_change_f
-!****s* H5P/H5Pset_attr_creation_order_f
+!****s* H5P/H5Pset_attr_creation_order_f
! NAME
-! H5Pset_attr_creation_order_f
+! H5Pset_attr_creation_order_f
!
! PURPOSE
! Sets tracking and indexing of attribute creation order
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! January, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pset_attr_creation_order_f(ocpl_id, crt_order_flags , hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (dataset or group) creation property list identifier
@@ -4606,36 +4606,36 @@ CONTAINS
hdferr = H5Pset_attr_creation_order_c(ocpl_id, crt_order_flags)
END SUBROUTINE h5pset_attr_creation_order_f
-!****s* H5P/H5Pset_shared_mesg_nindexes_f
+!****s* H5P/H5Pset_shared_mesg_nindexes_f
! NAME
-! H5Pset_shared_mesg_nindexes_f
+! H5Pset_shared_mesg_nindexes_f
!
! PURPOSE
-! Sets number of shared object header message indexes
+! Sets number of shared object header message indexes
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! January, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
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
! 0 on success and -1 on failure
-!*****
+!*****
!
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -4662,7 +4662,7 @@ CONTAINS
! Configures the specified shared object header message index
!
! 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.
@@ -4670,15 +4670,15 @@ CONTAINS
!
! OUTPUTS
!
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
! January, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pset_shared_mesg_index_f(fcpl_id, index_num, mesg_type_flags, min_mesg_size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fcpl_id ! file creation property list
@@ -4687,7 +4687,7 @@ CONTAINS
INTEGER, INTENT(IN) :: min_mesg_size ! Minimum message size.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
!
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -4696,7 +4696,7 @@ CONTAINS
BIND(C,NAME='h5pset_shared_mesg_index_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
@@ -4721,22 +4721,22 @@ CONTAINS
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! February, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
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
! 0 on success and -1 on failure
-!*****
+!*****
!
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -4759,7 +4759,7 @@ CONTAINS
! H5Pget_libver_bounds_f
!
! PURPOSE
-! Retrieves the lower and upper bounds on the HDF5 library release versions that indirectly
+! Retrieves the lower and upper bounds on the HDF5 library release versions that indirectly
! determine the object format versions used when creating objects in the file.
!
! INPUTS
@@ -4828,15 +4828,15 @@ CONTAINS
!
! OUTPUTS
!
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
! February 18, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pset_libver_bounds_f(fapl_id, low, high, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier
@@ -4867,9 +4867,9 @@ CONTAINS
END SUBROUTINE h5pset_libver_bounds_f
-!****s* H5P/H5Pset_link_creation_order_f
+!****s* H5P/H5Pset_link_creation_order_f
! NAME
-! H5Pset_link_creation_order_f
+! H5Pset_link_creation_order_f
!
! PURPOSE
! Sets creation order tracking and indexing for links in a group.
@@ -4881,15 +4881,15 @@ CONTAINS
!
! OUTPUTS
!
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
! February 18, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pset_link_creation_order_f(gcpl_id, crt_order_flags, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: gcpl_id ! File access property list identifier
@@ -4920,21 +4920,21 @@ CONTAINS
! Queries the settings for conversion between compact and dense groups.
!
! INPUTS
-!
+!
! gcpl_id - Group creation property list identifier
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! February 20, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pget_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
@@ -4958,37 +4958,37 @@ CONTAINS
hdferr = h5pget_link_phase_change_c(gcpl_id, max_compact, min_dense)
END SUBROUTINE h5pget_link_phase_change_f
-!****s* H5P/H5Pget_obj_track_times_f
+!****s* H5P/H5Pget_obj_track_times_f
! NAME
-! H5Pget_obj_track_times_f
+! H5Pget_obj_track_times_f
!
! PURPOSE
! Returns whether times are tracked for an object.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! February 22, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
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
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: status
!
! MS FORTRAN needs explicit interface for C functions called here.
@@ -4997,7 +4997,7 @@ CONTAINS
INTEGER FUNCTION h5pget_obj_track_times_c(plist_id, status) &
BIND(C,NAME='h5pget_obj_track_times_c')
IMPORT :: HID_T
- 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
@@ -5007,9 +5007,9 @@ CONTAINS
END SUBROUTINE h5pget_obj_track_times_f
-!****s* H5P/H5Pset_obj_track_times_f
+!****s* H5P/H5Pset_obj_track_times_f
! NAME
-! H5Pset_obj_track_times_f
+! H5Pset_obj_track_times_f
!
! PURPOSE
! Set whether the birth, access, modification & change times for
@@ -5029,22 +5029,22 @@ CONTAINS
! epoch) when queried.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! February 22, 2008
-!
-!
-! Fortran90 Interface:
+!
+!
+! Fortran90 Interface:
SUBROUTINE h5pset_obj_track_times_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property
@@ -5052,7 +5052,7 @@ CONTAINS
LOGICAL, INTENT(IN) :: flag ! Object timestamp setting
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: status
!
! MS FORTRAN needs explicit interface for C functions called here.
@@ -5062,7 +5062,7 @@ CONTAINS
BIND(C,NAME='h5pset_obj_track_times_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
@@ -5082,22 +5082,22 @@ CONTAINS
! Specifies in property list whether to create missing intermediate groups.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! February 22, 2008
!
-! HISTORY
+! HISTORY
! The long subroutine name (>31) on older f90 compilers causes problems
! so had to shorten the name
! Fortran90 Interface:
@@ -5137,15 +5137,15 @@ CONTAINS
! OUTPUTS
!
! crt_order_flags - Creation order flag(s)
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
! March 3, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pget_link_creation_order_f(gcpl_id, crt_order_flags, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier
@@ -5183,15 +5183,15 @@ CONTAINS
! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding
!
! OUTPUTS
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
! March 3, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pset_char_encoding_f(plist_id, encoding, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier
@@ -5232,15 +5232,15 @@ CONTAINS
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! March 3, 2008
!
-! Fortran90 Interface:
+! Fortran90 Interface:
SUBROUTINE h5pget_char_encoding_f(plist_id, encoding, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier
@@ -5268,20 +5268,20 @@ CONTAINS
!****s* H5P/h5pset_copy_object_f
! NAME
-! h5pset_copy_object_f
+! h5pset_copy_object_f
!
! PURPOSE
! Sets properties to be used when an object is copied.
!
! INPUTS
-!
+!
! ocp_plist_id - Object copy property list identifier
! copy_options - Copy option(s) to be set
! OUTPUTS
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5289,8 +5289,8 @@ CONTAINS
!
! HISTORY
!
-!
-! Fortran90 Interface:
+!
+! Fortran90 Interface:
SUBROUTINE h5pset_copy_object_f(ocp_plist_id, copy_options, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: ocp_plist_id ! Object copy property list identifier
@@ -5317,20 +5317,20 @@ CONTAINS
!****s* H5P/h5pget_copy_object_f
! NAME
-! h5pget_copy_object_f
+! h5pget_copy_object_f
!
! PURPOSE
! Retrieves the properties to be used when an object is copied.
!
! INPUTS
-!
+!
! ocp_plist_id - Object copy property list identifier
! OUTPUTS
-!
+!
! copy_options - Copy option(s) to be get
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5338,14 +5338,14 @@ CONTAINS
!
! HISTORY
!
-!
+!
! Fortran90 Interface:
SUBROUTINE h5pget_copy_object_f(ocp_plist_id, copy_options, hdferr)
IMPLICIT NONE
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
@@ -5364,23 +5364,23 @@ CONTAINS
hdferr = h5pget_copy_object_c(ocp_plist_id, copy_options)
END SUBROUTINE h5pget_copy_object_f
-!****s* H5P/h5pget_data_transform_f
+!****s* H5P/h5pget_data_transform_f
! NAME
-! h5pget_data_transform_f
+! h5pget_data_transform_f
!
! PURPOSE
! Retrieves a data transform expression.
!
! INPUTS
-!
+!
! plist_id - Identifier of the property list or class
! OUTPUTS
-!
+!
! expression - buffer to hold transform expression
! hdferr - Error code
! Success: Actual length 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
@@ -5400,7 +5400,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
INTEGER(SIZE_T), INTENT(OUT), OPTIONAL :: size ! Registered size of the transform expression
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: expression_len
INTEGER(SIZE_T) :: size_default
@@ -5410,8 +5410,8 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
IMPORT :: C_CHAR
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
- CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: expression
+ INTEGER(HID_T), INTENT(IN) :: plist_id
+ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: expression
INTEGER(SIZE_T) :: size_default
INTEGER :: expression_len
END FUNCTION h5pget_data_transform_c
@@ -5426,19 +5426,19 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
END SUBROUTINE h5pget_data_transform_f
-!****s* H5P/h5pset_data_transform_f
+!****s* H5P/h5pset_data_transform_f
! NAME
-! h5pset_data_transform_f
+! h5pset_data_transform_f
!
! PURPOSE
! Sets a data transform expression.
!
! INPUTS
-!
-! plist_id - Identifier of the property list or class
+!
+! plist_id - Identifier of the property list or class
! expression - Buffer to hold transform expression
! OUTPUTS
-!
+!
! hdferr - error code
! Success: 0
! Failure: -1
@@ -5454,7 +5454,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
CHARACTER(LEN=*), INTENT(IN) :: expression ! Buffer to hold transform expression
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTEGER :: expression_len
INTERFACE
@@ -5463,7 +5463,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
IMPORT :: C_CHAR
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER(HID_T), INTENT(IN) :: plist_id
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: expression
INTEGER :: expression_len
END FUNCTION h5pset_data_transform_c
@@ -5474,15 +5474,15 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
END SUBROUTINE h5pset_data_transform_f
-!****s* H5P/H5Pget_local_heap_size_hint_f
+!****s* H5P/H5Pget_local_heap_size_hint_f
! NAME
-! H5Pget_local_heap_size_hint_f
+! H5Pget_local_heap_size_hint_f
!
! PURPOSE
! Queries the local heap size hint for original-style groups.
!
! INPUTS
-!
+!
! gcpl_id - Group creation property list identifier
! OUTPUTS
!
@@ -5517,18 +5517,18 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
END SUBROUTINE h5pget_local_heap_size_hint_f
-!****s* H5P/H5Pget_est_link_info_f
+!****s* H5P/H5Pget_est_link_info_f
! NAME
-! H5Pget_est_link_info_f
+! H5Pget_est_link_info_f
!
! PURPOSE
! Queries data required to estimate required local heap or object header size.
!
! INPUTS
-!
+!
! gcpl_id - Group creation property list identifier
! 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
@@ -5541,11 +5541,11 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
!
! HISTORY
!
-!
+!
! Fortran90 Interface:
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
@@ -5556,7 +5556,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
BIND(C,NAME='h5pget_est_link_info_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
@@ -5566,15 +5566,15 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
END SUBROUTINE h5pget_est_link_info_f
-!****s* H5P/H5Pset_local_heap_size_hint_f
+!****s* H5P/H5Pset_local_heap_size_hint_f
! NAME
-! H5Pset_local_heap_size_hint_f
+! H5Pset_local_heap_size_hint_f
!
! PURPOSE
! Sets the local heap size hint for original-style groups.
!
! INPUTS
-!
+!
! gcpl_id - Group creation property list identifier
! size_hint - Hint for size of local heap
! OUTPUTS
@@ -5598,7 +5598,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
INTERFACE
INTEGER FUNCTION h5pset_local_heap_size_hint_c(gcpl_id, size_hint) &
BIND(C,NAME='h5pset_local_heap_size_hint_c')
- IMPORT :: HID_T, SIZE_T
+ IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: gcpl_id
INTEGER(SIZE_T), INTENT(IN) :: size_hint
@@ -5609,16 +5609,16 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
END SUBROUTINE h5pset_local_heap_size_hint_f
-!****s* H5P/h5pset_est_link_info_f
+!****s* H5P/h5pset_est_link_info_f
! NAME
-! h5pset_est_link_info_f
+! 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
+!
+! 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
@@ -5634,7 +5634,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
! Fortran90 Interface:
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
@@ -5645,7 +5645,7 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
BIND(C,NAME='h5pset_est_link_info_c')
IMPORT :: HID_T
IMPLICIT NONE
- 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
@@ -5663,15 +5663,15 @@ SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size)
! Sets the parameters for conversion between compact and dense groups.
!
! INPUTS
-!
-! gcpl_id - Group creation property list identifier
+!
+! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5708,16 +5708,16 @@ SUBROUTINE h5pset_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr)
! Sets up use of the direct I/O driver.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5725,7 +5725,7 @@ SUBROUTINE h5pset_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr)
!
! Fortran90 Interface:
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
@@ -5738,7 +5738,7 @@ SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdfer
BIND(C,NAME='h5pset_fapl_direct_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
@@ -5756,16 +5756,16 @@ SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdfer
! Gets up use of the direct I/O driver.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5773,7 +5773,7 @@ SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdfer
!
! Fortran90 Interface:
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
@@ -5786,7 +5786,7 @@ SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdfer
BIND(C,NAME='h5pget_fapl_direct_c')
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
- 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
@@ -5798,23 +5798,23 @@ SUBROUTINE h5pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdfer
!****s* H5P/H5Pset_attr_phase_change_f
! NAME
-! H5Pset_attr_phase_change_f
+! H5Pset_attr_phase_change_f
!
! PURPOSE
! Sets attribute storage phase change thresholds.
!
! INPUTS
-!
+!
! ocpl_id - Object (dataset or group) creation property list identifier
! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -5850,7 +5850,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!****s* H5P/H5Pset_nbit_f
! NAME
-! H5Pset_nbit_f
+! H5Pset_nbit_f
!
! PURPOSE
! Sets up the use of the N-Bit filter.
@@ -5886,7 +5886,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!****s* H5P/h5pset_scaleoffset_f
! NAME
-! h5pset_scaleoffset_f
+! h5pset_scaleoffset_f
!
! PURPOSE
! Sets up the use of the scale-offset filter.
@@ -5914,7 +5914,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER , INTENT(IN) :: scale_type
INTEGER , INTENT(IN) :: scale_factor
INTEGER , INTENT(OUT) :: hdferr
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pset_scaleoffset_c(plist_id, scale_type, scale_factor) &
@@ -5931,15 +5931,15 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END SUBROUTINE h5pset_scaleoffset_f
-!****s* H5P/h5pset_nlinks_f
+!****s* H5P/h5pset_nlinks_f
! NAME
-! h5pset_nlinks_f
+! h5pset_nlinks_f
!
! PURPOSE
! Sets maximum number of soft or user-defined link traversals.
!
! INPUTS
-!
+!
! lapl_id - File access property list identifier
! nlinks - Maximum number of links to traverse
!
@@ -5955,15 +5955,15 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! HISTORY
!
-!
+!
! Fortran90 Interface:
SUBROUTINE h5pset_nlinks_f(lapl_id, nlinks, hdferr)
IMPLICIT NONE
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
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pset_nlinks_c(lapl_id, nlinks) &
BIND(C,NAME='h5pset_nlinks_c')
@@ -5978,15 +5978,15 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END SUBROUTINE h5pset_nlinks_f
-!****s* H5P/h5pget_nlinks_f
+!****s* H5P/h5pget_nlinks_f
! NAME
-! h5pget_nlinks_f
+! h5pget_nlinks_f
!
! PURPOSE
! Gets maximum number of soft or user-defined link traversals.
!
! INPUTS
-!
+!
! lapl_id - File access property list identifier
! nlinks - Maximum number of links to traverse
!
@@ -6011,7 +6011,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTERFACE
INTEGER FUNCTION h5pget_nlinks_c(lapl_id, nlinks) &
BIND(C,NAME='h5pget_nlinks_c')
- IMPORT :: HID_T, SIZE_T
+ IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: lapl_id
INTEGER(SIZE_T), INTENT(OUT) :: nlinks
@@ -6030,22 +6030,22 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Determines whether property is set to enable creating missing intermediate groups.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
! April 4, 2008
!
! HISTORY
-!
+!
! The long subroutine name (>31) on older f90 compilers causes problems
! so the name was shortened
! Fortran90 Interface:
@@ -6056,7 +6056,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! upon creation of an object
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pget_create_inter_group_c(lcpl_id, crt_intermed_group) &
BIND(C,NAME='h5pget_create_inter_group_c')
@@ -6095,16 +6095,16 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! other chunks.
!
! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -6116,19 +6116,19 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
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) &
BIND(C,NAME='h5pset_chunk_cache_c')
- IMPORT :: HID_T, SIZE_T
+ IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dapl_id
INTEGER(SIZE_T), INTENT(IN) :: rdcc_nslots
@@ -6155,16 +6155,16 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! file access property list are returned.
!
! 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
+!
+! 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
!
! AUTHOR
! M. Scot Breitenfeld
@@ -6177,11 +6177,11 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, 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:
! 0 on success and -1 on failure
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pget_chunk_cache_c(dapl_id, rdcc_nslots, rdcc_nbytes, rdcc_w0) &
BIND(C,NAME='h5pget_chunk_cache_c')
@@ -6234,7 +6234,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! INTEGER, REAL, DOUBLE PRECISION and CHARACTER dtatypes.
!
! Fortran90 Interface:
-!! SUBROUTINE h5pset_fill_value_f(prp_id, type_id, fillvalue, hdferr)
+!! SUBROUTINE h5pset_fill_value_f(prp_id, type_id, fillvalue, hdferr)
!! IMPLICIT NONE
!! INTEGER(HID_T), INTENT(IN) :: prp_id
!! INTEGER(HID_T), INTENT(IN) :: type_id
@@ -6295,7 +6295,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! Fortran90 Interface:
!! SUBROUTINE h5pget_fill_value_f(prp_id, type_id, fillvalue, hdferr)
-!! INTEGER(HID_T), INTENT(IN) :: prp_id
+!! INTEGER(HID_T), INTENT(IN) :: prp_id
!! INTEGER(HID_T), INTENT(IN) :: type_id
!! TYPE(VOID) , INTENT(OUT) :: fillvalue
!! INTEGER , INTENT(OUT) :: hdferr
@@ -6402,7 +6402,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! Fortran2003 Interface:
!! SUBROUTINE h5pset_fill_value_f(prp_id, type_id, fillvalue, hdferr)
-!! INTEGER(HID_T), INTENT(IN) :: prp_id
+!! INTEGER(HID_T), INTENT(IN) :: prp_id
!! INTEGER(HID_T), INTENT(IN) :: type_id
!! TYPE(C_PTR) , INTENT(IN) :: fillvalue
!! INTEGER , INTENT(OUT) :: hdferr
@@ -6458,7 +6458,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! Fortran2003 Interface:
!! SUBROUTINE h5pget_fill_value_f(prp_id, type_id, fillvalue, hdferr)
-!! INTEGER(HID_T), INTENT(IN) :: prp_id
+!! INTEGER(HID_T), INTENT(IN) :: prp_id
!! INTEGER(HID_T), INTENT(IN) :: type_id
!! TYPE(C_PTR) :: fillvalue
!! INTEGER , INTENT(OUT) :: hdferr
@@ -6750,7 +6750,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!! CHARACTER(LEN=*), INTENT(IN) :: name
!! INTEGER(SIZE_T) , INTENT(IN) :: size
!! TYPE , INTENT(IN) :: value
-!! INTEGER , INTENT(OUT) :: hdferr
+!! INTEGER , INTENT(OUT) :: hdferr
!*****
SUBROUTINE h5pregister_integer(class, name, size, value, hdferr)
IMPLICIT NONE
@@ -6832,7 +6832,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!! CHARACTER(LEN=*), INTENT(IN) :: name
!! INTEGER(SIZE_T) , INTENT(IN) :: size
!! TYPE(C_PTR) , INTENT(IN) :: value
-!! INTEGER , INTENT(OUT) :: hdferr
+!! INTEGER , INTENT(OUT) :: hdferr
!*****
SUBROUTINE h5pregister_ptr(class, name, size, value, hdferr)
@@ -6951,7 +6951,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Outputs:
! hdferr - Returns 0 if successful and -1 if fails
!
-! AUTHOR
+! AUTHOR
! M. Scot Breitenfeld
! June 24, 2008
!
@@ -7077,7 +7077,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! Inputs:
! fapl_id - File access property list identifier
-! buf_ptr - Pointer to the initial file image,
+! buf_ptr - Pointer to the initial file image,
! or C_NULL_PTR if no initial file image is desired
! buf_len - Size of the supplied buffer, or 0 (zero) if no initial image is desired
!
@@ -7117,7 +7117,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pget_file_image_f
!
! PURPOSE
-! Retrieves a copy of the file image designated as the initial content and structure of a file.
+! Retrieves a copy of the file image designated as the initial content and structure of a file.
!
! Inputs:
! fapl_id - File access property list identifier.
@@ -7149,7 +7149,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
TYPE(C_PTR) , INTENT(OUT), DIMENSION(*) :: buf_ptr
INTEGER(SIZE_T), INTENT(OUT) :: buf_len_ptr
INTEGER , INTENT(OUT) :: hdferr
-
+
!*****
INTERFACE
INTEGER FUNCTION h5pget_file_image_c(fapl_id, buf_ptr, buf_len_ptr) &
@@ -7205,7 +7205,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
BIND(C,NAME='h5pset_fapl_mpio_c')
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER , INTENT(IN) :: comm
INTEGER , INTENT(IN) :: info
END FUNCTION h5pset_fapl_mpio_c
@@ -7248,7 +7248,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
BIND(C,NAME='h5pget_fapl_mpio_c')
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER , INTENT(OUT) :: comm
INTEGER , INTENT(OUT) :: info
END FUNCTION h5pget_fapl_mpio_c
@@ -7291,7 +7291,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
BIND(C,NAME='h5pset_dxpl_mpio_c')
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER , INTENT(IN) :: data_xfer_mode
END FUNCTION h5pset_dxpl_mpio_c
END INTERFACE
@@ -7333,7 +7333,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
BIND(C,NAME='h5pget_dxpl_mpio_c')
IMPORT :: HID_T
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: prp_id
+ INTEGER(HID_T), INTENT(IN) :: prp_id
INTEGER , INTENT(OUT) :: data_xfer_mode
END FUNCTION h5pget_dxpl_mpio_c
END INTERFACE
@@ -7346,8 +7346,8 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pget_mpio_actual_io_mode_f
!
! PURPOSE
-! Retrieves the type of I/O that HDF5 actually performed on the last
-! parallel I/O call. This is not necessarily the type of I/O requested.
+! Retrieves the type of I/O that HDF5 actually performed on the last
+! parallel I/O call. This is not necessarily the type of I/O requested.
!
! INPUTS
! dxpl_id - Dataset transfer property list identifier.
@@ -7367,7 +7367,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER(HID_T), INTENT(IN) :: dxpl_id
INTEGER , INTENT(OUT) :: actual_io_mode
INTEGER , INTENT(OUT) :: hdferr
-!*****
+!*****
INTERFACE
INTEGER FUNCTION h5pget_mpio_actual_io_mode_c(dxpl_id, actual_io_mode) &
BIND(C,NAME='h5pget_mpio_actual_io_mode_c')
@@ -7389,9 +7389,9 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pset_all_coll_metadata_ops_f
!
! PURPOSE
-! Sets requirement whether HDF5 metadata read operations using the access property
-! list are required to be collective or independent. If collective requirement is
-! selected, the HDF5 library will optimize the metadata reads improving performance.
+! Sets requirement whether HDF5 metadata read operations using the access property
+! list are required to be collective or independent. If collective requirement is
+! selected, the HDF5 library will optimize the metadata reads improving performance.
! The default setting is independent (false).
!
! INPUTS
@@ -7414,7 +7414,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER, INTENT(OUT) :: hdferr
!*****
LOGICAL(C_BOOL) :: c_is_collective
-
+
INTERFACE
INTEGER FUNCTION h5pset_all_coll_metadata_ops(plist_id, is_collective) BIND(C, NAME='H5Pset_all_coll_metadata_ops')
IMPORT :: HID_T, C_BOOL
@@ -7426,12 +7426,12 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Transfer value of Fortran LOGICAL to C c_bool type
c_is_collective = is_collective
-
+
hdferr = INT(H5Pset_all_coll_metadata_ops(plist_id, c_is_collective))
-
+
END SUBROUTINE h5pset_all_coll_metadata_ops_f
-!****s* H5P/h5pget_all_coll_metadata_ops_f
+!****s* H5P/h5pget_all_coll_metadata_ops_f
! NAME
! h5pget_all_coll_metadata_ops_f
!
@@ -7452,14 +7452,14 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! SOURCE
SUBROUTINE h5pget_all_coll_metadata_ops_f(plist_id, is_collective, hdferr)
-
+
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: plist_id
LOGICAL, INTENT(OUT) :: is_collective
INTEGER, INTENT(OUT) :: hdferr
!*****
LOGICAL(C_BOOL) :: c_is_collective
-
+
INTERFACE
INTEGER FUNCTION h5pget_all_coll_metadata_ops(plist_id, is_collective) BIND(C, NAME='H5Pget_all_coll_metadata_ops')
IMPORT :: HID_T, C_BOOL
@@ -7468,12 +7468,12 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
LOGICAL(C_BOOL), INTENT(OUT) :: is_collective
END FUNCTION h5pget_all_coll_metadata_ops
END INTERFACE
-
+
hdferr = INT(H5Pget_all_coll_metadata_ops(plist_id, c_is_collective))
-
- ! Transfer value of C c_bool type to Fortran LOGICAL
+
+ ! Transfer value of C c_bool type to Fortran LOGICAL
is_collective = c_is_collective
-
+
END SUBROUTINE h5pget_all_coll_metadata_ops_f
!****s* H5P/h5pset_coll_metadata_write_f
@@ -7503,7 +7503,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER, INTENT(OUT) :: hdferr
!*****
LOGICAL(C_BOOL) :: c_is_collective
-
+
INTERFACE
INTEGER FUNCTION h5pset_coll_metadata_write(plist_id, is_collective) BIND(C, NAME='H5Pset_coll_metadata_write')
IMPORT :: HID_T, C_BOOL
@@ -7512,12 +7512,12 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
LOGICAL(C_BOOL), INTENT(IN), VALUE :: is_collective
END FUNCTION h5pset_coll_metadata_write
END INTERFACE
-
+
! Transfer value of Fortran LOGICAL to C c_bool type
c_is_collective = is_collective
-
+
hdferr = INT(H5Pset_coll_metadata_write(plist_id, c_is_collective))
-
+
END SUBROUTINE h5pset_coll_metadata_write_f
!****s* H5P/h5pget_coll_metadata_write_f
@@ -7541,14 +7541,14 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! SOURCE
SUBROUTINE h5pget_coll_metadata_write_f(plist_id, is_collective, hdferr)
-
+
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: plist_id
LOGICAL, INTENT(OUT) :: is_collective
INTEGER, INTENT(OUT) :: hdferr
!*****
LOGICAL(C_BOOL) :: c_is_collective
-
+
INTERFACE
INTEGER FUNCTION h5pget_coll_metadata_write(plist_id, is_collective) BIND(C, NAME='H5Pget_coll_metadata_write')
IMPORT :: HID_T, C_BOOL
@@ -7557,14 +7557,14 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
LOGICAL(C_BOOL), INTENT(OUT) :: is_collective
END FUNCTION h5pget_coll_metadata_write
END INTERFACE
-
+
hdferr = INT(H5Pget_coll_metadata_write(plist_id, c_is_collective))
-
- ! Transfer value of C c_bool type to Fortran LOGICAL
+
+ ! Transfer value of C c_bool type to Fortran LOGICAL
is_collective = c_is_collective
-
+
END SUBROUTINE h5pget_coll_metadata_write_f
-
+
#endif
!
@@ -7584,9 +7584,9 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Valid values are:
! H5D_VDS_FIRST_MISSING_F
! H5D_VDS_LAST_AVAILABLE_F
-!
+!
! OUTPUTS
-!
+!
! hdferr - Returns 0 if successful and -1 if fails.
!
! AUTHOR
@@ -7601,7 +7601,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER(HID_T), INTENT(IN) :: dapl_id
INTEGER , INTENT(IN) :: view
INTEGER , INTENT(OUT) :: hdferr
-
+
!*****
INTERFACE
INTEGER FUNCTION h5pset_virtual_view(dapl_id, view) BIND(C,NAME='H5Pset_virtual_view')
@@ -7613,7 +7613,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END INTERFACE
hdferr = INT( h5pset_virtual_view(dapl_id, INT(view,ENUM_T)) )
-
+
END SUBROUTINE h5pset_virtual_view_f
!****s* H5P/h5pget_virtual_view_f
@@ -7621,7 +7621,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pget_virtual_view_f
!
! PURPOSE
-! Retrieves the view of a virtual dataset accessed with dapl_id.
+! Retrieves the view of a virtual dataset accessed with dapl_id.
!
! INPUTS
! dapl_id - Dataset access property list identifier for the virtual dataset
@@ -7657,7 +7657,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
hdferr = INT( h5pget_virtual_view(dapl_id, view_enum) )
view = INT(view_enum)
-
+
END SUBROUTINE h5pget_virtual_view_f
!****s* H5P/h5pset_virtual_printf_gap_f
@@ -7665,15 +7665,15 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pset_virtual_printf_gap_f
!
! PURPOSE
-! Sets the maximum number of missing source files and/or datasets with the printf-style names
-! when getting the extent of an unlimited virtual dataset.
+! Sets the maximum number of missing source files and/or datasets with the printf-style names
+! when getting the extent of an unlimited virtual dataset.
!
! INPUTS
! dapl_id - Dataset access property list identifier for the virtual dataset.
-! gap_size - Maximum number of files and/or datasets allowed to be missing for determining
+! gap_size - Maximum number of files and/or datasets allowed to be missing for determining
! the extent of an unlimited virtual dataset with printf-style mappings.
!
-! OUTPUTS
+! OUTPUTS
! hdferr - Returns 0 if successful and -1 if fails.
!
! AUTHOR
@@ -7682,7 +7682,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
!
! HISTORY
!
-! SOURCE
+! SOURCE
SUBROUTINE h5pset_virtual_printf_gap_f(dapl_id, gap_size, hdferr)
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: dapl_id
@@ -7699,7 +7699,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END INTERFACE
hdferr = INT( h5pset_virtual_printf_gap(dapl_id, gap_size) )
-
+
END SUBROUTINE h5pset_virtual_printf_gap_f
!****s* H5P/h5pget_virtual_printf_gap_f
@@ -7707,15 +7707,15 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! h5pget_virtual_printf_gap_f
!
! PURPOSE
-! Returns the maximum number of missing source files and/or datasets with the
+! Returns the maximum number of missing source files and/or datasets with the
! printf-style names when getting the extent for an unlimited virtual dataset.
!
! INPUTS
! dapl_id - Dataset access property list identifier for the virtual dataset
!
! OUTPUTS
-! gap_size - Maximum number of the files and/or datasets allowed to be missing for
-! determining the extent of an unlimited virtual dataset with printf-style mappings.
+! gap_size - Maximum number of the files and/or datasets allowed to be missing for
+! determining the extent of an unlimited virtual dataset with printf-style mappings.
! hdferr - Returns 0 if successful and -1 if fails
!
! AUTHOR
@@ -7727,7 +7727,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! SOURCE
SUBROUTINE h5pget_virtual_printf_gap_f(dapl_id, gap_size, hdferr)
IMPLICIT NONE
-
+
INTEGER(HID_T) , INTENT(IN) :: dapl_id
INTEGER(HSIZE_T), INTENT(OUT) :: gap_size
INTEGER , INTENT(OUT) :: hdferr
@@ -7742,7 +7742,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END INTERFACE
hdferr = INT( h5pget_virtual_printf_gap(dapl_id, gap_size) )
-
+
END SUBROUTINE h5pget_virtual_printf_gap_f
!****s* H5P/h5pset_virtual_f
@@ -7753,9 +7753,9 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Sets the mapping between virtual and source datasets.
!
! INPUTS
-! dcpl_id - The identifier of the dataset creation property list that will be
+! dcpl_id - The identifier of the dataset creation property list that will be
! used when creating the virtual dataset.
-! vspace_id - The dataspace identifier with the selection within the virtual
+! vspace_id - The dataspace identifier with the selection within the virtual
! dataset applied, possibly an unlimited selection.
! src_file_name - The name of the HDF5 file where the source dataset is located.
! src_dset_name - The path to the HDF5 dataset in the file specified by src_file_name.
@@ -7773,7 +7773,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! SOURCE
SUBROUTINE h5pset_virtual_f(dcpl_id, vspace_id, src_file_name, src_dset_name, src_space_id, hdferr)
IMPLICIT NONE
-
+
INTEGER(HID_T), INTENT(IN) :: dcpl_id
INTEGER(HID_T), INTENT(IN) :: vspace_id
CHARACTER(LEN=*), INTENT(IN) :: src_file_name
@@ -7813,7 +7813,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! Gets the number of mappings for the virtual dataset.
!
! INPUTS
-! dcpl_id - The identifier of the virtual dataset creation property list.
+! dcpl_id - The identifier of the virtual dataset creation property list.
!
! OUTPUTS
! count - The number of mappings.
@@ -7828,7 +7828,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
SUBROUTINE h5pget_virtual_count_f(dcpl_id, count, hdferr)
IMPLICIT NONE
-
+
INTEGER(HID_T), INTENT(IN) :: dcpl_id
INTEGER(SIZE_T), INTENT(OUT) :: count
INTEGER, INTENT(OUT) :: hdferr
@@ -7841,7 +7841,7 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER(SIZE_T), INTENT(OUT) :: count
END FUNCTION h5pget_virtual_count
END INTERFACE
-
+
hdferr = INT( h5pget_virtual_count(dcpl_id, count))
END SUBROUTINE h5pget_virtual_count_f
@@ -7856,10 +7856,10 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
! INPUTS
! dcpl_id - The identifier of the virtual dataset creation property list.
! index - Mapping index.
-! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
+! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
! where count is the number of mappings returned by h5pget_virtual_count.
!
-! OUTPUTS
+! OUTPUTS
! hdferr - Returns 0 if successful and -1 if fails.
!
! AUTHOR
@@ -7886,9 +7886,9 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
INTEGER(SIZE_T), INTENT(IN), VALUE :: index
END FUNCTION h5pget_virtual_vspace
END INTERFACE
-
+
ds_id = h5pget_virtual_vspace(dcpl_id, index)
-
+
hdferr = 0
IF(ds_id.LT.0) hdferr = -1
@@ -7904,7 +7904,7 @@ END SUBROUTINE h5pget_virtual_vspace_f
! INPUTS
! dcpl_id - The identifier of the virtual dataset creation property list.
! index - Mapping index.
-! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
+! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
! where count is the number of mappings returned by h5pget_virtual_count.
!
!
@@ -7936,7 +7936,7 @@ SUBROUTINE h5pget_virtual_srcspace_f(dcpl_id, index, ds_id, hdferr)
INTEGER(SIZE_T), INTENT(IN), VALUE :: index
END FUNCTION h5pget_virtual_srcspace
END INTERFACE
-
+
ds_id = h5pget_virtual_srcspace(dcpl_id, index)
hdferr = 0
@@ -7954,9 +7954,9 @@ END SUBROUTINE h5pget_virtual_srcspace_f
! INPUTS
! dcpl_id - The identifier of the virtual dataset creation property list.
! index - Mapping index.
-! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
+! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
! where count is the number of mappings returned by h5pget_virtual_count.
-!
+!
! OUTPUTS
! name - A buffer containing the name of the file containing the source dataset.
! hdferr - Returns 0 if successful and -1 if fails.
@@ -7983,7 +7983,7 @@ SUBROUTINE h5pget_virtual_filename_f(dcpl_id, index, name, hdferr, name_len)
CHARACTER(LEN=1,KIND=C_CHAR), DIMENSION(1:LEN(name)+1), TARGET :: c_name
TYPE(C_PTR) :: f_ptr
-
+
INTERFACE
INTEGER(SIZE_T) FUNCTION h5pget_virtual_filename(dcpl_id, index, name, size) BIND(C, NAME='H5Pget_virtual_filename')
IMPORT :: HID_T, SIZE_T, C_PTR
@@ -8022,9 +8022,9 @@ END SUBROUTINE h5pget_virtual_filename_f
! INPUTS
! dcpl_id - The identifier of the virtual dataset creation property list.
! index - Mapping index.
-! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
+! The value of index is 0 (zero) or greater and less than count (0 ≤ index < count),
! where count is the number of mappings returned by h5pget_virtual_count.
-!
+!
! OUTPUTS
! name - A buffer containing the name of the source dataset.
! hdferr - Returns 0 if successful and -1 if fails.
@@ -8051,7 +8051,7 @@ SUBROUTINE h5pget_virtual_dsetname_f(dcpl_id, index, name, hdferr, name_len)
CHARACTER(LEN=1,KIND=C_CHAR), DIMENSION(1:LEN(name)+1), TARGET :: c_name
TYPE(C_PTR) :: f_ptr
-
+
INTERFACE
INTEGER(SIZE_T) FUNCTION h5pget_virtual_dsetname(dcpl_id, index, name, size) BIND(C, NAME='H5Pget_virtual_dsetname')
IMPORT :: HID_T, SIZE_T, C_PTR
@@ -8120,7 +8120,7 @@ END SUBROUTINE h5pget_virtual_dsetname_f
hdferr = INT(h5pget_dset_no_attrs_hint_c(dcpl_id, c_minimize))
- ! Transfer value of C C_BOOL type to Fortran LOGICAL
+ ! Transfer value of C C_BOOL type to Fortran LOGICAL
minimize = c_minimize
END SUBROUTINE h5pget_dset_no_attrs_hint_f