summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5F.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5F.f90')
-rw-r--r--fortran/test/tH5F.f9027
1 files changed, 19 insertions, 8 deletions
diff --git a/fortran/test/tH5F.f90 b/fortran/test/tH5F.f90
index a7a1f70..6b62aea 100644
--- a/fortran/test/tH5F.f90
+++ b/fortran/test/tH5F.f90
@@ -1,4 +1,4 @@
-!****h* root/fortran/test/tH5F.f90
+!***rh* root/fortran/test/tH5F.f90
!
! NAME
! tH5F.f90
@@ -31,11 +31,19 @@
! and another file with a dataset. Mounting is used to
! access the dataset from the second file as a member of a group
! in the first file.
+
+
+
+MODULE TH5F
+
+CONTAINS
+
SUBROUTINE mountingtest(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
!
!the respective filename is "mount1.h5" and "mount2.h5"
@@ -241,7 +249,6 @@
do i = 1, NX
do j = 1, NY
IF (data_out(i,j) .NE. data_in(i, j)) THEN
- write(*, *) "mounting test error occured"
END IF
end do
end do
@@ -289,9 +296,10 @@
SUBROUTINE reopentest(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
!
CHARACTER(LEN=6), PARAMETER :: filename = "reopen"
@@ -475,9 +483,10 @@
SUBROUTINE plisttest(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
!
!file names are "plist1.h5" and "plist2.h5"
@@ -574,9 +583,10 @@
SUBROUTINE file_close(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
!
@@ -702,10 +712,11 @@
SUBROUTINE file_space(filename, cleanup, total_error)
USE HDF5 ! This module contains all necessary modules
+ USE TH5_MISC
IMPLICIT NONE
CHARACTER(*), INTENT(IN) :: filename
LOGICAL, INTENT(IN) :: cleanup
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(INOUT) :: total_error
INTEGER :: error
!
CHARACTER(LEN=3), PARAMETER :: grpname = "grp"
@@ -770,4 +781,4 @@
END SUBROUTINE file_space
-
+END MODULE TH5F