summaryrefslogtreecommitdiffstats
path: root/hl/fortran/test
diff options
context:
space:
mode:
Diffstat (limited to 'hl/fortran/test')
-rw-r--r--hl/fortran/test/tstds.F9036
-rw-r--r--hl/fortran/test/tstlite.F9016
-rw-r--r--hl/fortran/test/tsttable.F9014
3 files changed, 33 insertions, 33 deletions
diff --git a/hl/fortran/test/tstds.F90 b/hl/fortran/test/tstds.F90
index 387f524..e0335b6 100644
--- a/hl/fortran/test/tstds.F90
+++ b/hl/fortran/test/tstds.F90
@@ -46,7 +46,7 @@ SUBROUTINE write_test_status( test_result)
IF (test_result .EQ. 0) THEN
error_string = success
ENDIF
-
+
WRITE(*, fmt = '(T34, A)') error_string
END SUBROUTINE write_test_status
@@ -66,7 +66,7 @@ SUBROUTINE test_testds(err)
IMPLICIT NONE
- INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
+ INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
INTEGER, PARAMETER :: DIM_DATA = 12
INTEGER, PARAMETER :: DIM1_SIZE = 3
INTEGER, PARAMETER :: DIM2_SIZE = 4
@@ -82,13 +82,13 @@ SUBROUTINE test_testds(err)
INTEGER(hid_t) :: fid ! file ID
INTEGER(hid_t) :: did ! dataset ID
INTEGER(hid_t) :: dsid ! DS dataset ID
- INTEGER :: rankds = 1 ! rank of DS dataset
- INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of DATA dataset
- INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! DATA of DATA dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
- REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! DATA of DS 1 dataset
- INTEGER, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! DATA of DS 2 dataset
+ INTEGER :: rankds = 1 ! rank of DS dataset
+ INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of DATA dataset
+ INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! DATA of DATA dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
+ REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! DATA of DS 1 dataset
+ INTEGER, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! DATA of DS 2 dataset
INTEGER :: err
INTEGER :: num_scales
INTEGER(size_t) :: name_len
@@ -107,7 +107,7 @@ SUBROUTINE test_testds(err)
CALL H5Fcreate_f("tstds.h5",H5F_ACC_TRUNC_F, fid, err)
IF(err.LT.0) RETURN
- ! make a dataset
+ ! make a dataset
CALL H5LTmake_dataset_int_f(fid,DSET_NAME,rank,dims,buf, err)
IF(err.LT.0) RETURN
@@ -185,11 +185,11 @@ SUBROUTINE test_testds(err)
RETURN
ENDIF
CALL write_test_status(err)
-
+
!-------------------------------------------------------------------------
! set the DS_1_NAME dimension scale to DSET_NAME at dimension 0
!-------------------------------------------------------------------------
-
+
CALL test_begin(' Test Setting Dimension Scale ')
CALL H5DSset_scale_f(dsid, err, "Dimension Scale Set 1")
@@ -245,15 +245,15 @@ SUBROUTINE test_testds(err)
CALL write_test_status(err)
RETURN
ENDIF
-
+
! close DS id
CALL H5Dclose_f(dsid, err)
IF(err.LT.0) RETURN
-
+
!-------------------------------------------------------------------------
! attach the DS_2_NAME dimension scale to DSET_NAME
!-------------------------------------------------------------------------
-
+
! get the DS dataset id
CALL H5Dopen_f(fid, DS_2_NAME, dsid, err)
IF(err.LT.0) RETURN
@@ -301,7 +301,7 @@ SUBROUTINE test_testds(err)
ENDIF
! Test label where character length is to small
-
+
label_len = 5
label = ''
CALL H5DSget_label_f(did, DIM2, label(1:label_len), label_len, err)
@@ -341,7 +341,7 @@ SUBROUTINE test_testds(err)
CALL H5Dclose_f(dsid, err)
IF(err.LT.0) RETURN
- ! close file
+ ! close file
CALL H5Fclose_f(fid, err)
IF(err.LT.0) RETURN
@@ -352,7 +352,7 @@ END MODULE TSTDS_TESTS
PROGRAM test_ds
USE TSTDS_TESTS ! module for testing dataset routines
-
+
IMPLICIT NONE
INTEGER :: err
diff --git a/hl/fortran/test/tstlite.F90 b/hl/fortran/test/tstlite.F90
index 673807b..071bd3f 100644
--- a/hl/fortran/test/tstlite.F90
+++ b/hl/fortran/test/tstlite.F90
@@ -635,7 +635,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -660,7 +660,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -685,7 +685,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -1356,7 +1356,7 @@ CONTAINS
TYPE(hvl_t), DIMENSION(1:2), TARGET :: rdata ! Pointer to vlen structures
INTEGER(hsize_t), DIMENSION(1:1) :: dims_vl = (/2/)
INTEGER, DIMENSION(:), POINTER :: ptr_r
- INTEGER(HID_T) :: type_id
+ INTEGER(HID_T) :: type_id
!
! Initialize FORTRAN predefined datatypes.
@@ -1911,7 +1911,7 @@ CONTAINS
STOP
ENDIF
- !
+ !
! ** Test reading a string that was created with a C program **
!
@@ -1923,7 +1923,7 @@ CONTAINS
!!$ !
!!$ IF ( bufr_c .NE. buf_c ) THEN
!!$ PRINT *, 'read buffer differs from write buffer'
-!!$ PRINT *, bufr1, ' and ', buf_c
+!!$ PRINT *, bufr1, ' and ', buf_c
!!$ STOP
!!$ ENDIF
!!$ !
@@ -1936,9 +1936,9 @@ CONTAINS
!!$ !
!!$ IF ( buf_c(1:16) .NE. bufr_c_lg(1:16) .AND. bufr_c_lg(17:18) .NE. ' ' ) THEN
!!$ PRINT *, 'larger read buffer differs from write buffer'
-!!$ PRINT *, buf_c, ' and ', bufr_c_lg
+!!$ PRINT *, buf_c, ' and ', bufr_c_lg
!!$ STOP
-!!$ ENDIF
+!!$ ENDIF
!!$ CALL h5fclose_f(file_id1, errcode)
diff --git a/hl/fortran/test/tsttable.F90 b/hl/fortran/test/tsttable.F90
index 840d33d..55cdbf0 100644
--- a/hl/fortran/test/tsttable.F90
+++ b/hl/fortran/test/tsttable.F90
@@ -58,7 +58,7 @@ SUBROUTINE test_table1()
USE TSTTABLE ! module for testing table support routines
IMPLICIT NONE
-
+
CHARACTER(len=8), PARAMETER :: filename = "f1tab.h5" ! File name
CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name
INTEGER(HID_T) :: file_id ! File identifier
@@ -106,7 +106,7 @@ SUBROUTINE test_table1()
SIZEOF_X = SIZEOF(bufd(1))
#endif
- ! If Fortran DOUBLE PRECISION and C DOUBLE sizeofs don't match then disable
+ ! If Fortran DOUBLE PRECISION and C DOUBLE sizeofs don't match then disable
! creating a DOUBLE RECISION field, and instead create a REAL field. This
! is needed to handle when DOUBLE PRECISION is promoted via a compiler flag.
Exclude_double = .FALSE.
@@ -511,7 +511,7 @@ SUBROUTINE test_table1()
IF ( maxlen .NE. 8 ) THEN
WRITE(*,'(/,5X,"H5TBGET_FIELD_INFO_F: INCORRECT MAXIMUM CHARACTER LENGTH OF THE FIELD NAMES")')
- WRITE(*,'(5X,"RETURNED VALUE = ", I0, ", CORRECT VALUE = ", I0)') maxlen, 8
+ WRITE(*,'(5X,"RETURNED VALUE = ", I0, ", CORRECT VALUE = ", I0)') maxlen, 8
STOP
ENDIF
@@ -552,7 +552,7 @@ SUBROUTINE test_table2()
USE TSTTABLE ! module for testing table support routines
IMPLICIT NONE
-
+
INTEGER, PARAMETER :: i8 = SELECTED_INT_KIND(9) !should map to INTEGER*4 on most modern processors
INTEGER, PARAMETER :: i16 = SELECTED_INT_KIND(9) ! (18) !should map to INTEGER*8 on most modern processors
INTEGER, PARAMETER :: sp = SELECTED_REAL_KIND(5) ! This should map to REAL*4 on most modern processors
@@ -605,7 +605,7 @@ SUBROUTINE test_table2()
test_txt = "Testing H5TBread_table_f and H5TBmake_table_f (F2003)"
CALL test_begin(test_txt)
-
+
! Define an array of Particles
p_data(1:nrecords) = (/ &
particle_t("zero ",0_i8,0_i16,0.0_sp,0.0_dp), &
@@ -641,7 +641,7 @@ SUBROUTINE test_table2()
/)
#endif
- dst_offset(1:nfields) = (/ &
+ dst_offset(1:nfields) = (/ &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%name(1:1))), &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%lati)), &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%long)), &
@@ -693,7 +693,7 @@ SUBROUTINE test_table2()
f_ptr1 = C_LOC(p_data(1)%name(1:1))
f_ptr2 = C_NULL_PTR
-
+
CALL h5tbmake_table_f("Table Title",file_id, table_name, nfields, nrecords, &
dst_size, field_names, dst_offset, field_type, &
chunk_size, f_ptr2, compress, f_ptr1, errcode )