diff options
Diffstat (limited to 'fortran/src/H5Aff_F03.f90')
-rw-r--r-- | fortran/src/H5Aff_F03.f90 | 286 |
1 files changed, 0 insertions, 286 deletions
diff --git a/fortran/src/H5Aff_F03.f90 b/fortran/src/H5Aff_F03.f90 index 8565661..ff1ba1c 100644 --- a/fortran/src/H5Aff_F03.f90 +++ b/fortran/src/H5Aff_F03.f90 @@ -468,149 +468,6 @@ CONTAINS hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) END SUBROUTINE h5awrite_real_7 - - SUBROUTINE h5awrite_double_scalar(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_scalar - - SUBROUTINE h5awrite_double_1(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_1 - - - SUBROUTINE h5awrite_double_2(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_2 - - - SUBROUTINE h5awrite_double_3(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_3 - - - SUBROUTINE h5awrite_double_4(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_4 - - - SUBROUTINE h5awrite_double_5(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_5 - - - SUBROUTINE h5awrite_double_6(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - - END SUBROUTINE h5awrite_double_6 - - - SUBROUTINE h5awrite_double_7(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5awrite_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5awrite_double_7 - SUBROUTINE h5awrite_char_scalar(attr_id, memtype_id, buf, dims, hdferr) USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE @@ -1090,149 +947,6 @@ CONTAINS hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) END SUBROUTINE h5aread_real_7 - - SUBROUTINE h5aread_double_scalar(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_scalar - - SUBROUTINE h5aread_double_1(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_1 - - - SUBROUTINE h5aread_double_2(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_2 - - - SUBROUTINE h5aread_double_3(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_3 - - - SUBROUTINE h5aread_double_4(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_4 - - - SUBROUTINE h5aread_double_5(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_5 - - - SUBROUTINE h5aread_double_6(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_6 - - - SUBROUTINE h5aread_double_7(attr_id, memtype_id, buf, dims, hdferr) - USE, INTRINSIC :: ISO_C_BINDING - IMPLICIT NONE - 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), & - DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf ! Attribute data - INTEGER, INTENT(OUT) :: hdferr ! Error code - TYPE(C_PTR) :: f_ptr - - f_ptr = C_LOC(buf) - - hdferr = h5aread_f_c(attr_id, memtype_id, f_ptr) - END SUBROUTINE h5aread_double_7 - - SUBROUTINE h5aread_char_scalar(attr_id, memtype_id, buf, dims, hdferr) USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE |