summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5O.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5O.f90')
-rw-r--r--fortran/test/tH5O.f9022
1 files changed, 14 insertions, 8 deletions
diff --git a/fortran/test/tH5O.f90 b/fortran/test/tH5O.f90
index ea91631..8672e3c 100644
--- a/fortran/test/tH5O.f90
+++ b/fortran/test/tH5O.f90
@@ -26,13 +26,17 @@
! test_h5o, test_h5o_link, test_h5o_plist
!
!*****
+MODULE TH5O
+
+CONTAINS
SUBROUTINE test_h5o(cleanup, total_error)
USE HDF5 ! This module contains all necessary modules
+ USE TH5_MISC
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(INOUT) :: total_error
INTEGER :: error
CALL test_h5o_plist(total_error) ! Test object creation properties
@@ -54,9 +58,10 @@ END SUBROUTINE test_h5o
SUBROUTINE test_h5o_link(total_error)
USE HDF5 ! This module contains all necessary modules
+ USE TH5_MISC
IMPLICIT NONE
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(INOUT) :: total_error
INTEGER(HID_T) :: file_id
INTEGER(HID_T) :: group_id
@@ -66,7 +71,6 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER(HID_T) :: fapl_id
INTEGER(HID_T) :: lcpl_id
INTEGER(HID_T) :: ocpypl_id
- INTEGER(HID_T) :: mem_space_id, file_space_id, xfer_prp
CHARACTER(LEN=11), PARAMETER :: TEST_FILENAME = 'TestFile.h5'
INTEGER, PARAMETER :: TEST6_DIM1 = 2, TEST6_DIM2 = 5
!EP INTEGER(HSIZE_T), DIMENSION(1:2), PARAMETER :: dims = (/TEST6_DIM1,TEST6_DIM2/)
@@ -74,11 +78,11 @@ SUBROUTINE test_h5o_link(total_error)
!EP INTEGER, DIMENSION(1:TEST6_DIM1,1:TEST6_DIM2) :: wdata, rdata
INTEGER, DIMENSION(TEST6_DIM1,TEST6_DIM2) :: wdata, rdata
- INTEGER, PARAMETER :: TRUE = 1, FALSE = 0
+ INTEGER, PARAMETER :: TRUE = 1
LOGICAL :: committed ! /* Whether the named datatype is committed
- INTEGER :: i, n, j
+ INTEGER :: i, j
INTEGER :: error ! /* Value returned from API calls
CHARACTER(LEN=14) :: NAME_DATATYPE_SIMPLE="H5T_NATIVE_INT"
@@ -91,8 +95,7 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER , PARAMETER :: dim0 = 4
INTEGER(HSIZE_T), DIMENSION(1:1) :: dims2 = (/dim0/) ! size read/write buffer
- INTEGER , DIMENSION(1:dim0) :: wdata2, & ! Write buffer
- rdata2 ! Read buffer
+ INTEGER , DIMENSION(1:dim0) :: wdata2 ! Write buffer
LOGICAL :: link_exists
CHARACTER(LEN=8) :: chr_exact
CHARACTER(LEN=10) :: chr_lg
@@ -576,9 +579,10 @@ END SUBROUTINE test_h5o_link
SUBROUTINE test_h5o_plist(total_error)
USE HDF5 ! This module contains all necessary modules
+ USE TH5_MISC
IMPLICIT NONE
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(INOUT) :: total_error
INTEGER(hid_t) :: fid ! HDF5 File ID
INTEGER(hid_t) :: grp, dset, dtype, dspace ! Object identifiers
@@ -789,3 +793,5 @@ SUBROUTINE test_h5o_plist(total_error)
CALL check("H5Pclose_f", error, total_error)
END SUBROUTINE test_h5o_plist
+
+END MODULE TH5O