summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Aff_F03.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Aff_F03.f90')
-rw-r--r--fortran/src/H5Aff_F03.f90186
1 files changed, 164 insertions, 22 deletions
diff --git a/fortran/src/H5Aff_F03.f90 b/fortran/src/H5Aff_F03.f90
index 387dbae..b9e6c92 100644
--- a/fortran/src/H5Aff_F03.f90
+++ b/fortran/src/H5Aff_F03.f90
@@ -173,6 +173,57 @@ MODULE H5A_PROVISIONAL
CONTAINS
+!****s* H5A (F03)/h5awrite_f_F90
+!
+! NAME
+! h5awrite_f_F90
+!
+! PURPOSE
+! Writes an attribute.
+!
+! Inputs:
+! attr_id - Attribute identifier
+! memtype_id - Attribute datatype identifier (in memory)
+! dims - Array to hold corresponding dimension sizes of data buffer buf;
+! dim(k) has value of the k-th dimension of buffer buf;
+! values are ignored if buf is a scalar
+! buf - Data buffer; may be a scalar or an array
+!
+! Outputs:
+! hdferr - Returns 0 if successful and -1 if fails
+!
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces are added for
+! called C functions (it is needed for Windows
+! port). February 27, 2001
+!
+! dims parameter was added to make code portable;
+! Aprile 4, 2001
+!
+! Changed buf intent to INOUT to be consistant
+! with how the C functions handles it. The pg
+! compiler will return 0 if a buf value is not set.
+! February, 2008
+!
+! NOTES
+! This function is overloaded to write INTEGER,
+! REAL, DOUBLE PRECISION and CHARACTER buffers
+! up to 7 dimensions.
+!
+! Fortran90 Interface:
+!! SUBROUTINE h5awrite_f(attr_id, memtype_id, buf, dims, hdferr)
+!! INTEGER(HID_T) , INTENT(IN) :: attr_id
+!! INTEGER(HID_T) , INTENT(IN) :: memtype_id
+!! TYPE , INTENT(IN) :: buf
+!! INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims
+!! INTEGER , INTENT(OUT) :: hdferr
+!*****
+
+
SUBROUTINE h5awrite_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
@@ -500,8 +551,6 @@ CONTAINS
END SUBROUTINE h5awrite_char_scalar_fix
-
-
SUBROUTINE h5awrite_char_1(attr_id, memtype_id, buf, dims, hdferr)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
@@ -626,22 +675,75 @@ CONTAINS
END SUBROUTINE h5awrite_char_7
-!****s* H5A (F03)/h5aread_f
+!****s* H5A (F03)/h5awrite_f_F03
!
! NAME
-! h5aread_f
+! h5awrite_f_F03
+!
+! PURPOSE
+! Writes an attribute.
+!
+! Inputs:
+! attr_id - Attribute identifier
+! memtype_id - Attribute datatype identifier (in memory)
+! buf - Data buffer; may be a scalar or an array
+!
+! Outputs:
+! hdferr - Returns 0 if successful and -1 if fails
+!
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces are added for
+! called C functions (it is needed for Windows
+! port). February 27, 2001
+!
+! NOTES
+! This function is overloaded to write INTEGER,
+! REAL, DOUBLE PRECISION and CHARACTER buffers
+! up to 7 dimensions.
+!
+! Fortran2003 Interface:
+!! SUBROUTINE h5awrite_f(attr_id, memtype_id, buf, hdferr)
+!! INTEGER(HID_T) , INTENT(IN) :: attr_id
+!! INTEGER(HID_T) , INTENT(IN) :: memtype_id
+!! TYPE(C_PTR) , INTENT(IN) :: buf
+!! INTEGER , INTENT(OUT) :: hdferr
+!*****
+
+ SUBROUTINE h5awrite_ptr(attr_id, mem_type_id, buf, hdferr)
+ USE, INTRINSIC :: ISO_C_BINDING
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
+ INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
+ TYPE(C_PTR), INTENT(IN), TARGET :: buf
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ hdferr = h5awrite_f_c(attr_id, mem_type_id, buf)
+
+ END SUBROUTINE h5awrite_ptr
+
+!****s* H5A (F03)/h5aread_f_F90
+!
+! NAME
+! h5aread_f_F90
!
! PURPOSE
! Reads an attribute.
!
! Inputs:
-! attr_id - attribute identifier
-! memtype_id - attribute memory type identifier
-! dims - 1D array of size 7, stores sizes of the
-! - buf array dimensions.
+! attr_id - Attribute identifier
+! memtype_id - Attribute datatype identifier (in memory)
+! dims - Array to hold corresponding dimension sizes of data buffer buf;
+! dim(k) has value of the k-th dimension of buffer buf;
+! values are ignored if buf is a scalar
+!
! Outputs:
-! buf - buffer to read attribute data in
-! hdferr - Returns 0 if successful and -1 if fails
+! buf - Data buffer; may be a scalar or an array
+! hdferr - Returns 0 if successful and -1 if fails
+!
! AUTHOR
! Elena Pourmal
! August 12, 1999
@@ -663,7 +765,13 @@ CONTAINS
! This function is overloaded to write INTEGER,
! REAL, DOUBLE PRECISION and CHARACTER buffers
! up to 7 dimensions.
-!
+! Fortran90 Interface:
+!! SUBROUTINE h5aread_f(attr_id, memtype_id, buf, dims, hdferr)
+!! INTEGER(HID_T) , INTENT(IN) :: attr_id
+!! INTEGER(HID_T) , INTENT(IN) :: memtype_id
+!! TYPE , INTENT(INOUT) :: buf
+!! INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims
+!! INTEGER , INTENT(OUT) :: hdferr
!*****
SUBROUTINE h5aread_integer_scalar(attr_id, memtype_id, buf, dims, hdferr)
USE, INTRINSIC :: ISO_C_BINDING
@@ -1103,24 +1211,58 @@ CONTAINS
END SUBROUTINE h5aread_char_7
- SUBROUTINE h5awrite_ptr(attr_id, mem_type_id, buf, hdferr)
- USE, INTRINSIC :: ISO_C_BINDING
- IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
- INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
- TYPE(C_PTR), INTENT(IN), TARGET :: buf
- INTEGER, INTENT(OUT) :: hdferr ! Error code
- hdferr = h5awrite_f_c(attr_id, mem_type_id, buf)
-
- END SUBROUTINE h5awrite_ptr
+!****s* H5A (F03)/h5aread_f_F03
+!
+! NAME
+! h5aread_f_F03
+!
+! PURPOSE
+! Reads an attribute.
+!
+! Inputs:
+! attr_id - Attribute identifier
+! memtype_id - Attribute datatype identifier (in memory)
+!
+! Outputs:
+! buf - Data buffer; may be a scalar or an array
+! hdferr - Returns 0 if successful and -1 if fails
+!
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces are added for
+! called C functions (it is needed for Windows
+! port). February 27, 2001
+!
+! dims parameter was added to make code portable;
+! Aprile 4, 2001
+!
+! Changed buf intent to INOUT to be consistant
+! with how the C functions handles it. The pg
+! compiler will return 0 if a buf value is not set.
+! February, 2008
+!
+! NOTES
+! This function is overloaded to write INTEGER,
+! REAL, DOUBLE PRECISION and CHARACTER buffers
+! up to 7 dimensions.
+! Fortran2003 Interface:
+!! SUBROUTINE h5aread_f(attr_id, memtype_id, buf, hdferr)
+!! INTEGER(HID_T) , INTENT(IN) :: attr_id
+!! INTEGER(HID_T) , INTENT(IN) :: memtype_id
+!! TYPE(C_PTR) , INTENT(INOUT) :: buf
+!! INTEGER , INTENT(OUT) :: hdferr
+!*****
SUBROUTINE h5aread_ptr(attr_id, mem_type_id, buf, hdferr)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id ! Attribute identifier
INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
- TYPE(C_PTR), INTENT(IN), TARGET :: buf
+ TYPE(C_PTR), INTENT(INOUT), TARGET :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
hdferr = h5aread_f_c(attr_id, mem_type_id, buf)