summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Aff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Aff.f90')
-rw-r--r--fortran/src/H5Aff.f901478
1 files changed, 739 insertions, 739 deletions
diff --git a/fortran/src/H5Aff.f90 b/fortran/src/H5Aff.f90
index 9834914..af1e630 100644
--- a/fortran/src/H5Aff.f90
+++ b/fortran/src/H5Aff.f90
@@ -1,4 +1,4 @@
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
! All rights reserved. *
@@ -11,7 +11,7 @@
! is linked from the top-level documents page. It can also be found at *
! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
! access to either file, you may request a copy from help@hdfgroup.org. *
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
!
! This file contains Fortran90 interfaces for H5A functions.
@@ -20,29 +20,29 @@ MODULE H5A
USE H5GLOBAL
!
-!On Windows there are no big (integer*8) integers, so overloading
+!On Windows there are no big (integer*8) integers, so overloading
!for bug #670 does not work. I have to use DEC compilation directives to make
!Windows DEC Visual Fortran and OSF compilers happy and do right things.
! 05/01/02 EP
!
INTERFACE h5awrite_f
- MODULE PROCEDURE h5awrite_integer_scalar
- MODULE PROCEDURE h5awrite_integer_1
- MODULE PROCEDURE h5awrite_integer_2
- MODULE PROCEDURE h5awrite_integer_3
- MODULE PROCEDURE h5awrite_integer_4
- MODULE PROCEDURE h5awrite_integer_5
- MODULE PROCEDURE h5awrite_integer_6
- MODULE PROCEDURE h5awrite_integer_7
- MODULE PROCEDURE h5awrite_char_scalar
- MODULE PROCEDURE h5awrite_char_1
- MODULE PROCEDURE h5awrite_char_2
- MODULE PROCEDURE h5awrite_char_3
- MODULE PROCEDURE h5awrite_char_4
- MODULE PROCEDURE h5awrite_char_5
- MODULE PROCEDURE h5awrite_char_6
- MODULE PROCEDURE h5awrite_char_7
+ MODULE PROCEDURE h5awrite_integer_scalar
+ MODULE PROCEDURE h5awrite_integer_1
+ MODULE PROCEDURE h5awrite_integer_2
+ MODULE PROCEDURE h5awrite_integer_3
+ MODULE PROCEDURE h5awrite_integer_4
+ MODULE PROCEDURE h5awrite_integer_5
+ MODULE PROCEDURE h5awrite_integer_6
+ MODULE PROCEDURE h5awrite_integer_7
+ MODULE PROCEDURE h5awrite_char_scalar
+ MODULE PROCEDURE h5awrite_char_1
+ MODULE PROCEDURE h5awrite_char_2
+ MODULE PROCEDURE h5awrite_char_3
+ MODULE PROCEDURE h5awrite_char_4
+ MODULE PROCEDURE h5awrite_char_5
+ MODULE PROCEDURE h5awrite_char_6
+ MODULE PROCEDURE h5awrite_char_7
MODULE PROCEDURE h5awrite_real_scalar
MODULE PROCEDURE h5awrite_real_1
MODULE PROCEDURE h5awrite_real_2
@@ -67,21 +67,21 @@ MODULE H5A
INTERFACE h5aread_f
MODULE PROCEDURE h5aread_integer_scalar
- MODULE PROCEDURE h5aread_integer_1
- MODULE PROCEDURE h5aread_integer_2
- MODULE PROCEDURE h5aread_integer_3
- MODULE PROCEDURE h5aread_integer_4
- MODULE PROCEDURE h5aread_integer_5
- MODULE PROCEDURE h5aread_integer_6
- MODULE PROCEDURE h5aread_integer_7
- MODULE PROCEDURE h5aread_char_scalar
- MODULE PROCEDURE h5aread_char_1
- MODULE PROCEDURE h5aread_char_2
- MODULE PROCEDURE h5aread_char_3
- MODULE PROCEDURE h5aread_char_4
- MODULE PROCEDURE h5aread_char_5
- MODULE PROCEDURE h5aread_char_6
- MODULE PROCEDURE h5aread_char_7
+ MODULE PROCEDURE h5aread_integer_1
+ MODULE PROCEDURE h5aread_integer_2
+ MODULE PROCEDURE h5aread_integer_3
+ MODULE PROCEDURE h5aread_integer_4
+ MODULE PROCEDURE h5aread_integer_5
+ MODULE PROCEDURE h5aread_integer_6
+ MODULE PROCEDURE h5aread_integer_7
+ MODULE PROCEDURE h5aread_char_scalar
+ MODULE PROCEDURE h5aread_char_1
+ MODULE PROCEDURE h5aread_char_2
+ MODULE PROCEDURE h5aread_char_3
+ MODULE PROCEDURE h5aread_char_4
+ MODULE PROCEDURE h5aread_char_5
+ MODULE PROCEDURE h5aread_char_6
+ MODULE PROCEDURE h5aread_char_7
MODULE PROCEDURE h5aread_real_scalar
MODULE PROCEDURE h5aread_real_1
MODULE PROCEDURE h5aread_real_2
@@ -102,60 +102,60 @@ MODULE H5A
! End commnet if on Crays
!
END INTERFACE
-
+
CONTAINS
!----------------------------------------------------------------------
-! Name: h5acreate_f
+! Name: h5acreate_f
!
-! Purpose: Creates a dataset as an attribute of a group, dataset,
-! or named datatype
+! Purpose: Creates a dataset as an attribute of a group, dataset,
+! or named datatype
!
-! Inputs:
+! Inputs:
! loc_id - identifier of an object (group, dataset,
! or named datatype) attribute is attached to
! name - attribute name
! type_id - attribute datatype identifier
! space_id - attribute dataspace identifier
!
-! Outputs:
+! Outputs:
! attr_id - attribute identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! acpl_id - Attribute creation property list identifier
-! appl_id - Attribute access property list identifier
+! appl_id - Attribute access property list identifier
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
SUBROUTINE h5acreate_f(loc_id, name, type_id, space_id, attr_id, &
- hdferr, acpl_id, aapl_id )
+ hdferr, acpl_id, aapl_id )
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5acreate_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: loc_id ! Object identifier
+ INTEGER(HID_T), INTENT(IN) :: loc_id ! Object identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Attribute name
- INTEGER(HID_T), INTENT(IN) :: type_id
- ! Attribute datatype identifier
- INTEGER(HID_T), INTENT(IN) :: space_id
+ INTEGER(HID_T), INTENT(IN) :: type_id
+ ! Attribute datatype identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id
! Attribute dataspace identifier
- INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: acpl_id ! Attribute creation property list identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list identifier
-
+
INTEGER(HID_T) :: acpl_id_default
- INTEGER(HID_T) :: aapl_id_default
+ INTEGER(HID_T) :: aapl_id_default
INTEGER(SIZE_T) :: namelen
! INTEGER, EXTERNAL :: h5acreate_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -178,7 +178,7 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: attr_id
END FUNCTION h5acreate_c
END INTERFACE
-
+
acpl_id_default = H5P_DEFAULT_F
aapl_id_default = H5P_DEFAULT_F
namelen = LEN(NAME)
@@ -192,40 +192,40 @@ CONTAINS
!----------------------------------------------------------------------
-! Name: h5aopen_name_f
+! Name: h5aopen_name_f
!
-! Purpose: Opens an attribute specified by name.
+! Purpose: Opens an attribute specified by name.
!
-! Inputs:
-! obj_id - identifier of a group, dataset, or named
+! Inputs:
+! obj_id - identifier of a group, dataset, or named
! datatype atttribute to be attached to
! name - attribute name
-! Outputs:
+! Outputs:
! attr_id - attribute identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aopen_name_f(obj_id, name, attr_id, hdferr)
+ SUBROUTINE h5aopen_name_f(obj_id, name, attr_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aopen_name_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
+ INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Attribute name
- INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER(SIZE_T) :: namelen
@@ -245,49 +245,49 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: attr_id
END FUNCTION h5aopen_name_c
END INTERFACE
-
+
namelen = LEN(name)
hdferr = h5aopen_name_c(obj_id, name, namelen, attr_id)
END SUBROUTINE h5aopen_name_f
!----------------------------------------------------------------------
-! Name: h5aopen_idx_f
+! Name: h5aopen_idx_f
!
! Purpose: Opens the attribute specified by its index.
!
-! Inputs:
+! Inputs:
! obj_id - identifier of a group, dataset, or named
! datatype an attribute to be attached to
! index - index of the attribute to open (zero-based)
-! Outputs:
+! Outputs:
! attr_id - attribute identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aopen_idx_f(obj_id, index, attr_id, hdferr)
+ SUBROUTINE h5aopen_idx_f(obj_id, index, attr_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aopen_idx_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
- INTEGER, INTENT(IN) :: index ! Attribute index
- INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
+ INTEGER, INTENT(IN) :: index ! Attribute index
+ INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! INTEGER, EXTERNAL :: h5aopen_idx_c
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -302,22 +302,22 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: attr_id
END FUNCTION h5aopen_idx_c
END INTERFACE
-
+
hdferr = h5aopen_idx_c(obj_id, index, attr_id)
END SUBROUTINE h5aopen_idx_f
- SUBROUTINE h5awrite_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- INTEGER, INTENT(IN) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER, INTENT(IN) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_integer_s_c
@@ -329,31 +329,31 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_S_C'::h5awrite_integer_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN)::buf
END FUNCTION h5awrite_integer_s_c
END INTERFACE
-
+
hdferr = h5awrite_integer_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_integer_scalar
- SUBROUTINE h5awrite_integer_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN) , &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! INTEGER, EXTERNAL :: h5awrite_integer_1_c
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -363,7 +363,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_1_C'::h5awrite_integer_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), DIMENSION(dims(1)) :: buf
@@ -375,21 +375,21 @@ CONTAINS
END SUBROUTINE h5awrite_integer_1
- SUBROUTINE h5awrite_integer_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN) , &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! INTEGER, EXTERNAL :: h5awrite_integer_2_c
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -399,7 +399,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_2_C'::h5awrite_integer_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2)) :: buf
@@ -410,18 +410,18 @@ CONTAINS
END SUBROUTINE h5awrite_integer_2
- SUBROUTINE h5awrite_integer_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_integer_3_c
@@ -433,30 +433,30 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_3_C'::h5awrite_integer_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2),dims(3)) :: buf
END FUNCTION h5awrite_integer_3_c
END INTERFACE
-
+
hdferr = h5awrite_integer_3_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_integer_3
- SUBROUTINE h5awrite_integer_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_integer_4_c
@@ -468,7 +468,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_4_C'::h5awrite_integer_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
@@ -479,18 +479,18 @@ CONTAINS
END SUBROUTINE h5awrite_integer_4
- SUBROUTINE h5awrite_integer_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_integer_5_c
@@ -502,7 +502,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_5_C'::h5awrite_integer_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
@@ -513,21 +513,21 @@ CONTAINS
END SUBROUTINE h5awrite_integer_5
- SUBROUTINE h5awrite_integer_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+
! INTEGER, EXTERNAL :: h5awrite_integer_6_c
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -537,7 +537,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_6_C'::h5awrite_integer_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), &
@@ -549,19 +549,19 @@ CONTAINS
END SUBROUTINE h5awrite_integer_6
- SUBROUTINE h5awrite_integer_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_integer_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_integer_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_integer_7_c
@@ -573,7 +573,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_INTEGER_7_C'::h5awrite_integer_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(IN), &
@@ -585,17 +585,17 @@ CONTAINS
END SUBROUTINE h5awrite_integer_7
- SUBROUTINE h5awrite_real_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- REAL, INTENT(IN) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ REAL, INTENT(IN) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_s_c
@@ -607,7 +607,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_S_C'::h5awrite_real_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN)::buf
@@ -617,19 +617,19 @@ CONTAINS
hdferr = h5awrite_real_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_real_scalar
- SUBROUTINE h5awrite_real_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_1_c
@@ -641,7 +641,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_1_C'::h5awrite_real_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -653,19 +653,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_1
- SUBROUTINE h5awrite_real_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_2_c
@@ -677,7 +677,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_2_C'::h5awrite_real_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -689,19 +689,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_2
- SUBROUTINE h5awrite_real_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_3_c
@@ -713,7 +713,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_3_C'::h5awrite_real_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -725,19 +725,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_3
- SUBROUTINE h5awrite_real_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_4_c
@@ -749,7 +749,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_4_C'::h5awrite_real_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -761,19 +761,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_4
- SUBROUTINE h5awrite_real_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_5_c
@@ -785,7 +785,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_5_C'::h5awrite_real_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -797,19 +797,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_5
- SUBROUTINE h5awrite_real_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_6_c
@@ -821,7 +821,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_6_C'::h5awrite_real_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -833,19 +833,19 @@ CONTAINS
END SUBROUTINE h5awrite_real_6
- SUBROUTINE h5awrite_real_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_real_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_real_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_real_7_c
@@ -857,7 +857,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_REAL_7_C'::h5awrite_real_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(IN), &
@@ -869,17 +869,17 @@ CONTAINS
END SUBROUTINE h5awrite_real_7
- SUBROUTINE h5awrite_double_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- DOUBLE PRECISION, INTENT(IN) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ DOUBLE PRECISION, INTENT(IN) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_s_c
@@ -891,7 +891,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_S_C'::h5awrite_double_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN)::buf
@@ -901,18 +901,18 @@ CONTAINS
hdferr = h5awrite_double_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_double_scalar
- SUBROUTINE h5awrite_double_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
- DIMENSION(dims(1)) :: buf ! Attribute data
+ DIMENSION(dims(1)) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_1_c
@@ -924,7 +924,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_1_C'::h5awrite_double_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -936,19 +936,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_1
- SUBROUTINE h5awrite_double_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- DOUBLE PRECISION, INTENT(IN), &
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_2_c
@@ -960,7 +960,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_2_C'::h5awrite_double_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -972,19 +972,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_2
- SUBROUTINE h5awrite_double_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_3_c
@@ -996,7 +996,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_3_C'::h5awrite_double_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -1008,19 +1008,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_3
- SUBROUTINE h5awrite_double_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_4_c
@@ -1032,7 +1032,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_4_C'::h5awrite_double_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -1044,19 +1044,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_4
- SUBROUTINE h5awrite_double_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_5_c
@@ -1068,7 +1068,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_5_C'::h5awrite_double_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -1080,19 +1080,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_5
- SUBROUTINE h5awrite_double_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_6_c
@@ -1104,7 +1104,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_6_C'::h5awrite_double_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -1116,19 +1116,19 @@ CONTAINS
END SUBROUTINE h5awrite_double_6
- SUBROUTINE h5awrite_double_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_double_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_double_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awrite_double_7_c
@@ -1140,7 +1140,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITE_DOUBLE_7_C'::h5awrite_double_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(IN), &
@@ -1151,18 +1151,18 @@ CONTAINS
hdferr = h5awrite_double_7_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_double_7
- SUBROUTINE h5awrite_char_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- CHARACTER(LEN=*),INTENT(IN) :: buf
- ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ CHARACTER(LEN=*),INTENT(IN) :: buf
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_s_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1173,7 +1173,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_S_C'::h5awritec_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
!DEC$ATTRIBUTES reference :: buf
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
@@ -1184,19 +1184,19 @@ CONTAINS
hdferr = h5awritec_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5awrite_char_scalar
- SUBROUTINE h5awrite_char_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_1_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1208,7 +1208,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_1_C'::h5awritec_1_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), DIMENSION(dims(1))::buf
@@ -1219,19 +1219,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_1
- SUBROUTINE h5awrite_char_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_2_c
@@ -1243,7 +1243,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_2_C'::h5awritec_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
!DEC$ATTRIBUTES reference :: buf
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
@@ -1256,19 +1256,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_2
- SUBROUTINE h5awrite_char_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_3_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1280,7 +1280,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_3_C'::h5awritec_3_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), &
@@ -1292,19 +1292,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_3
- SUBROUTINE h5awrite_char_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_4_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1316,7 +1316,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_4_C'::h5awritec_4_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), &
@@ -1328,19 +1328,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_4
- SUBROUTINE h5awrite_char_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_5_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1352,7 +1352,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_5_C'::h5awritec_5_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), &
@@ -1364,19 +1364,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_5
- SUBROUTINE h5awrite_char_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_6_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1388,7 +1388,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_6_C'::h5awritec_6_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), &
@@ -1400,19 +1400,19 @@ CONTAINS
END SUBROUTINE h5awrite_char_6
- SUBROUTINE h5awrite_char_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5awrite_char_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5awrite_char_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(IN), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5awritec_7_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1424,7 +1424,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AWRITEC_7_C'::h5awritec_7_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(IN), &
@@ -1436,29 +1436,29 @@ CONTAINS
END SUBROUTINE h5awrite_char_7
!----------------------------------------------------------------------
-! Name: h5aread_f
+! Name: h5aread_f
!
! Purpose: Reads an attribute.
!
-! Inputs:
+! Inputs:
! attr_id - attribute identifier
! memtype_id - attribute memory type identifier
-! dims - 1D array of size 7, stores sizes of the
+! dims - 1D array of size 7, stores sizes of the
! - buf array dimensions.
-! Outputs:
+! Outputs:
! buf - buffer to read attribute data in
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
! dims parameter was added to make code portable;
! Aprile 4, 2001
@@ -1470,20 +1470,20 @@ CONTAINS
!
! Comment: This function is overloaded to write INTEGER,
! REAL, DOUBLE PRECISION and CHARACTER buffers
-! up to 7 dimensions.
+! up to 7 dimensions.
!----------------------------------------------------------------------
- SUBROUTINE h5aread_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- INTEGER, INTENT(INOUT) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER, INTENT(INOUT) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_integer_s_c
@@ -1495,7 +1495,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_S_C'::h5aread_integer_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT)::buf
@@ -1504,16 +1504,16 @@ CONTAINS
hdferr = h5aread_integer_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5aread_integer_scalar
- SUBROUTINE h5aread_integer_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), DIMENSION(dims(1)) :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1526,7 +1526,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_1_C'::h5aread_integer_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), DIMENSION(dims(1)) :: buf
@@ -1537,16 +1537,16 @@ CONTAINS
END SUBROUTINE h5aread_integer_1
- SUBROUTINE h5aread_integer_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT),DIMENSION(dims(1),dims(2)) :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1559,7 +1559,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_2_C'::h5aread_integer_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), DIMENSION(dims(1),dims(2)) :: buf
@@ -1570,16 +1570,16 @@ CONTAINS
END SUBROUTINE h5aread_integer_2
- SUBROUTINE h5aread_integer_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1593,7 +1593,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_3_C'::h5aread_integer_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), &
@@ -1605,19 +1605,19 @@ CONTAINS
END SUBROUTINE h5aread_integer_3
- SUBROUTINE h5aread_integer_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_integer_4_c
@@ -1629,7 +1629,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_4_C'::h5aread_integer_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), &
@@ -1641,19 +1641,19 @@ CONTAINS
END SUBROUTINE h5aread_integer_4
- SUBROUTINE h5aread_integer_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_integer_5_c
@@ -1665,7 +1665,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_5_C'::h5aread_integer_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), &
@@ -1677,19 +1677,19 @@ CONTAINS
END SUBROUTINE h5aread_integer_5
- SUBROUTINE h5aread_integer_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_integer_6_c
@@ -1701,7 +1701,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_6_C'::h5aread_integer_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), &
@@ -1713,19 +1713,19 @@ CONTAINS
END SUBROUTINE h5aread_integer_6
- SUBROUTINE h5aread_integer_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_integer_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_integer_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_integer_7_c
@@ -1737,7 +1737,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_INTEGER_7_C'::h5aread_integer_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
INTEGER, INTENT(INOUT), &
@@ -1749,17 +1749,17 @@ CONTAINS
END SUBROUTINE h5aread_integer_7
- SUBROUTINE h5aread_real_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- REAL, INTENT(INOUT) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ REAL, INTENT(INOUT) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_s_c
@@ -1771,7 +1771,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_S_C'::h5aread_real_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT)::buf
@@ -1781,19 +1781,19 @@ CONTAINS
hdferr = h5aread_real_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5aread_real_scalar
- SUBROUTINE h5aread_real_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_1_c
@@ -1805,7 +1805,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_1_C'::h5aread_real_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1817,19 +1817,19 @@ CONTAINS
END SUBROUTINE h5aread_real_1
- SUBROUTINE h5aread_real_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_2_c
@@ -1841,7 +1841,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_2_C'::h5aread_real_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1853,19 +1853,19 @@ CONTAINS
END SUBROUTINE h5aread_real_2
- SUBROUTINE h5aread_real_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_3_c
@@ -1877,7 +1877,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_3_C'::h5aread_real_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1889,19 +1889,19 @@ CONTAINS
END SUBROUTINE h5aread_real_3
- SUBROUTINE h5aread_real_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_4_c
@@ -1913,7 +1913,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_4_C'::h5aread_real_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1925,19 +1925,19 @@ CONTAINS
END SUBROUTINE h5aread_real_4
- SUBROUTINE h5aread_real_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_5_c
@@ -1949,7 +1949,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_5_C'::h5aread_real_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1961,19 +1961,19 @@ CONTAINS
END SUBROUTINE h5aread_real_5
- SUBROUTINE h5aread_real_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_6_c
@@ -1985,7 +1985,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_6_C'::h5aread_real_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -1997,19 +1997,19 @@ CONTAINS
END SUBROUTINE h5aread_real_6
- SUBROUTINE h5aread_real_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_real_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_real_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
REAL, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_real_7_c
@@ -2021,7 +2021,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_REAL_7_C'::h5aread_real_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
REAL, INTENT(INOUT), &
@@ -2033,17 +2033,17 @@ CONTAINS
END SUBROUTINE h5aread_real_7
- SUBROUTINE h5aread_double_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- DOUBLE PRECISION, INTENT(INOUT) :: buf ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ DOUBLE PRECISION, INTENT(INOUT) :: buf ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_s_c
@@ -2055,7 +2055,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_S_C'::h5aread_double_s_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT)::buf
@@ -2065,19 +2065,19 @@ CONTAINS
hdferr = h5aread_double_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5aread_double_scalar
- SUBROUTINE h5aread_double_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_1_c
@@ -2089,7 +2089,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_1_C'::h5aread_double_1_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2101,19 +2101,19 @@ CONTAINS
END SUBROUTINE h5aread_double_1
- SUBROUTINE h5aread_double_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_2_c
@@ -2125,7 +2125,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_2_C'::h5aread_double_2_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2137,19 +2137,19 @@ CONTAINS
END SUBROUTINE h5aread_double_2
- SUBROUTINE h5aread_double_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_3_c
@@ -2161,7 +2161,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_3_C'::h5aread_double_3_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2173,19 +2173,19 @@ CONTAINS
END SUBROUTINE h5aread_double_3
- SUBROUTINE h5aread_double_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_4_c
@@ -2197,7 +2197,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_4_C'::h5aread_double_4_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2209,19 +2209,19 @@ CONTAINS
END SUBROUTINE h5aread_double_4
- SUBROUTINE h5aread_double_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_5_c
@@ -2233,7 +2233,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_5_C'::h5aread_double_5_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2245,19 +2245,19 @@ CONTAINS
END SUBROUTINE h5aread_double_5
- SUBROUTINE h5aread_double_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_6_c
@@ -2269,7 +2269,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_6_C'::h5aread_double_6_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2281,19 +2281,19 @@ CONTAINS
END SUBROUTINE h5aread_double_6
- SUBROUTINE h5aread_double_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_double_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_double_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
DOUBLE PRECISION, INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5aread_double_7_c
@@ -2305,7 +2305,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREAD_DOUBLE_7_C'::h5aread_double_7_c
!DEC$ ENDIF
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
DOUBLE PRECISION, INTENT(INOUT), &
@@ -2317,18 +2317,18 @@ CONTAINS
END SUBROUTINE h5aread_double_7
- SUBROUTINE h5aread_char_scalar(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_scalar(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_scalar
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
- CHARACTER(LEN=*), INTENT(INOUT) :: buf
- ! Attribute data
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ CHARACTER(LEN=*), INTENT(INOUT) :: buf
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_s_c
@@ -2341,7 +2341,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_S_C'::h5areadc_s_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT) :: buf
@@ -2351,19 +2351,19 @@ CONTAINS
hdferr = h5areadc_s_c(attr_id, memtype_id, buf, dims)
END SUBROUTINE h5aread_char_scalar
- SUBROUTINE h5aread_char_1(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_1(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_1
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_1_c
@@ -2376,7 +2376,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_1_C'::h5areadc_1_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2388,19 +2388,19 @@ CONTAINS
END SUBROUTINE h5aread_char_1
- SUBROUTINE h5aread_char_2(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_2(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_2
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_2_c
@@ -2413,7 +2413,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_2_C'::h5areadc_2_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2425,19 +2425,19 @@ CONTAINS
END SUBROUTINE h5aread_char_2
- SUBROUTINE h5aread_char_3(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_3(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_3
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_3_c
@@ -2450,7 +2450,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_3_C'::h5areadc_3_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2462,19 +2462,19 @@ CONTAINS
END SUBROUTINE h5aread_char_3
- SUBROUTINE h5aread_char_4(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_4(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_4
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_4_c
@@ -2487,7 +2487,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_4_C'::h5areadc_4_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2499,19 +2499,19 @@ CONTAINS
END SUBROUTINE h5aread_char_4
- SUBROUTINE h5aread_char_5(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_5(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_5
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_5_c
@@ -2524,7 +2524,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_5_C'::h5areadc_5_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2536,19 +2536,19 @@ CONTAINS
END SUBROUTINE h5aread_char_5
- SUBROUTINE h5aread_char_6(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_6(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_6
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_6_c
@@ -2561,7 +2561,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_6_C'::h5areadc_6_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2573,19 +2573,19 @@ CONTAINS
END SUBROUTINE h5aread_char_6
- SUBROUTINE h5aread_char_7(attr_id, memtype_id, buf, dims, hdferr)
+ SUBROUTINE h5aread_char_7(attr_id, memtype_id, buf, dims, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aread_char_7
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: memtype_id ! Attribute datatype
! identifier (in memory)
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
CHARACTER(LEN=*), INTENT(INOUT), &
DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)) :: buf
- ! Attribute data
+ ! Attribute data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5areadc_7_c
@@ -2598,7 +2598,7 @@ CONTAINS
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AREADC_7_C'::h5areadc_7_c
!DEC$ ENDIF
!DEC$ATTRIBUTES reference :: buf
- INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
+ INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims ! Array to story buf dimension sizes
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: memtype_id
CHARACTER(LEN=*), INTENT(INOUT), &
@@ -2611,37 +2611,37 @@ CONTAINS
!----------------------------------------------------------------------
-! Name: h5aget_space_f
+! Name: h5aget_space_f
!
! Purpose: Gets a copy of the dataspace for an attribute.
!
-! Inputs:
+! Inputs:
! attr_id - attribute identifier
-! Outputs:
+! Outputs:
! space_id - attribite dataspace identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_space_f(attr_id, space_id, hdferr)
+ SUBROUTINE h5aget_space_f(attr_id, space_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_space_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(OUT) :: space_id
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(OUT) :: space_id
! Attribute dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2663,37 +2663,37 @@ CONTAINS
END SUBROUTINE h5aget_space_f
!----------------------------------------------------------------------
-! Name: h5aget_type_f
+! Name: h5aget_type_f
!
! Purpose: Gets an attribute datatype.
!
-! Inputs:
+! Inputs:
! attr_id - attribute identifier
-! Outputs:
+! Outputs:
! type_id - attribute datatype identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_type_f(attr_id, type_id, hdferr)
+ SUBROUTINE h5aget_type_f(attr_id, type_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_type_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(OUT) :: type_id
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(OUT) :: type_id
! Attribute datatype identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2715,40 +2715,40 @@ CONTAINS
END SUBROUTINE h5aget_type_f
!----------------------------------------------------------------------
-! Name: h5aget_name_f
+! Name: h5aget_name_f
!
-! Purpose: Gets an attribute name.
+! Purpose: Gets an attribute name.
!
-! Inputs:
+! Inputs:
! attr_id - attribute identifier
! size - size of a buffer to read name in
-! Outputs:
+! Outputs:
! buf - buffer to read name in
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_name_f(attr_id, size, buf, hdferr)
+ SUBROUTINE h5aget_name_f(attr_id, size, buf, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_name_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(SIZE_T), INTENT(IN) :: size ! Buffer size
- CHARACTER(LEN=*), INTENT(INOUT) :: buf
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(SIZE_T), INTENT(IN) :: size ! Buffer size
+ CHARACTER(LEN=*), INTENT(INOUT) :: buf
! Buffer to hold attribute name
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! name length is successful,
@@ -2775,9 +2775,9 @@ CONTAINS
!----------------------------------------------------------------------
! Name: h5aget_name_by_idx_f
!
-! Purpose: Gets an attribute name, by attribute index position.
+! Purpose: Gets an attribute name, by attribute index position.
!
-! Inputs:
+! Inputs:
! loc_id - Location of object to which attribute is attached
! obj_name - Name of object to which attribute is attached, relative to location
! idx_type - Type of index; Possible values are:
@@ -2798,13 +2798,13 @@ CONTAINS
! order - Index traversal order
! n - Attribute’s position in index
!
-! Outputs:
+! Outputs:
! name - Attribute name
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
! size - Size, in bytes, of attribute name
!
! Programmer: M.S. Breitenfeld
@@ -2814,7 +2814,7 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5aget_name_by_idx_f(loc_id, obj_name, idx_type, order, &
- n, name, hdferr, size, lapl_id)
+ n, name, hdferr, size, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_name_by_idx_f
@@ -2837,10 +2837,10 @@ CONTAINS
! H5_ITER_N_F - Number of iteration orders
INTEGER(HSIZE_T), INTENT(IN) :: n ! Attribute’s position in index
-
+
CHARACTER(LEN=*), INTENT(OUT) :: name ! Attribute name
-
+
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! Returns attribute name size,
! -1 if fail
@@ -2865,7 +2865,7 @@ CONTAINS
INTEGER, INTENT(IN) :: idx_type
INTEGER, INTENT(IN) :: order
INTEGER(HSIZE_T), INTENT(IN) :: n
-
+
CHARACTER(LEN=*), INTENT(OUT) :: name
INTEGER(SIZE_T) :: size_default
INTEGER(HID_T) :: lapl_id_default
@@ -2881,7 +2881,7 @@ CONTAINS
hdferr = h5aget_name_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, &
n, name, size_default, lapl_id_default)
-
+
IF(PRESENT(size)) size = size_default
@@ -2889,37 +2889,37 @@ CONTAINS
!----------------------------------------------------------------------
-! Name: h5aget_num_attrs_f
+! Name: h5aget_num_attrs_f
!
! Purpose: Determines the number of attributes attached to an object.
!
-! Inputs:
+! Inputs:
! obj_id - object (group, dataset, or named datatype)
! identifier
-! Outputs:
+! Outputs:
! attr_num - number of attributes attached to the object
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_num_attrs_f(obj_id, attr_num, hdferr)
+ SUBROUTINE h5aget_num_attrs_f(obj_id, attr_num, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_num_attrs_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
+ INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
INTEGER, INTENT(OUT) :: attr_num ! Number of attributes of the
! object
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2937,43 +2937,43 @@ CONTAINS
INTEGER, INTENT(OUT) :: attr_num
END FUNCTION h5aget_num_attrs_c
END INTERFACE
-
+
hdferr = h5aget_num_attrs_c(obj_id, attr_num)
END SUBROUTINE h5aget_num_attrs_f
!----------------------------------------------------------------------
-! Name: h5adelete_f
+! Name: h5adelete_f
!
! Purpose: Deletes an attribute of an object (group, dataset or
! named datatype)
!
-! Inputs:
+! Inputs:
! obj_id - object identifier
! name - attribute name
-! Outputs:
+! Outputs:
!
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5adelete_f(obj_id, name, hdferr)
+ SUBROUTINE h5adelete_f(obj_id, name, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5adelete_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
+ INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Attribute name
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER(SIZE_T) :: namelen
@@ -2982,7 +2982,7 @@ CONTAINS
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5adelete_c(obj_id, name, namelen)
+ INTEGER FUNCTION h5adelete_c(obj_id, name, namelen)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5ADELETE_C'::h5adelete_c
@@ -2993,42 +2993,42 @@ CONTAINS
INTEGER(SIZE_T) :: namelen
END FUNCTION h5adelete_c
END INTERFACE
-
+
namelen = LEN(name)
hdferr = h5adelete_c(obj_id, name, namelen)
END SUBROUTINE h5adelete_f
!----------------------------------------------------------------------
-! Name: h5aclose_f
+! Name: h5aclose_f
!
! Purpose: Closes the specified attribute.
-!
-! Inputs:
+!
+! Inputs:
! attr_id - attribute identifier
-! Outputs:
+! Outputs:
!
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces are added for
+! Modifications: Explicit Fortran interfaces are added for
! called C functions (it is needed for Windows
-! port). February 27, 2001
+! port). February 27, 2001
!
!----------------------------------------------------------------------
- SUBROUTINE h5aclose_f(attr_id, hdferr)
+ SUBROUTINE h5aclose_f(attr_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aclose_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! INTEGER, EXTERNAL :: h5aclose_c
@@ -3043,39 +3043,39 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: attr_id
END FUNCTION h5aclose_c
END INTERFACE
-
+
hdferr = h5aclose_c(attr_id)
END SUBROUTINE h5aclose_f
!----------------------------------------------------------------------
-! Name: h5aget_storage_size_f
+! Name: h5aget_storage_size_f
!
! Purpose: Returns the amount of storage required for an attribute.
-!
-! Inputs:
+!
+! Inputs:
! attr_id - attribute identifier
-! Outputs:
+! Outputs:
! size - attribute storage size
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: M. S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_storage_size_f(attr_id, size, hdferr)
+ SUBROUTINE h5aget_storage_size_f(attr_id, size, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_storage_size_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Attribute storage requirement
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -3091,39 +3091,39 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(OUT) :: size
END FUNCTION h5aget_storage_size_c
END INTERFACE
-
+
hdferr = h5aget_storage_size_c(attr_id, size)
END SUBROUTINE h5aget_storage_size_f
!----------------------------------------------------------------------
-! Name: h5aget_create_plist_f
+! Name: h5aget_create_plist_f
!
! Purpose: Gets an attribute creation property list identifier
-!
-! Inputs:
+!
+! Inputs:
! attr_id - Identifier of the attribute
-! Outputs:
+! Outputs:
! creation_prop_id - Identifier for the attribute’s creation property
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: M. S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_create_plist_f(attr_id, creation_prop_id, hdferr)
+ SUBROUTINE h5aget_create_plist_f(attr_id, creation_prop_id, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_create_plist_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Identifier of the attribute
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Identifier of the attribute
INTEGER(HID_T), INTENT(OUT) :: creation_prop_id ! Identifier for the attribute’s creation property
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
@@ -3140,49 +3140,49 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: creation_prop_id
END FUNCTION h5aget_create_plist_c
END INTERFACE
-
+
hdferr = h5aget_create_plist_c(attr_id, creation_prop_id)
END SUBROUTINE h5aget_create_plist_f
!----------------------------------------------------------------------
-! Name: h5arename_by_name_f
+! Name: h5arename_by_name_f
!
! Purpose: Renames an attribute
!
-! Inputs:
+! Inputs:
! loc_id - Location or object identifier; may be dataset or group
-! obj_name - Name of object, relative to location,
+! obj_name - Name of object, relative to location,
! whose attribute is to be renamed
! old_attr_name - Prior attribute name
! new_attr_name - New attribute name
! lapl_id - Link access property list identifier
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! Programmer: M.S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
SUBROUTINE h5arename_by_name_f(loc_id, obj_name, old_attr_name, new_attr_name, &
- hdferr, lapl_id)
+ hdferr, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5arename_by_name_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: loc_id ! Object identifier
- CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
+ INTEGER(HID_T), INTENT(IN) :: loc_id ! Object identifier
+ CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
! whose attribute is to be renamed
CHARACTER(LEN=*), INTENT(IN) :: old_attr_name ! Prior attribute name
CHARACTER(LEN=*), INTENT(IN) :: new_attr_name ! New attribute name
-
+
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
@@ -3191,7 +3191,7 @@ CONTAINS
INTEGER(SIZE_T) :: obj_namelen
INTEGER(SIZE_T) :: old_attr_namelen
INTEGER(SIZE_T) :: new_attr_namelen
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -3211,7 +3211,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: new_attr_name
INTEGER(SIZE_T) :: new_attr_namelen
INTEGER(HID_T) :: lapl_id_default
-
+
END FUNCTION h5arename_by_name_c
END INTERFACE
@@ -3221,49 +3221,49 @@ CONTAINS
lapl_id_default = H5P_DEFAULT_F
IF(PRESENT(lapl_id)) lapl_id_default=lapl_id
-
+
hdferr = h5arename_by_name_c(loc_id, obj_name, obj_namelen, &
old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen, &
lapl_id_default)
-
+
END SUBROUTINE h5arename_by_name_f
!----------------------------------------------------------------------
-! Name: h5aopen_f
+! Name: h5aopen_f
!
-! Purpose: Opens an attribute for an object specified by object
+! Purpose: Opens an attribute for an object specified by object
! identifier and attribute name
!
-! Inputs:
+! Inputs:
! obj_id - Identifer for object to which attribute is attached
! attr_name - Name of attribute to open
-! Outputs:
+! Outputs:
! attr_id - attribute identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! aapl_id - Attribute access property list
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications: N/A
+! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5aopen_f(obj_id, attr_name, attr_id, hdferr, aapl_id)
+ SUBROUTINE h5aopen_f(obj_id, attr_name, attr_id, hdferr, aapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aopen_f
!DEC$endif
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
+ INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
- INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
- INTEGER, INTENT(OUT) :: hdferr ! Error code
+ INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
! Success: 0
- ! Failure: -1
+ ! Failure: -1
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list
INTEGER(HID_T) :: aapl_id_default
@@ -3281,7 +3281,7 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: obj_id
CHARACTER(LEN=*), INTENT(IN) :: attr_name
INTEGER(HID_T) :: aapl_id_default
- INTEGER(SIZE_T) :: attr_namelen
+ INTEGER(SIZE_T) :: attr_namelen
INTEGER(HID_T), INTENT(OUT) :: attr_id
END FUNCTION h5aopen_c
END INTERFACE
@@ -3296,11 +3296,11 @@ CONTAINS
END SUBROUTINE h5aopen_f
!----------------------------------------------------------------------
-! Name: h5adelete_by_idx_f
+! Name: h5adelete_by_idx_f
!
-! Purpose: Deletes an attribute from an object according to index order
+! Purpose: Deletes an attribute from an object according to index order
!
-! Inputs:
+! Inputs:
! loc_id - Location or object identifier; may be dataset or group
! obj_name - Name of object, relative to location, from which attribute is to be removed
! idx_type - Type of index; Possible values are:
@@ -3309,7 +3309,7 @@ CONTAINS
! H5_INDEX_NAME_F - Index on names
! H5_INDEX_CRT_ORDER_F - Index on creation order
! H5_INDEX_N_F - Number of indices defined
-!
+!
! order - Order in which to iterate over index; Possible values are:
!
! H5_ITER_UNKNOWN_F - Unknown order
@@ -3320,26 +3320,26 @@ CONTAINS
!
! n - Offset within index
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lapl_id - Link access property list
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications: N/A
+! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5adelete_by_idx_f(loc_id, obj_name, idx_type, order, n, hdferr, lapl_id)
+ SUBROUTINE h5adelete_by_idx_f(loc_id, obj_name, idx_type, order, n, hdferr, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5adelete_by_idx_f
!DEC$endif
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifer for object to which attribute is attached
- CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
+ CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
! from which attribute is to be removed
INTEGER, INTENT(IN) :: idx_type ! Type of index; Possible values are:
! H5_INDEX_UNKNOWN_F - Unknown index type
@@ -3354,14 +3354,14 @@ CONTAINS
! H5_ITER_NATIVE_F - No particular order, whatever is fastest
! H5_ITER_N_F - Number of iteration orders
!
- INTEGER(HSIZE_T), INTENT(IN) :: n ! Offset within index
+ INTEGER(HSIZE_T), INTENT(IN) :: n ! Offset within index
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(SIZE_T) :: obj_namelen
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(HID_T) :: lapl_id_default
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -3375,7 +3375,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: obj_name
INTEGER, INTENT(IN) :: idx_type
INTEGER, INTENT(IN) :: order
- INTEGER(HSIZE_T), INTENT(IN) :: n
+ INTEGER(HSIZE_T), INTENT(IN) :: n
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: obj_namelen
END FUNCTION h5adelete_by_idx_c
@@ -3383,48 +3383,48 @@ CONTAINS
lapl_id_default = H5P_DEFAULT_F
IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
-
+
obj_namelen = LEN(obj_name)
hdferr = h5adelete_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, lapl_id_default)
-
+
END SUBROUTINE h5adelete_by_idx_f
!----------------------------------------------------------------------
-! Name: h5adelete_by_name_f
+! Name: h5adelete_by_name_f
!
! Purpose: Removes an attribute from a specified location
!
-! Inputs:
+! Inputs:
! loc_id - Identifer for object to which attribute is attached
! obj_name - Name of attribute to open
! attr_name - Attribute access property list
! lapl_id - Link access property list
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: M.S. Breitenfeld
! January, 2008
!
-! Modifications: N/A
+! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5adelete_by_name_f(loc_id, obj_name, attr_name, hdferr, lapl_id)
+ SUBROUTINE h5adelete_by_name_f(loc_id, obj_name, attr_name, hdferr, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5adelete_by_name_f
!DEC$endif
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifer for object to which attribute is attached
- CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
+ CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object, relative to location,
! from which attribute is to be removed
CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Name of attribute to delete
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(SIZE_T) :: attr_namelen
INTEGER(SIZE_T) :: obj_namelen
@@ -3447,7 +3447,7 @@ CONTAINS
INTEGER(SIZE_T) :: obj_namelen
END FUNCTION h5adelete_by_name_c
END INTERFACE
-
+
obj_namelen = LEN(obj_name)
attr_namelen = LEN(attr_name)
@@ -3459,32 +3459,32 @@ CONTAINS
END SUBROUTINE h5adelete_by_name_f
!----------------------------------------------------------------------
-! Name: h5aopen_by_idx_f
+! Name: h5aopen_by_idx_f
!
! Purpose: Opens an existing attribute that is attached to an object specified by location and name
!
-! Inputs:
+! Inputs:
! loc_id - Location of object to which attribute is attached
! obj_name - Name of object to which attribute is attached, relative to location
! idx_type - Type of index
! order - Index traversal order
! n - Attribute’s position in index
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! aapl_id - Attribute access property list
! lapl_id - Link access property list
!
! Programmer: M.S. Breitenfeld
-! January, 2008
+! January, 2008
!
-! Modifications: N/A
+! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5aopen_by_idx_f(loc_id, obj_name, idx_type, order, n, attr_id, hdferr, aapl_id, lapl_id)
+ SUBROUTINE h5aopen_by_idx_f(loc_id, obj_name, idx_type, order, n, attr_id, hdferr, aapl_id, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aopen_by_idx_f
@@ -3502,7 +3502,7 @@ CONTAINS
! H5_ITER_INC_F - Increasing order
! H5_ITER_DEC_F - Decreasing order
! H5_ITER_NATIVE_F - No particular order, whatever is fastest
-
+
INTEGER(HSIZE_T), INTENT(IN) :: n ! Attribute’s position in index
INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
@@ -3512,7 +3512,7 @@ CONTAINS
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(SIZE_T) :: obj_namelen
- INTEGER(HID_T) :: aapl_id_default
+ INTEGER(HID_T) :: aapl_id_default
INTEGER(HID_T) :: lapl_id_default
!
@@ -3553,31 +3553,31 @@ CONTAINS
! Name: h5aget_info_f
!
! Purpose: Retrieves attribute information, by attribute identifier
-!
-! Inputs:
+!
+! Inputs:
! attr_id - attribute identifier
!
! Outputs: NOTE: In C it is defined as a structure: H5A_info_t
!
! corder_valid - indicates whether the creation order data is valid for this attribute
-! corder - is a positive integer containing the creation order of the attribute
-! cset - indicates the character set used for the attribute’s name
+! corder - is a positive integer containing the creation order of the attribute
+! cset - indicates the character set used for the attribute’s name
! data_size - indicates the size, in the number of characters, of the attribute
-!
-! hdferr - error code
+!
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: M. S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5aget_info_f(attr_id, f_corder_valid, corder, cset, data_size, hdferr)
+ SUBROUTINE h5aget_info_f(attr_id, f_corder_valid, corder, cset, data_size, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_info_f
@@ -3585,7 +3585,7 @@ CONTAINS
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
+ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
@@ -3612,10 +3612,10 @@ CONTAINS
END INTERFACE
hdferr = h5aget_info_c(attr_id, corder_valid, corder, cset, data_size)
-
+
f_corder_valid =.FALSE.
IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-
+
END SUBROUTINE h5aget_info_f
@@ -3624,7 +3624,7 @@ CONTAINS
! Name: h5aget_info_by_idx_f
!
! Purpose: Retrieves attribute information, by attribute index position
-!
+!
! Inputs:
! loc_id - Location of object to which attribute is attached
! obj_name - Name of object to which attribute is attached, relative to location
@@ -3634,23 +3634,23 @@ CONTAINS
!
! Outputs: NOTE: In C it is defined as a structure: H5A_info_t
! corder_valid - indicates whether the creation order data is valid for this attribute
-! corder - is a positive integer containing the creation order of the attribute
-! cset - indicates the character set used for the attribute’s name
-! data_size - indicates the size, in the number of characters, of the attribute
-! hdferr - error code
+! corder - is a positive integer containing the creation order of the attribute
+! cset - indicates the character set used for the attribute’s name
+! data_size - indicates the size, in the number of characters, of the attribute
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
!
! Programmer: M. S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
SUBROUTINE h5aget_info_by_idx_f(loc_id, obj_name, idx_type, order, n, &
- f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
+ f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_info_by_idx_f
@@ -3668,11 +3668,11 @@ CONTAINS
! H5_ITER_INC_F - Increasing order
! H5_ITER_DEC_F - Decreasing order
! H5_ITER_NATIVE_F - No particular order, whatever is fastest
-
+
INTEGER(HSIZE_T), INTENT(IN) :: n ! Attribute’s position in index
- LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
+ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
@@ -3698,7 +3698,7 @@ CONTAINS
INTEGER, INTENT(IN) :: order
INTEGER(HSIZE_T), INTENT(IN) :: n
INTEGER(HID_T) :: lapl_id_default
- INTEGER, INTENT(OUT) :: corder_valid
+ INTEGER, INTENT(OUT) :: corder_valid
INTEGER, INTENT(OUT) :: corder
INTEGER, INTENT(OUT) :: cset
INTEGER(HSIZE_T), INTENT(OUT) :: data_size
@@ -3717,14 +3717,14 @@ CONTAINS
f_corder_valid =.FALSE.
IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-
+
END SUBROUTINE h5aget_info_by_idx_f
!----------------------------------------------------------------------
! Name: h5aget_info_by_name_f
!
! Purpose: Retrieves attribute information, by attribute name
-!
+!
! Inputs:
! loc_id - Location of object to which attribute is attached
! obj_name - Name of object to which attribute is attached, relative to location
@@ -3732,23 +3732,23 @@ CONTAINS
!
! Outputs: NOTE: In C it is defined as a structure: H5A_info_t
! corder_valid - indicates whether the creation order data is valid for this attribute
-! corder - is a positive integer containing the creation order of the attribute
-! cset - indicates the character set used for the attribute’s name
-! data_size - indicates the size, in the number of characters, of the attribute
-! hdferr - error code
+! corder - is a positive integer containing the creation order of the attribute
+! cset - indicates the character set used for the attribute’s name
+! data_size - indicates the size, in the number of characters, of the attribute
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
!
! Programmer: M. S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
SUBROUTINE h5aget_info_by_name_f(loc_id, obj_name, attr_name, &
- f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
+ f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5aget_info_by_name_f
@@ -3759,7 +3759,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
- LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
+ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
@@ -3770,7 +3770,7 @@ CONTAINS
INTEGER(SIZE_T) :: attr_namelen
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(HID_T) :: lapl_id_default
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -3787,7 +3787,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: attr_name
INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
INTEGER(HID_T) :: lapl_id_default
- INTEGER, INTENT(OUT) :: corder_valid
+ INTEGER, INTENT(OUT) :: corder_valid
INTEGER, INTENT(OUT) :: corder
INTEGER, INTENT(OUT) :: cset
INTEGER(HSIZE_T), INTENT(OUT) :: data_size
@@ -3799,21 +3799,21 @@ CONTAINS
attr_namelen = LEN(attr_name)
lapl_id_default = H5P_DEFAULT_F
- IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
+ IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
hdferr = h5aget_info_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, &
corder_valid, corder, cset, data_size)
f_corder_valid =.FALSE.
IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-
+
END SUBROUTINE h5aget_info_by_name_f
!----------------------------------------------------------------------
-! Name: H5Acreate_by_name_f
+! Name: H5Acreate_by_name_f
!
! Purpose: Creates an attribute attached to a specified object
-!
+!
! Inputs:
! loc_id - Location or object identifier; may be dataset or group
! obj_name - Name, relative to loc_id, of object that attribute is to be attached to
@@ -3823,16 +3823,16 @@ CONTAINS
!
! Outputs:
! attr - an attribute identifier
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! acpl_id - Attribute creation property list identifier (Currently not used.)
! aapl_id - Attribute access property list identifier (Currently not used.)
-! lapl_id - Link access property list
+! lapl_id - Link access property list
!
! Programmer: M. S. Breitenfeld
-! February, 2008
+! February, 2008
!
! Modifications: N/A
!
@@ -3882,7 +3882,7 @@ CONTAINS
INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
CHARACTER(LEN=*), INTENT(IN) :: attr_name
INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
- INTEGER(HID_T), INTENT(IN) :: type_id
+ INTEGER(HID_T), INTENT(IN) :: type_id
INTEGER(HID_T), INTENT(IN) :: space_id
INTEGER(HID_T) :: acpl_id_default
INTEGER(HID_T) :: aapl_id_default
@@ -3902,30 +3902,30 @@ CONTAINS
IF(PRESENT(acpl_id)) acpl_id_default = acpl_id
IF(PRESENT(aapl_id)) aapl_id_default = aapl_id
IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
-
+
hdferr = h5acreate_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, &
type_id, space_id, acpl_id_default, aapl_id_default, lapl_id_default, attr)
END SUBROUTINE h5acreate_by_name_f
!----------------------------------------------------------------------
-! Name: H5Aexists_f
+! Name: H5Aexists_f
!
! Purpose: Determines whether an attribute with a given name exists on an object
-!
+!
! Inputs:
! obj_id - Object identifier
! attr_name - Attribute name
!
! Outputs:
! attr_exists - attribute exists status
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! NONE
+! NONE
!
! Programmer: M. S. Breitenfeld
-! February, 2008
+! February, 2008
!
! Modifications: N/A
!
@@ -3966,15 +3966,15 @@ CONTAINS
hdferr = h5aexists_c(obj_id, attr_name, attr_namelen, attr_exists_c)
attr_exists = .FALSE.
- IF(attr_exists_c.GT.0) attr_exists = .TRUE.
+ IF(attr_exists_c.GT.0) attr_exists = .TRUE.
END SUBROUTINE h5aexists_f
!----------------------------------------------------------------------
-! Name: H5Aexists_by_name_f
+! Name: H5Aexists_by_name_f
!
! Purpose: Determines whether an attribute with a given name exists on an object
-!
+!
! Inputs:
! loc_id - Location identifier
! obj_name - Object name either relative to loc_id, absolute from the file’s root group, or '.' (a dot)
@@ -3982,14 +3982,14 @@ CONTAINS
!
! Outputs:
! attr_exists - attribute exists status
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list identifier
+! lapl_id - Link access property list identifier
!
! Programmer: M. S. Breitenfeld
-! February, 2008
+! February, 2008
!
! Modifications: N/A
!
@@ -4003,7 +4003,7 @@ CONTAINS
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
- CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
+ CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
! absolute from the file’s root group, or '.'
CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
LOGICAL, INTENT(OUT) :: attr_exists ! .TRUE. if exists, .FALSE. otherwise
@@ -4024,7 +4024,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AEXISTS_BY_NAME_C'::h5aexists_by_name_c
!DEC$ ENDIF
- INTEGER(HID_T), INTENT(IN) :: loc_id
+ INTEGER(HID_T), INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: obj_name
INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
CHARACTER(LEN=*), INTENT(IN) :: attr_name
@@ -4043,30 +4043,30 @@ CONTAINS
hdferr = h5aexists_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, attr_exists_c)
attr_exists = .FALSE.
- IF(attr_exists_c.GT.0) attr_exists = .TRUE.
+ IF(attr_exists_c.GT.0) attr_exists = .TRUE.
END SUBROUTINE h5aexists_by_name_f
!----------------------------------------------------------------------
-! Name: H5Aopen_by_name_f
+! Name: H5Aopen_by_name_f
!
! Purpose: Opens an attribute for an object by object name and attribute name.
-!
+!
! Inputs:
-! loc_id - Location from which to find object to which attribute is attached
+! loc_id - Location from which to find object to which attribute is attached
! obj_name - Object name either relative to loc_id, absolute from the file’s root group, or '.' (a dot)
! attr_name - Attribute name
!
! Outputs:
! attr_id - attribute identifier
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! aapl_id - Attribute access property list (Currently unused; should be passed in as H5P_DEFAULT.)
-! lapl_id - Link access property list identifier
+! lapl_id - Link access property list identifier
!
! Programmer: M. S. Breitenfeld
-! February, 2008
+! February, 2008
!
! Modifications: N/A
!
@@ -4080,16 +4080,16 @@ CONTAINS
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
- CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
+ CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
! absolute from the file’s root group, or '.'
CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list
! (Currently unused; should be passed in as H5P_DEFAULT_F)
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
-
+
INTEGER(HID_T) :: aapl_id_default
INTEGER(HID_T) :: lapl_id_default
@@ -4105,7 +4105,7 @@ CONTAINS
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_BY_NAME_C'::h5aopen_by_name_c
!DEC$ ENDIF
- INTEGER(HID_T), INTENT(IN) :: loc_id
+ INTEGER(HID_T), INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: obj_name
INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
CHARACTER(LEN=*), INTENT(IN) :: attr_name
@@ -4130,28 +4130,28 @@ CONTAINS
END SUBROUTINE h5aopen_by_name_f
!----------------------------------------------------------------------
-! Name: h5arename_f
+! Name: h5arename_f
!
! Purpose: Renames an attribute
!
-! Inputs:
+! Inputs:
! loc_id - Location or object identifier; may be dataset or group
! old_attr_name - Prior attribute name
! new_attr_name - New attribute name
!
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
!
! Programmer: M.S. Breitenfeld
-! January, 2008
+! January, 2008
!
! Modifications: N/A
!
!----------------------------------------------------------------------
- SUBROUTINE h5arename_f(loc_id, old_attr_name, new_attr_name, hdferr)
+ SUBROUTINE h5arename_f(loc_id, old_attr_name, new_attr_name, hdferr)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -4165,7 +4165,7 @@ CONTAINS
! 0 on success and -1 on failure
INTEGER(SIZE_T) :: old_attr_namelen
INTEGER(SIZE_T) :: new_attr_namelen
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -4181,16 +4181,16 @@ CONTAINS
INTEGER(SIZE_T) :: old_attr_namelen
CHARACTER(LEN=*), INTENT(IN) :: new_attr_name
INTEGER(SIZE_T) :: new_attr_namelen
-
+
END FUNCTION h5arename_c
END INTERFACE
old_attr_namelen = LEN(old_attr_name)
new_attr_namelen = LEN(new_attr_name)
-
+
hdferr = h5arename_c(loc_id, &
old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen)
-
+
END SUBROUTINE h5arename_f
END MODULE H5A