summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5P_F03.F90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5P_F03.F90')
-rw-r--r--fortran/test/tH5P_F03.F90220
1 files changed, 110 insertions, 110 deletions
diff --git a/fortran/test/tH5P_F03.F90 b/fortran/test/tH5P_F03.F90
index 083c312..3e7c552 100644
--- a/fortran/test/tH5P_F03.F90
+++ b/fortran/test/tH5P_F03.F90
@@ -5,7 +5,7 @@
!
! FUNCTION
! Test FORTRAN HDF5 H5P APIs which are dependent on FORTRAN 2003
-! features.
+! features.
!
! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
@@ -40,35 +40,35 @@ MODULE test_genprop_cls_cb1_mod
USE HDF5
USE ISO_C_BINDING
IMPLICIT NONE
-
- TYPE, BIND(C) :: cop_cb_struct_ ! Struct for iterations
+
+ TYPE, BIND(C) :: cop_cb_struct_ ! Struct for iterations
INTEGER :: count
INTEGER(HID_T) :: id
END TYPE cop_cb_struct_
CONTAINS
-
+
INTEGER FUNCTION test_genprop_cls_cb1_f(list_id, create_data ) bind(C)
-
+
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN), VALUE :: list_id
-
+
TYPE(cop_cb_struct_) :: create_data
create_data%count = create_data%count + 1
create_data%id = list_id
test_genprop_cls_cb1_f = 0
-
+
END FUNCTION test_genprop_cls_cb1_f
END MODULE test_genprop_cls_cb1_mod
MODULE TH5P_F03
- USE HDF5
- USE TH5_MISC
+ USE HDF5
+ USE TH5_MISC
USE TH5_MISC_GEN
USE ISO_C_BINDING
@@ -89,7 +89,7 @@ CONTAINS
! * Modifications:
! *
! *-------------------------------------------------------------------------
-!
+!
SUBROUTINE test_create(total_error)
@@ -116,9 +116,9 @@ SUBROUTINE test_create(total_error)
!
! * Create a file.
- !
+ !
CALL h5fcreate_f(filename,H5F_ACC_TRUNC_F,file,error)
- CALL check("h5fcreate_f", error, total_error)
+ CALL check("h5fcreate_f", error, total_error)
CALL h5screate_simple_f(5, cur_size, space, error, cur_size)
CALL check("h5screate_simple_f", error, total_error)
@@ -129,7 +129,7 @@ SUBROUTINE test_create(total_error)
CALL h5pset_chunk_f(dcpl, 5, ch_size, error)
CALL check("h5pset_chunk_f",error, total_error)
- ! Create a compound datatype
+ ! Create a compound datatype
CALL h5tcreate_f(H5T_COMPOUND_F, H5_SIZEOF(fill_ctype), comp_type_id, error)
CALL check("h5tcreate_f", error, total_error)
h5off = H5OFFSETOF(C_LOC(fill_ctype), C_LOC(fill_ctype%a))
@@ -150,7 +150,7 @@ SUBROUTINE test_create(total_error)
CALL H5Pset_fill_time_f(dcpl, H5D_FILL_TIME_ALLOC_F, error)
CALL check("H5Pset_fill_time_f",error, total_error)
- ! Compound datatype test
+ ! Compound datatype test
f_ptr = C_LOC(fill_ctype)
@@ -205,7 +205,7 @@ SUBROUTINE test_create(total_error)
CALL h5fclose_f(file,error)
CALL check("h5fclose_f", error, total_error)
- ! Open the file and get the dataset fill value from each dataset
+ ! Open the file and get the dataset fill value from each dataset
CALL h5pcreate_f(H5P_FILE_ACCESS_F, fapl, error)
CALL check("h5pcreate_f",error, total_error)
@@ -252,7 +252,7 @@ SUBROUTINE test_create(total_error)
CALL h5fopen_f (FILENAME, H5F_ACC_RDONLY_F, file, error, fapl)
CALL check("h5fopen_f", error, total_error)
- ! Compound datatype test
+ ! Compound datatype test
CALL h5dopen_f(file, "dset9", dset9, error)
CALL check("h5dopen_f", error, total_error)
@@ -306,9 +306,9 @@ SUBROUTINE test_genprop_class_callback(total_error)
INTEGER, INTENT(INOUT) :: total_error
- INTEGER(hid_t) :: cid1, cid2 ! Generic Property class ID
- INTEGER(hid_t) :: lid1, lid2 ! Generic Property list ID
- INTEGER(size_t) :: nprops ! Number of properties in class
+ INTEGER(hid_t) :: cid1, cid2 ! Generic Property class ID
+ INTEGER(hid_t) :: lid1, lid2 ! Generic Property list ID
+ INTEGER(size_t) :: nprops ! Number of properties in class
TYPE(cop_cb_struct_), TARGET :: crt_cb_struct, cls_cb_struct
INTEGER :: CLASS1_NAME_SIZE = 7 ! length of class string
@@ -329,7 +329,7 @@ SUBROUTINE test_genprop_class_callback(total_error)
INTEGER :: PROP3_DEF_VALUE = 10
INTEGER :: PROP4_DEF_VALUE = 10
- INTEGER :: error ! Generic RETURN value
+ INTEGER :: error ! Generic RETURN value
LOGICAL :: flag ! for tests
f1 = C_FUNLOC(test_genprop_cls_cb1_f)
@@ -338,45 +338,45 @@ SUBROUTINE test_genprop_class_callback(total_error)
f2 = C_LOC(crt_cb_struct)
f6 = C_LOC(cls_cb_struct)
- ! Create a new generic class, derived from the root of the class hierarchy
+ ! Create a new generic class, derived from the root of the class hierarchy
CALL h5pcreate_class_f(h5p_ROOT_F, CLASS1_NAME, cid1, error, f1, f2, c_null_funptr, c_null_ptr, f5, f6)
CALL check("h5pcreate_class_f", error, total_error)
- ! Insert first property into class (with no callbacks)
+ ! Insert first property into class (with no callbacks)
CALL h5pregister_f(cid1, PROP1_NAME, PROP1_SIZE, PROP1_DEF_VALUE, error)
CALL check("h5pregister_f", error, total_error)
- ! Insert second property into class (with no callbacks)
+ ! Insert second property into class (with no callbacks)
CALL h5pregister_f(cid1, PROP2_NAME, PROP2_SIZE, PROP2_DEF_VALUE, error)
CALL check("h5pregister_f", error, total_error)
- ! Insert third property into class (with no callbacks)
+ ! Insert third property into class (with no callbacks)
CALL h5pregister_f(cid1, PROP3_NAME, PROP3_SIZE, PROP3_DEF_VALUE, error)
CALL check("h5pregister_f", error, total_error)
- ! Insert fourth property into class (with no callbacks)
+ ! Insert fourth property into class (with no callbacks)
CALL h5pregister_f(cid1, PROP4_NAME, PROP4_SIZE, PROP4_DEF_VALUE, error)
CALL check("h5pregister_f", error, total_error)
- ! Check the number of properties in class
+ ! Check the number of properties in class
CALL h5pget_nprops_f(cid1, nprops, error)
CALL check("h5pget_nprops_f", error, total_error)
CALL verify("h5pget_nprops_f", INT(nprops), 4, total_error)
- ! Initialize class callback structs
+ ! Initialize class callback structs
crt_cb_struct%count = 0
crt_cb_struct%id = -1
cls_cb_struct%count = 0
cls_cb_struct%id = -1
- ! Create a property list from the class
+ ! Create a property list from the class
CALL h5pcreate_f(cid1, lid1, error)
CALL check("h5pcreate_f", error, total_error)
- ! Get the list's class
+ ! Get the list's class
CALL H5Pget_class_f(lid1, cid2, error)
CALL check("H5Pget_class_f", error, total_error)
- ! Check that the list's class is correct
+ ! Check that the list's class is correct
CALL H5Pequal_f(cid2, cid1, flag, error)
CALL check("H5Pequal_f", error, total_error)
CALL verify("H5Pequal_f", flag, .TRUE., total_error)
@@ -389,41 +389,41 @@ SUBROUTINE test_genprop_class_callback(total_error)
WRITE(*,*) 'Class names do not match! name=',CLASS1_NAME_BUF, 'CLASS1_NAME=',CLASS1_NAME
total_error = total_error + 1
ENDIF
- ! Close class
+ ! Close class
CALL h5pclose_class_f(cid2, error)
CALL check("h5pclose_class_f", error, total_error)
- ! Verify that the creation callback occurred
+ ! Verify that the creation callback occurred
CALL verify("h5pcreate_f", crt_cb_struct%count, 1, total_error)
CALL verify("h5pcreate_f", crt_cb_struct%id, lid1, total_error)
- ! Check the number of properties in list
+ ! Check the number of properties in list
CALL h5pget_nprops_f(lid1,nprops, error)
CALL check("h5pget_nprops_f", error, total_error)
CALL verify("h5pget_nprops_f", INT(nprops), 4, total_error)
- ! Create another property list from the class
+ ! Create another property list from the class
CALL h5pcreate_f(cid1, lid2, error)
CALL check("h5pcreate_f", error, total_error)
- ! Verify that the creation callback occurred
+ ! Verify that the creation callback occurred
CALL verify("h5pcreate_f", crt_cb_struct%count, 2, total_error)
CALL verify("h5pcreate_f", crt_cb_struct%id, lid2, total_error)
- ! Check the number of properties in list
+ ! Check the number of properties in list
CALL h5pget_nprops_f(lid2,nprops, error)
CALL check("h5pget_nprops_f", error, total_error)
CALL verify("h5pget_nprops_f", INT(nprops), 4, total_error)
- ! Close first list
+ ! Close first list
CALL h5pclose_f(lid1, error);
CALL check("h5pclose_f", error, total_error)
- ! Verify that the close callback occurred
+ ! Verify that the close callback occurred
CALL verify("h5pcreate_f", cls_cb_struct%count, 1, total_error)
CALL verify("h5pcreate_f", cls_cb_struct%id, lid1, total_error)
- ! Close second list
+ ! Close second list
CALL h5pclose_f(lid2, error);
CALL check("h5pclose_f", error, total_error)
@@ -431,7 +431,7 @@ SUBROUTINE test_genprop_class_callback(total_error)
CALL verify("h5pcreate_f", cls_cb_struct%count, 2, total_error)
CALL verify("h5pcreate_f", cls_cb_struct%id, lid2, total_error)
- ! Close class
+ ! Close class
CALL h5pclose_class_f(cid1, error)
CALL check("h5pclose_class_f", error, total_error)
@@ -459,7 +459,7 @@ SUBROUTINE test_h5p_file_image(total_error)
INTEGER, PARAMETER :: count = 10
INTEGER, DIMENSION(1:count), TARGET :: buffer
INTEGER, DIMENSION(1:count), TARGET :: temp
- INTEGER :: i
+ INTEGER :: i
INTEGER(size_t) :: size
INTEGER(size_t) :: temp_size
INTEGER :: error ! error return value
@@ -489,7 +489,7 @@ SUBROUTINE test_h5p_file_image(total_error)
CALL h5pset_file_image_f(fapl_1, f_ptr, size, error)
CALL check("h5pset_file_image_f", error, total_error)
-
+
! Get the same data back
DO i = 1, count
f_ptr1(i) = C_LOC(temp(i))
@@ -501,7 +501,7 @@ SUBROUTINE test_h5p_file_image(total_error)
! Check that sizes are the same, and that the buffers are identical but separate
CALL verify("h5pget_file_image_f", INT(temp_size), INT(size), total_error)
-
+
! Verify the image data is correct
DO i = 1, count
CALL verify("h5pget_file_image_f", temp(i), buffer(i), total_error)
@@ -529,18 +529,18 @@ SUBROUTINE external_test_offset(cleanup,total_error)
LOGICAL, INTENT(IN) :: cleanup
INTEGER(hid_t) :: fapl=-1 ! file access property list
- INTEGER(hid_t) :: file=-1 ! file to write to
- INTEGER(hid_t) :: dcpl=-1 ! dataset creation properties
- INTEGER(hid_t) :: space=-1 ! data space
- INTEGER(hid_t) :: dset=-1 ! dataset
+ INTEGER(hid_t) :: file=-1 ! file to write to
+ INTEGER(hid_t) :: dcpl=-1 ! dataset creation properties
+ INTEGER(hid_t) :: space=-1 ! data space
+ INTEGER(hid_t) :: dset=-1 ! dataset
INTEGER(hid_t) :: grp=-1 ! group to emit diagnostics
- INTEGER(size_t) :: i, j ! miscellaneous counters
+ INTEGER(size_t) :: i, j ! miscellaneous counters
CHARACTER(LEN=180) :: filename ! file names
INTEGER, DIMENSION(1:25) :: part
- INTEGER, DIMENSION(1:100), TARGET :: whole ! raw data buffers
- INTEGER(hsize_t), DIMENSION(1:1) :: cur_size ! current data space size
- INTEGER(hid_t) :: hs_space ! hyperslab data space
- INTEGER(hsize_t), DIMENSION(1:1) :: hs_start = (/30/) ! hyperslab starting offset
+ INTEGER, DIMENSION(1:100), TARGET :: whole ! raw data buffers
+ INTEGER(hsize_t), DIMENSION(1:1) :: cur_size ! current data space size
+ INTEGER(hid_t) :: hs_space ! hyperslab data space
+ INTEGER(hsize_t), DIMENSION(1:1) :: hs_start = (/30/) ! hyperslab starting offset
INTEGER(hsize_t), DIMENSION(1:1) :: hs_count = (/25/) ! hyperslab size
CHARACTER(LEN=1) :: ichr1 ! character conversion holder
INTEGER :: error ! error status
@@ -559,23 +559,23 @@ SUBROUTINE external_test_offset(cleanup,total_error)
WRITE(ichr1,'(I1.1)') i
filename = "extern_"//ichr1//"a.raw"
OPEN(10, FILE=filename, ACCESS='STREAM', form='UNFORMATTED')
-
+
WRITE(10) temparray(1:(i-1)*10)
WRITE(10) part
CLOSE(10)
ENDDO
!
- ! Create the file and an initial group.
+ ! Create the file and an initial group.
CALL h5pcreate_f(H5P_FILE_ACCESS_F, fapl, error)
CALL h5fcreate_f('extren_raw.h5', H5F_ACC_TRUNC_F, file, error, access_prp=fapl)
CALL check("h5fcreate_f",error,total_error)
-
+
CALL h5gcreate_f(file, "emit-diagnostics", grp, error)
CALL check("h5gcreate_f",error, total_error)
-
+
! Create the dataset
- sizeof_part = INT(H5_SIZEOF(part(1))*25, hsize_t)
+ sizeof_part = INT(H5_SIZEOF(part(1))*25, hsize_t)
CALL h5pcreate_f(H5P_DATASET_CREATE_F, dcpl, error)
CALL check("h5pcreate_f", error, total_error)
@@ -587,7 +587,7 @@ SUBROUTINE external_test_offset(cleanup,total_error)
CALL check("h5pset_external_f",error,total_error)
CALL h5pset_external_f(dcpl, "extern_4a.raw", INT(30,off_t), sizeof_part, error)
CALL check("h5pset_external_f",error,total_error)
-
+
cur_size(1) = 100
CALL h5screate_simple_f(1, cur_size, space, error)
CALL check("h5screate_simple_f", error, total_error)
@@ -629,7 +629,7 @@ SUBROUTINE external_test_offset(cleanup,total_error)
EXIT
ENDIF
ENDDO
-
+
CALL h5dclose_f(dset, error)
CALL check("h5dclose_f", error, total_error)
CALL h5pclose_f(dcpl, error)
@@ -678,12 +678,12 @@ SUBROUTINE test_vds(total_error)
CHARACTER(LEN=3), PARAMETER :: DATASET="VDS"
INTEGER(hsize_t) :: VDSDIM0
INTEGER(hsize_t), PARAMETER :: VDSDIM1 = 10
- INTEGER(hsize_t), PARAMETER :: VDSDIM2 = 15
+ INTEGER(hsize_t), PARAMETER :: VDSDIM2 = 15
INTEGER(hsize_t) :: DIM0
INTEGER, PARAMETER :: DIM0_1= 4 ! Initial size of the source datasets
- INTEGER, PARAMETER :: DIM1 = 10
- INTEGER, PARAMETER :: DIM2 = 15
+ INTEGER, PARAMETER :: DIM1 = 10
+ INTEGER, PARAMETER :: DIM2 = 15
INTEGER, PARAMETER :: RANK = 3
INTEGER(hsize_t), PARAMETER :: PLANE_STRIDE = 4
@@ -709,15 +709,15 @@ SUBROUTINE test_vds(total_error)
src_count, block
INTEGER(hsize_t), DIMENSION(1:2,1:3) :: vdsdims_out_correct
- INTEGER(hsize_t), DIMENSION(1:3) :: start_out, & !Hyperslab PARAMETER out
+ INTEGER(hsize_t), DIMENSION(1:3) :: start_out, & !Hyperslab PARAMETER out
stride_out, count_out, block_out
INTEGER(hsize_t), DIMENSION(1:3,1:PLANE_STRIDE) :: start_correct
INTEGER :: i, j
- INTEGER(size_t) :: i_sz
+ INTEGER(size_t) :: i_sz
INTEGER :: layout ! Storage layout
- INTEGER(size_t) :: num_map ! Number of mappings
- INTEGER(size_t) :: len ! Length of the string also a RETURN value
+ INTEGER(size_t) :: num_map ! Number of mappings
+ INTEGER(size_t) :: len ! Length of the string also a RETURN value
! Different sized character buffers
CHARACTER(len=LEN(SRC_FILE(1))-3) :: SRC_FILE_LEN_TINY
CHARACTER(len=LEN(SRC_FILE(1))-1) :: SRC_FILE_LEN_SMALL
@@ -726,7 +726,7 @@ SUBROUTINE test_vds(total_error)
CHARACTER(len=LEN(SRC_FILE(1))+10) :: SRC_FILE_LEN_HUGE
CHARACTER(len=LEN(SRC_DATASET(1))) :: SRC_DATASET_LEN_EXACT
- INTEGER(HID_T) :: space_out
+ INTEGER(HID_T) :: space_out
INTEGER :: s_type, virtual_view
INTEGER :: type1, type2
@@ -735,13 +735,13 @@ SUBROUTINE test_vds(total_error)
TYPE(C_PTR) :: f_ptr
INTEGER(SIZE_T) :: nsize
LOGICAL :: IsRegular
- INTEGER(HSIZE_T) :: gap_size
+ INTEGER(HSIZE_T) :: gap_size
! For testing against
vdsdims_out_correct(1,1) = DIM0_1*5
vdsdims_out_correct(2,1) = DIM0_1*8
- vdsdims_out_correct(1:2,2) = VDSDIM1
- vdsdims_out_correct(1:2,3) = VDSDIM2
+ vdsdims_out_correct(1:2,2) = VDSDIM1
+ vdsdims_out_correct(1:2,3) = VDSDIM2
VDSDIM0 = H5S_UNLIMITED_F
DIM0 = H5S_UNLIMITED_F
@@ -749,7 +749,7 @@ SUBROUTINE test_vds(total_error)
dims_max = (/INT(DIM0,hsize_t), INT(DIM1,hsize_t), INT(DIM2,hsize_t)/)
!
- ! Create source files and datasets.
+ ! Create source files and datasets.
!
DO i = 1, PLANE_STRIDE
!
@@ -758,7 +758,7 @@ SUBROUTINE test_vds(total_error)
wdata(j) = i
ENDDO
!
- ! Create the source files and datasets. Write data to each dataset and
+ ! Create the source files and datasets. Write data to each dataset and
! close all resources.
CALL h5fcreate_f(SRC_FILE(i), H5F_ACC_TRUNC_F, file, error)
CALL check("h5fcreate_f", error, total_error)
@@ -769,7 +769,7 @@ SUBROUTINE test_vds(total_error)
CALL check("h5pcreate_f", error, total_error)
CALL h5pset_chunk_f(dcpl, RANK, chunk_dims, error)
CALL check("h5pset_chunk_f",error, total_error)
-
+
CALL h5dcreate_f(file, SRC_DATASET(i), H5T_NATIVE_INTEGER, src_space, dset, error, dcpl, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5dcreate_f",error, total_error)
f_ptr = C_LOC(wdata(1))
@@ -795,20 +795,20 @@ SUBROUTINE test_vds(total_error)
! Create dataspaces for the source dataset.
CALL H5Screate_simple_f(RANK, dims, src_space, error, dims_max)
CALL check("H5Screate_simple_f", error, total_error)
-
+
! Create VDS creation property
CALL H5Pcreate_f (H5P_DATASET_CREATE_F, dcpl, error)
CALL check("H5Pcreate_f", error, total_error)
-
- ! Initialize hyperslab values
+
+ ! Initialize hyperslab values
start(1:3) = 0
- stride(1:3) = (/PLANE_STRIDE,1_hsize_t,1_hsize_t/) ! we will select every fifth plane in VDS
+ stride(1:3) = (/PLANE_STRIDE,1_hsize_t,1_hsize_t/) ! we will select every fifth plane in VDS
count(1:3) = (/H5S_UNLIMITED_F,1_hsize_t,1_hsize_t/)
src_count(1:3) = (/H5S_UNLIMITED_F,1_hsize_t,1_hsize_t/)
block(1:3) = (/1, DIM1, DIM2/)
-
- !
- ! Build the mappings
+
+ !
+ ! Build the mappings
!
start_correct = 0
CALL H5Sselect_hyperslab_f(src_space, H5S_SELECT_SET_F, start, src_count, error, block=block)
@@ -827,10 +827,10 @@ SUBROUTINE test_vds(total_error)
start(1) = start(1) + 1
ENDDO
- CALL H5Sselect_none_f(vspace, error)
+ CALL H5Sselect_none_f(vspace, error)
CALL check("H5Sselect_none_f", error, total_error)
- ! Create a virtual dataset
+ ! Create a virtual dataset
CALL H5Dcreate_f(vfile, DATASET, H5T_NATIVE_INTEGER, vspace, vdset, error, dcpl, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("H5Dcreate_f", error, total_error)
CALL H5Sclose_f(vspace, error)
@@ -840,9 +840,9 @@ SUBROUTINE test_vds(total_error)
CALL H5Pclose_f(dcpl, error)
CALL check("H5Pclose_f", error, total_error)
- ! Let's add data to the source datasets and check new dimensions for VDS
+ ! Let's add data to the source datasets and check new dimensions for VDS
! We will add only one plane to the first source dataset, two planes to the
- ! second one, three to the third, and four to the forth.
+ ! second one, three to the third, and four to the forth.
DO i = 1, PLANE_STRIDE
!
@@ -852,15 +852,15 @@ SUBROUTINE test_vds(total_error)
ENDDO
!
- ! Open the source files and datasets. Append data to each dataset and
+ ! Open the source files and datasets. Append data to each dataset and
! close all resources.
CALL H5Fopen_f (SRC_FILE(i), H5F_ACC_RDWR_F, file, error)
CALL check("H5Fopen_f", error, total_error)
CALL H5Dopen_f (file, SRC_DATASET(i), dset, error)
CALL check("H5Dopen_f", error, total_error)
extdims(1) = DIM0_1+i
- CALL H5Dset_extent_f(dset, extdims, error)
- CALL check("H5Dset_extent_f", error, total_error)
+ CALL H5Dset_extent_f(dset, extdims, error)
+ CALL check("H5Dset_extent_f", error, total_error)
CALL H5Dget_space_f(dset, src_space, error)
CALL check("H5Dget_space_f", error, total_error)
@@ -870,13 +870,13 @@ SUBROUTINE test_vds(total_error)
memdims(1) = i
- CALL H5Screate_simple_f(RANK, memdims, mem_space, error)
+ CALL H5Screate_simple_f(RANK, memdims, mem_space, error)
CALL check("H5Screate_simple_f", error, total_error)
- CALL H5Sselect_hyperslab_f(src_space, H5S_SELECT_SET_F, start,count, error,block=block)
+ CALL H5Sselect_hyperslab_f(src_space, H5S_SELECT_SET_F, start,count, error,block=block)
CALL check("H5Sselect_hyperslab_f", error, total_error)
f_ptr = C_LOC(wdata(1))
- CALL H5Dwrite_f(dset, H5T_NATIVE_INTEGER, f_ptr, error, mem_space, src_space, H5P_DEFAULT_F)
+ CALL H5Dwrite_f(dset, H5T_NATIVE_INTEGER, f_ptr, error, mem_space, src_space, H5P_DEFAULT_F)
CALL check("H5Dwrite_f", error, total_error)
CALL H5Sclose_f(src_space, error)
CALL check("H5Sclose_f", error, total_error)
@@ -888,38 +888,38 @@ SUBROUTINE test_vds(total_error)
call H5Dclose_f(vdset, error)
CALL check("H5Dclose_f", error, total_error)
- call H5Fclose_f(vfile, error)
+ call H5Fclose_f(vfile, error)
CALL check("H5Fclose_f", error, total_error)
-
+
!
! begin the read section
!
! Open file and dataset using the default properties.
CALL H5Fopen_f(VFILENAME, H5F_ACC_RDONLY_F, vfile, error)
- CALL check("H5Fopen_f", error, total_error)
-
- !
+ CALL check("H5Fopen_f", error, total_error)
+
+ !
! Open VDS using different access properties to use max or
! min extents depending on the sizes of the underlying datasets
CALL H5Pcreate_f(H5P_DATASET_ACCESS_F, dapl, error)
- CALL check("H5Pcreate_f", error, total_error)
+ CALL check("H5Pcreate_f", error, total_error)
DO i = 1, 2
IF(i.NE.1)THEN
CALL H5Pset_virtual_view_f(dapl, H5D_VDS_LAST_AVAILABLE_F, error)
- CALL check("H5Pset_virtual_view_f", error, total_error)
+ CALL check("H5Pset_virtual_view_f", error, total_error)
ELSE
CALL H5Pset_virtual_view_f(dapl, H5D_VDS_FIRST_MISSING_F, error)
- CALL check("H5Pset_virtual_view_f", error, total_error)
+ CALL check("H5Pset_virtual_view_f", error, total_error)
ENDIF
-
+
CALL H5Dopen_f(vfile, DATASET, vdset, error, dapl)
- CALL check("H5Dopen_f", error, total_error)
+ CALL check("H5Dopen_f", error, total_error)
! Let's get space of the VDS and its dimension we should get 32(or 20)x10x10
CALL H5Dget_space_f(vdset, vspace, error)
- CALL check("H5Dget_space_f", error, total_error)
+ CALL check("H5Dget_space_f", error, total_error)
CALL H5Sget_simple_extent_dims_f(vspace, vdsdims_out, vdsdims_max_out, error)
CALL check("H5Sget_simple_extent_dims_f", error, total_error)
@@ -927,12 +927,12 @@ SUBROUTINE test_vds(total_error)
DO j = 1, RANK
IF(vdsdims_out(j).NE.vdsdims_out_correct(i,j))THEN
total_error = total_error + 1
- EXIT
+ EXIT
ENDIF
ENDDO
CALL H5Pget_virtual_view_f(dapl, virtual_view, error)
- CALL check("h5pget_virtual_view_f", error, total_error)
+ CALL check("h5pget_virtual_view_f", error, total_error)
IF(i.EQ.1)THEN
IF(virtual_view .NE. H5D_VDS_FIRST_MISSING_F)THEN
@@ -942,10 +942,10 @@ SUBROUTINE test_vds(total_error)
IF(virtual_view .NE. H5D_VDS_LAST_AVAILABLE_F)THEN
total_error = total_error + 1
ENDIF
-
+
ENDIF
- ! Close
+ ! Close
CALL H5Dclose_f(vdset, error)
CALL check("H5Dclose_f", error, total_error)
CALL H5Sclose_f(vspace, error)
@@ -957,7 +957,7 @@ SUBROUTINE test_vds(total_error)
!
! Get creation property list and mapping properties.
- !
+ !
CALL H5Dget_create_plist_f (vdset, dcpl, error)
CALL check("H5Dget_create_plist_f", error, total_error)
@@ -973,7 +973,7 @@ SUBROUTINE test_vds(total_error)
!
! Find number of mappings.
-
+
CALL H5Pget_virtual_count_f(dcpl, num_map, error)
CALL check("H5Pget_virtual_count_f", error, total_error)
@@ -981,7 +981,7 @@ SUBROUTINE test_vds(total_error)
PRINT*,"Number of mappings is incorrect"
total_error = total_error + 1
ENDIF
- !
+ !
! Get mapping parameters for each mapping.
!
DO i_sz = 1, num_map
@@ -1105,7 +1105,7 @@ SUBROUTINE test_vds(total_error)
PRINT*,"gapsize is incorrect"
total_error = total_error + 1
ENDIF
-
+
CALL H5Dclose_f(vdset, error)
CALL check("H5Dclose_f", error, total_error)
CALL H5Sclose_f(vspace, error)
@@ -1114,7 +1114,7 @@ SUBROUTINE test_vds(total_error)
CALL check("H5Pclose_f", error, total_error)
CALL H5Fclose_f(vfile, error)
CALL check("H5Fclose_f", error, total_error)
-
+
END SUBROUTINE test_vds