summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Dff.F90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Dff.F90')
-rw-r--r--fortran/src/H5Dff.F9050
1 files changed, 25 insertions, 25 deletions
diff --git a/fortran/src/H5Dff.F90 b/fortran/src/H5Dff.F90
index ec73f60..7128698 100644
--- a/fortran/src/H5Dff.F90
+++ b/fortran/src/H5Dff.F90
@@ -86,7 +86,7 @@
#include <H5config_f.inc>
MODULE H5D
-
+
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR, C_CHAR
USE H5GLOBAL
@@ -1088,7 +1088,7 @@ CONTAINS
SUBROUTINE h5dget_offset_f(dset_id, offset, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id
- INTEGER(HADDR_T), INTENT(OUT) :: offset
+ INTEGER(HADDR_T), INTENT(OUT) :: offset
INTEGER, INTENT(OUT) :: hdferr
!*****
INTERFACE
@@ -1100,7 +1100,7 @@ CONTAINS
END INTERFACE
offset = h5dget_offset(dset_id)
-
+
hdferr = 0 ! never returns a function error because C API never returns a function error.
END SUBROUTINE h5dget_offset_f
@@ -1164,7 +1164,7 @@ CONTAINS
! plist_id - Dataset access property list identifier
! hdferr - Returns 0 if successful and -1 if fails
!
-! AUTHOR
+! AUTHOR
! M. Scot Breitenfeld
! April 13, 2009
!
@@ -1172,8 +1172,8 @@ CONTAINS
SUBROUTINE h5dget_access_plist_f(dset_id, plist_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id
- INTEGER(HID_T), INTENT(OUT) :: plist_id
- INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(HID_T), INTENT(OUT) :: plist_id
+ INTEGER , INTENT(OUT) :: hdferr
!*****
INTERFACE
INTEGER FUNCTION h5dget_access_plist_c(dset_id, plist_id) BIND(C,NAME='h5dget_access_plist_c')
@@ -1183,9 +1183,9 @@ CONTAINS
INTEGER(HID_T), INTENT(OUT) :: plist_id
END FUNCTION h5dget_access_plist_c
END INTERFACE
-
+
hdferr = h5dget_access_plist_c(dset_id, plist_id)
-
+
END SUBROUTINE h5dget_access_plist_f
@@ -1295,7 +1295,7 @@ CONTAINS
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
-
+
CALL h5dwrite_char_scalar_fix(dset_id, mem_type_id, buf, LEN(buf), dims, hdferr, &
mem_space_id, file_space_id, xfer_prp)
@@ -1483,17 +1483,17 @@ CONTAINS
!****s* H5D (F03)/h5dwrite_f_F03
!
-! NAME
+! NAME
! h5dwrite_f_F03
!
! PURPOSE
-! Writes raw data from a dataset into a buffer.
+! Writes raw data from a dataset into a buffer.
!
! Inputs:
! dset_id - Identifier of the dataset to write to.
! mem_type_id - Identifier of the memory datatype.
! buf - Buffer with data to be written to the file.
-!
+!
! Outputs:
! hdferr - Returns 0 if successful and -1 if fails
!
@@ -1548,16 +1548,16 @@ CONTAINS
!****s* H5D (F03)/h5dread_f_F03
!
-! NAME
+! NAME
! h5dread_f_F03
!
! PURPOSE
-! Reads raw data from a dataset into a buffer.
+! Reads raw data from a dataset into a buffer.
!
! Inputs:
! dset_id - Identifier of the dataset read from.
! mem_type_id - Identifier of the memory datatype.
-!
+!
! Outputs:
! buf - Buffer to receive data read from file.
! hdferr - Returns 0 if successful and -1 if fails
@@ -1612,10 +1612,10 @@ CONTAINS
END SUBROUTINE h5dread_ptr
!
-! NAME
+! NAME
! h5dfill_integer
!
-! PURPOSE
+! PURPOSE
! Fills dataspace elements with a fill value in a memory buffer.
! Only INTEGER, CHARACTER, REAL and DOUBLE PRECISION datatypes
! of the fillvalues and buffers are supported. Buffer and fillvalue
@@ -1786,10 +1786,10 @@ CONTAINS
END SUBROUTINE h5dfill_c_long_double
#endif
!
-! NAME
+! NAME
! h5dfill_char
!
-! PURPOSE
+! PURPOSE
! Fills dataspace elements with a fill value in a memory buffer.
! Only INTEGER, CHARACTER, REAL and DOUBLE PRECISION datatypes
! of the fillvalues and buffers are supported. Buffer and fillvalue
@@ -1835,15 +1835,15 @@ CONTAINS
! NAME
! h5dvlen_reclaim_f
!
-! PURPOSE
-! Reclaims VL datatype memory buffers.
+! PURPOSE
+! Reclaims VL datatype memory buffers.
!
! Inputs:
!
-! type_id - Identifier of the datatype.
-! space_id - Identifier of the dataspace.
-! plist_id - Identifier of the property list used to create the buffer.
-! buf - Pointer to the buffer to be reclaimed.
+! type_id - Identifier of the datatype.
+! space_id - Identifier of the dataspace.
+! plist_id - Identifier of the property list used to create the buffer.
+! buf - Pointer to the buffer to be reclaimed.
!
! Outputs:
! hdferr - Returns 0 if successful and -1 if fails