summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5D.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5D.f90')
-rw-r--r--fortran/test/tH5D.f90110
1 files changed, 55 insertions, 55 deletions
diff --git a/fortran/test/tH5D.f90 b/fortran/test/tH5D.f90
index e704db2..56e82f4 100644
--- a/fortran/test/tH5D.f90
+++ b/fortran/test/tH5D.f90
@@ -1,4 +1,4 @@
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
! All rights reserved. *
@@ -11,10 +11,10 @@
! is linked from the top-level documents page. It can also be found at *
! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
! access to either file, you may request a copy from help@hdfgroup.org. *
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+!
!
!
-!
! Testing Dataset Interface functionality.
!
!
@@ -23,20 +23,20 @@
! h5dread_f, and h5dwrite_f
!
SUBROUTINE datasettest(cleanup, total_error)
- USE HDF5 ! This module contains all necessary modules
+ USE HDF5 ! This module contains all necessary modules
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(OUT) :: total_error
CHARACTER(LEN=5), PARAMETER :: filename = "dsetf" ! File name
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=4), PARAMETER :: dsetname = "dset" ! Dataset name
CHARACTER(LEN=9), PARAMETER :: null_dsetname = "null_dset" ! Dataset name
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
- INTEGER(HID_T) :: null_dset ! Null dataset identifier
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dset_id ! Dataset identifier
+ INTEGER(HID_T) :: null_dset ! Null dataset identifier
INTEGER(HID_T) :: dspace_id ! Dataspace identifier
INTEGER(HID_T) :: null_dspace ! Null dataspace identifier
INTEGER(HID_T) :: dtype_id ! Datatype identifier
@@ -65,7 +65,7 @@
!
! Create a new file using default properties.
- !
+ !
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
if (error .ne. 0) then
write(*,*) "Cannot modify filename"
@@ -75,12 +75,12 @@
CALL check("h5fcreate_f", error, total_error)
- !
+ !
! Create the dataspace.
!
CALL h5screate_simple_f(rank, dims, dspace_id, error)
CALL check("h5screate_simple_f", error, total_error)
- !
+ !
! Create null dataspace.
!
CALL h5screate_f(H5S_NULL_F, null_dspace, error)
@@ -94,7 +94,7 @@
dset_id, error)
CALL check("h5dcreate_f", error, total_error)
!
- ! Create the null dataset.
+ ! Create the null dataset.
!
CALL h5dcreate_f(file_id, null_dsetname, H5T_NATIVE_INTEGER, null_dspace, &
null_dset, error)
@@ -104,20 +104,20 @@
! Write the dataset.
!
data_dims(1) = 4
- data_dims(2) = 6
+ data_dims(2) = 6
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, data_dims, error)
CALL check("h5dwrite_f", error, total_error)
!
! Write null dataset. Nothing can be written.
- !
- null_data_dim(1) = 1
+ !
+ null_data_dim(1) = 1
CALL h5dwrite_f(null_dset, H5T_NATIVE_INTEGER, null_dset_data, null_data_dim, error)
CALL check("h5dwrite_f", error, total_error)
- !
+ !
! End access to the dataset and release resources used by it.
- !
+ !
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f", error, total_error)
CALL h5dclose_f(null_dset, error)
@@ -131,7 +131,7 @@
CALL h5sclose_f(null_dspace, error)
CALL check("h5sclose_f", error, total_error)
- !
+ !
! Close the file.
!
CALL h5fclose_f(file_id, error)
@@ -144,7 +144,7 @@
CALL check("h5fopen_f", error, total_error)
!
- ! Open the existing dataset.
+ ! Open the existing dataset.
!
CALL h5dopen_f(file_id, dsetname, dset_id, error)
CALL check("h5dopen_f", error, total_error)
@@ -152,13 +152,13 @@
CALL check("h5dopen_f", error, total_error)
!
- ! Get the dataset type.
+ ! Get the dataset type.
!
CALL h5dget_type_f(dset_id, dtype_id, error)
CALL check("h5dget_type_f", error, total_error)
!
- ! Get the data space.
+ ! Get the data space.
!
CALL h5dget_space_f(dset_id, dspace_id, error)
CALL check("h5dget_space_f", error, total_error)
@@ -176,26 +176,26 @@
!
!Compare the data.
- !
+ !
do i = 1, 4
do j = 1, 6
- IF (data_out(i,j) .NE. dset_data(i, j)) THEN
+ IF (data_out(i,j) .NE. dset_data(i, j)) THEN
write(*, *) "dataset test error occured"
write(*,*) "data read is not the same as the data writen"
END IF
- end do
+ end do
end do
!
! Check if no change to null_dset_data
!
- IF (null_dset_data .NE. 1) THEN
+ IF (null_dset_data .NE. 1) THEN
write(*, *) "null dataset test error occured"
END IF
- !
+ !
! End access to the dataset and release resources used by it.
- !
+ !
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f", error, total_error)
CALL h5dclose_f(null_dset, error)
@@ -212,14 +212,14 @@
!
CALL h5tclose_f(dtype_id, error)
CALL check("h5tclose_f", error, total_error)
- !
+ !
! Close the file.
!
CALL h5fclose_f(file_id, error)
CALL check("h5fclose_f", error, total_error)
if(cleanup) CALL h5_cleanup_f(filename, H5P_DEFAULT_F, error)
CALL check("h5_cleanup_f", error, total_error)
-
+
RETURN
END SUBROUTINE datasettest
@@ -228,11 +228,11 @@
!
SUBROUTINE extenddsettest(cleanup, total_error)
- USE HDF5 ! This module contains all necessary modules
+ USE HDF5 ! This module contains all necessary modules
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
- INTEGER, INTENT(OUT) :: total_error
+ INTEGER, INTENT(OUT) :: total_error
!
!the dataset is stored in file "extf.h5"
@@ -250,11 +250,11 @@
!
INTEGER :: RANK = 2
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
- INTEGER(HID_T) :: dataspace ! Dataspace identifier
- INTEGER(HID_T) :: memspace ! memory Dataspace identifier
- INTEGER(HID_T) :: crp_list ! dataset creatation property identifier
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dset_id ! Dataset identifier
+ INTEGER(HID_T) :: dataspace ! Dataspace identifier
+ INTEGER(HID_T) :: memspace ! memory Dataspace identifier
+ INTEGER(HID_T) :: crp_list ! dataset creatation property identifier
!
!dataset dimensions at creation time
@@ -262,44 +262,44 @@
INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/3,3/)
!
- !data dimensions
+ !data dimensions
!
INTEGER(HSIZE_T), DIMENSION(2) :: dims1 = (/10,3/)
!
!Maximum dimensions
!
- INTEGER(HSIZE_T), DIMENSION(2) :: maxdims
+ INTEGER(HSIZE_T), DIMENSION(2) :: maxdims
!
- !data arrays for reading and writing
+ !data arrays for reading and writing
!
INTEGER, DIMENSION(10,3) :: data_in, data_out
!
- !Size of data in the file
+ !Size of data in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: size
!
- !general purpose integer
+ !general purpose integer
!
INTEGER :: i, j
!
- !flag to check operation success
+ !flag to check operation success
!
- INTEGER :: error
+ INTEGER :: error
!
!Variables used in reading data back
- !
+ !
INTEGER(HSIZE_T), DIMENSION(2) :: dimsr, maxdimsr
INTEGER :: rankr
INTEGER(HSIZE_T), DIMENSION(2) :: data_dims
!
- !data initialization
+ !data initialization
!
do i = 1, 10
do j = 1, 3
@@ -310,12 +310,12 @@
!
!Initialize FORTRAN predifined datatypes
!
-! CALL h5init_types_f(error)
+! CALL h5init_types_f(error)
! CALL check("h5init_types_f",error,total_error)
!
!Create a new file using default properties.
- !
+ !
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
if (error .ne. 0) then
write(*,*) "Cannot modify filename"
@@ -361,8 +361,8 @@
!
!Extend the dataset. Dataset becomes 10 x 3.
!
- size(1) = 10;
- size(2) = 3;
+ size(1) = 10;
+ size(2) = 3;
CALL h5dextend_f(dset_id, size, error)
CALL check("h5dextend_f",error,total_error)
@@ -451,7 +451,7 @@
CALL check("h5screate_simple_f",error,total_error)
!
- !Read data
+ !Read data
!
CALL H5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, &
memspace, dataspace)
@@ -460,14 +460,14 @@
!
!Compare the data.
- !
+ !
do i = 1, dims1(1)
do j = 1, dims1(2)
- IF (data_out(i,j) .NE. data_in(i, j)) THEN
+ IF (data_out(i,j) .NE. data_in(i, j)) THEN
write(*, *) "extend dataset test error occured"
write(*, *) "read value is not the same as the written values"
END IF
- end do
+ end do
end do
!
@@ -503,6 +503,6 @@
CALL check("h5_cleanup_f", error, total_error)
RETURN
- END SUBROUTINE extenddsettest
+ END SUBROUTINE extenddsettest