summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5VL.f90
diff options
context:
space:
mode:
authorQuincey Koziol <koziol@hdfgroup.org>2010-01-30 04:29:13 (GMT)
committerQuincey Koziol <koziol@hdfgroup.org>2010-01-30 04:29:13 (GMT)
commitfd70b2afa883f94718ffb7f4f33d104d76e3fe0a (patch)
treec1add8db2a4848202d86a9b274bfaf8c7b80e961 /fortran/test/tH5VL.f90
parent35b0159a0a5f1f4b80e305204ea51a742b052403 (diff)
downloadhdf5-fd70b2afa883f94718ffb7f4f33d104d76e3fe0a.zip
hdf5-fd70b2afa883f94718ffb7f4f33d104d76e3fe0a.tar.gz
hdf5-fd70b2afa883f94718ffb7f4f33d104d76e3fe0a.tar.bz2
[svn-r18197] Description:
Trim trailing whitespace from source code files with this command: find . \( -name "*.[ch]" -or -name "*.cpp" -or -name "*.f90" \) -print |xargs -n 1 sed -i "" 's/[[:blank:]]*$//' Tested on: None - eyeballed only
Diffstat (limited to 'fortran/test/tH5VL.f90')
-rw-r--r--fortran/test/tH5VL.f90126
1 files changed, 63 insertions, 63 deletions
diff --git a/fortran/test/tH5VL.f90 b/fortran/test/tH5VL.f90
index 13f2af1..3afd025 100644
--- a/fortran/test/tH5VL.f90
+++ b/fortran/test/tH5VL.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,34 +11,34 @@
! 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 Variable_length datatypes
!
!
!
SUBROUTINE vl_test_integer(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=7), PARAMETER :: filename = "VLtypes" ! File name
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=5), PARAMETER :: dsetname = "VLint" ! Dataset name
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dset_id ! Dataset identifier
INTEGER(HID_T) :: dspace_id ! Dataspace identifier
INTEGER(HID_T) :: vltype_id ! Datatype identifier
INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/6/) ! Dataset dimensions
- INTEGER(SIZE_T), DIMENSION(6) :: len ! Elements lengths
- INTEGER(SIZE_T), DIMENSION(6) :: len_out
+ INTEGER(SIZE_T), DIMENSION(6) :: len ! Elements lengths
+ INTEGER(SIZE_T), DIMENSION(6) :: len_out
INTEGER :: rank = 1 ! Dataset rank
INTEGER, DIMENSION(5,6) :: vl_int_data ! Data buffers
@@ -52,14 +52,14 @@
!
! Initialize the vl_int_data array.
!
- do i = 1, 6
- do j = 1, 5
+ do i = 1, 6
+ do j = 1, 5
vl_int_data(j,i) = -100
end do
end do
- do i = 2, 6
- do j = 1, i-1
+ do i = 2, 6
+ do j = 1, i-1
vl_int_data(j,i) = i-1
end do
end do
@@ -71,7 +71,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"
@@ -81,7 +81,7 @@
CALL check("h5fcreate_f", error, total_error)
- !
+ !
! Create the dataspace.
!
CALL h5screate_simple_f(rank, dims, dspace_id, error)
@@ -105,13 +105,13 @@
CALL check("h5dwrite_int_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)
- !
+ !
! Close the file.
!
CALL h5fclose_f(file_id, error)
@@ -124,11 +124,11 @@
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)
-
+
CALL h5dvlen_get_max_len_f(dset_id, vltype_id, dspace_id, max_len, error)
CALL check("h5dvlen_get_max_len_f", error, total_error)
if(max_len .ne. data_dims(1)) then
@@ -168,37 +168,37 @@
CALL h5sclose_f(dspace_id, error)
CALL check("h5sclose_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 vl_test_integer
SUBROUTINE vl_test_real(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=8), PARAMETER :: filename = "VLtypesR" ! File name
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=6), PARAMETER :: dsetname = "VLreal" ! Dataset name
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dset_id ! Dataset identifier
INTEGER(HID_T) :: dspace_id ! Dataspace identifier
INTEGER(HID_T) :: vltype_id ! Datatype identifier
INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/6/) ! Dataset dimensions
- INTEGER(SIZE_T), DIMENSION(6) :: len ! Elements lengths
- INTEGER(SIZE_T), DIMENSION(6) :: len_out
+ INTEGER(SIZE_T), DIMENSION(6) :: len ! Elements lengths
+ INTEGER(SIZE_T), DIMENSION(6) :: len_out
INTEGER :: rank = 1 ! Dataset rank
REAL, DIMENSION(5,6) :: vl_real_data ! Data buffers
@@ -214,14 +214,14 @@
!
! Initialize the vl_int_data array.
!
- do i = 1, 6
- do j = 1, 5
+ do i = 1, 6
+ do j = 1, 5
vl_real_data(j,i) = -100.
end do
end do
- do i = 2, 6
- do j = 1, i-1
+ do i = 2, 6
+ do j = 1, i-1
vl_real_data(j,i) = i-1
end do
end do
@@ -233,7 +233,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"
@@ -243,7 +243,7 @@
CALL check("h5fcreate_f", error, total_error)
- !
+ !
! Create the dataspace.
!
CALL h5screate_simple_f(rank, dims, dspace_id, error)
@@ -276,13 +276,13 @@
CALL check("h5dwrite_vl_real_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)
- !
+ !
! Close the file.
!
CALL h5fclose_f(file_id, error)
@@ -295,11 +295,11 @@
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)
-
+
CALL h5dvlen_get_max_len_f(dset_id, vltype_id, dspace_id, max_len, error)
CALL check("h5dvlen_get_max_len_f", error, total_error)
if(max_len .ne. data_dims(1)) then
@@ -339,36 +339,36 @@
CALL h5sclose_f(dspace_id, error)
CALL check("h5sclose_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 vl_test_real
SUBROUTINE vl_test_string(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=8), PARAMETER :: filename = "VLtypesS" ! File name
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=9), PARAMETER :: dsetname = "VLstrings" ! Dataset name
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dset_id ! Dataset identifier
INTEGER(HID_T) :: dspace_id ! Dataspace identifier
INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/4/) ! Dataset dimensions
- INTEGER(SIZE_T), DIMENSION(4) :: str_len ! Elements lengths
- INTEGER(SIZE_T), DIMENSION(4) :: str_len_out
+ INTEGER(SIZE_T), DIMENSION(4) :: str_len ! Elements lengths
+ INTEGER(SIZE_T), DIMENSION(4) :: str_len_out
INTEGER :: rank = 1 ! Dataset rank
CHARACTER(LEN=10), DIMENSION(4) :: string_data ! Array of strings
@@ -388,14 +388,14 @@
string_data(2) = 'a fortran '
str_len(2) = 10
string_data(3) = 'strings '
- str_len(3) = 8
+ str_len(3) = 8
string_data(4) = 'test. '
- str_len(4) = 5
+ str_len(4) = 5
!
! 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"
@@ -405,7 +405,7 @@
CALL check("h5fcreate_f", error, total_error)
- !
+ !
! Create the dataspace.
!
CALL h5screate_simple_f(rank, dims, dspace_id, error)
@@ -437,13 +437,13 @@
CALL check("h5dwrite_string_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)
- !
+ !
! Close the file.
!
CALL h5fclose_f(file_id, error)
@@ -456,7 +456,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)
@@ -471,13 +471,13 @@
total_error=total_error + 1
write(*,*) 'Returned string length is incorrect'
goto 100
- endif
+ endif
if(string_data(1)(1:str_len(i)) .ne. string_data_out(1)(1:str_len(i))) then
write(*,*) ' Returned string is wrong'
total_error = total_error + 1
endif
-100 continue
-
+100 continue
+
!
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f", error, total_error)
@@ -488,14 +488,14 @@
CALL h5sclose_f(dspace_id, error)
CALL check("h5sclose_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 vl_test_string