summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5Sselect.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5Sselect.f90')
-rw-r--r--fortran/test/tH5Sselect.f90330
1 files changed, 165 insertions, 165 deletions
diff --git a/fortran/test/tH5Sselect.f90 b/fortran/test/tH5Sselect.f90
index 7e11b61..f7fd8af 100644
--- a/fortran/test/tH5Sselect.f90
+++ b/fortran/test/tH5Sselect.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,9 +11,9 @@
! 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 Selection-related Dataspace Interface functionality.
!
@@ -22,17 +22,17 @@
! h5sget_select_npoints_f, h5sselect_elements_f, h5sselect_all_f,
! h5sselect_none_f, h5sselect_valid_f, h5sselect_hyperslab_f,
! h5sget_select_bounds_f, h5sget_select_elem_pointlist_f,
-! h5sget_select_elem_npoints_f, h5sget_select_hyper_blocklist_f,
+! h5sget_select_elem_npoints_f, h5sget_select_hyper_blocklist_f,
! h5sget_select_hyper_nblocks_f, h5sget_select_npoints_f
!
SUBROUTINE test_select_hyperslab(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 = "tselect"
CHARACTER(LEN=80) :: fix_filename
@@ -42,60 +42,60 @@
!
CHARACTER(LEN=8), PARAMETER :: dsetname = "IntArray"
- INTEGER(HID_T) :: file_id ! File identifier
- INTEGER(HID_T) :: dset_id ! Dataset identifier
- INTEGER(HID_T) :: dataspace ! Dataspace identifier
- INTEGER(HID_T) :: memspace ! memspace 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 ! memspace identifier
!
- !Memory space dimensions
+ !Memory space dimensions
!
INTEGER(HSIZE_T), DIMENSION(3) :: dimsm = (/7,7,3/)
!
- !Dataset dimensions
+ !Dataset dimensions
!
INTEGER(HSIZE_T), DIMENSION(2) :: dimsf = (/5,6/)
!
- !Size of the hyperslab in the file
+ !Size of the hyperslab in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: count = (/3,4/)
!
- !hyperslab offset in the file
+ !hyperslab offset in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: offset = (/1,2/)
!
- !Size of the hyperslab in memory
+ !Size of the hyperslab in memory
!
INTEGER(HSIZE_T), DIMENSION(3) :: count_out = (/3,4,1/)
!
- !hyperslab offset in memory
+ !hyperslab offset in memory
!
INTEGER(HSIZE_T), DIMENSION(3) :: offset_out = (/3,0,0/)
!
- !data to write
+ !data to write
!
INTEGER, DIMENSION(5,6) :: data
!
- !output buffer
+ !output buffer
!
INTEGER, DIMENSION(7,7,3) :: data_out
!
- !dataset space rank
+ !dataset space rank
!
- INTEGER :: dsetrank = 2
+ INTEGER :: dsetrank = 2
!
- !memspace rank
+ !memspace rank
!
INTEGER :: memrank = 3
@@ -103,23 +103,23 @@
!
- !general purpose integer
+ !general purpose integer
!
- INTEGER :: i, j
+ INTEGER :: i, j
!
- !flag to check operation success
+ !flag to check operation success
!
- INTEGER :: error
+ INTEGER :: error
INTEGER(HSIZE_T), DIMENSION(3) :: data_dims
!
- !This writes data to the HDF5 file.
+ !This writes data to the HDF5 file.
!
!
- !data initialization
+ !data initialization
!
do i = 1, 5
do j = 1, 6
@@ -137,12 +137,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"
@@ -152,7 +152,7 @@
CALL check("h5fcreate_f", error, total_error)
!
- !Create the data space for the dataset.
+ !Create the data space for the dataset.
!
CALL h5screate_simple_f(dsetrank, dimsf, dataspace, error)
CALL check("h5screate_simple_f", error, total_error)
@@ -168,7 +168,7 @@
! Write the dataset
!
data_dims(1) = 5
- data_dims(2) = 6
+ data_dims(2) = 6
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, data_dims, error)
CALL check("h5dwrite_f", error, total_error)
@@ -191,7 +191,7 @@
CALL check("h5fclose_f", error, total_error)
!
- !This reads the hyperslab from the sds.h5 file just
+ !This reads the hyperslab from the sds.h5 file just
!created, into a 2-dimensional plane of the 3-dimensional array.
!
@@ -228,7 +228,7 @@
!Select hyperslab in the dataset.
!
CALL h5sselect_hyperslab_f(dataspace, H5S_SELECT_SET_F, &
- offset, count, error)
+ offset, count, error)
CALL check("h5sselect_hyperslab_f", error, total_error)
!
!create memory dataspace.
@@ -240,16 +240,16 @@
!Select hyperslab in memory.
!
CALL h5sselect_hyperslab_f(memspace, H5S_SELECT_SET_F, &
- offset_out, count_out, error)
+ offset_out, count_out, error)
CALL check("h5sselect_hyperslab_f", error, total_error)
!
- !Read data from hyperslab in the file into the hyperslab in
+ !Read data from hyperslab in the file into the hyperslab in
!memory and display.
!
data_dims(1) = 7
- data_dims(2) = 7
- data_dims(3) = 3
+ data_dims(2) = 7
+ data_dims(3) = 3
CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, &
memspace, dataspace)
CALL check("h5dread_f", error, total_error)
@@ -264,7 +264,7 @@
! 0 0 0 0 0 0 0
! 0 0 0 0 0 0 0
! 0 0 0 0 0 0 0
- ! 3 4 5 6 0 0 0
+ ! 3 4 5 6 0 0 0
! 4 5 6 7 0 0 0
! 5 6 7 8 0 0 0
! 0 0 0 0 0 0 0
@@ -307,11 +307,11 @@
SUBROUTINE test_select_element(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 dataset1 is stored in file "copy1.h5"
@@ -335,60 +335,60 @@
CHARACTER(LEN=8), PARAMETER :: dsetname2 = "Copy2"
!
- !dataset rank
+ !dataset rank
!
INTEGER, PARAMETER :: RANK = 2
!
- !number of points selected
+ !number of points selected
!
INTEGER(SIZE_T), PARAMETER :: NUMP = 2
- INTEGER(HID_T) :: file1_id ! File1 identifier
- INTEGER(HID_T) :: file2_id ! File2 identifier
- INTEGER(HID_T) :: dset1_id ! Dataset1 identifier
- INTEGER(HID_T) :: dset2_id ! Dataset2 identifier
- INTEGER(HID_T) :: dataspace1 ! Dataspace identifier
- INTEGER(HID_T) :: dataspace2 ! Dataspace identifier
- INTEGER(HID_T) :: memspace ! memspace identifier
+ INTEGER(HID_T) :: file1_id ! File1 identifier
+ INTEGER(HID_T) :: file2_id ! File2 identifier
+ INTEGER(HID_T) :: dset1_id ! Dataset1 identifier
+ INTEGER(HID_T) :: dset2_id ! Dataset2 identifier
+ INTEGER(HID_T) :: dataspace1 ! Dataspace identifier
+ INTEGER(HID_T) :: dataspace2 ! Dataspace identifier
+ INTEGER(HID_T) :: memspace ! memspace identifier
!
- !Memory space dimensions
+ !Memory space dimensions
!
INTEGER(HSIZE_T), DIMENSION(1) :: dimsm = (/2/)
!
- !Dataset dimensions
+ !Dataset dimensions
!
INTEGER(HSIZE_T), DIMENSION(2) :: dimsf = (/3,4/)
!
- !Points positions in the file
+ !Points positions in the file
!
INTEGER(HSIZE_T), DIMENSION(RANK,NUMP) :: coord
!
- !data buffers
+ !data buffers
!
INTEGER, DIMENSION(3,4) :: buf1, buf2, bufnew
!
- !value to write
+ !value to write
!
INTEGER, DIMENSION(2) :: val = (/53, 59/)
!
- !memory rank
+ !memory rank
!
- INTEGER :: memrank = 1
+ INTEGER :: memrank = 1
!
- !general purpose integer
+ !general purpose integer
!
- INTEGER :: i, j
+ INTEGER :: i, j
!
- !flag to check operation success
+ !flag to check operation success
!
INTEGER :: error
INTEGER(HSIZE_T), DIMENSION(3) :: data_dims
@@ -396,11 +396,11 @@
!
!Create two files containing identical datasets. Write 0's to one
- !and 1's to the other.
+ !and 1's to the other.
!
!
- !data initialization
+ !data initialization
!
do i = 1, 3
do j = 1, 4
@@ -417,12 +417,12 @@
!
!Initialize FORTRAN predifined datatypes
!
-! CALL h5init_types_f(error)
+! CALL h5init_types_f(error)
! CALL check("h5init_types_f", error, total_error)
!
!Create file1, file2 using default properties.
- !
+ !
CALL h5_fixname_f(filename1, fix_filename1, H5P_DEFAULT_F, error)
if (error .ne. 0) then
write(*,*) "Cannot modify filename"
@@ -440,7 +440,7 @@
CALL check("h5fcreate_f", error, total_error)
!
- !Create the data space for the datasets.
+ !Create the data space for the datasets.
!
CALL h5screate_simple_f(RANK, dimsf, dataspace1, error)
CALL check("h5screate_simple_f", error, total_error)
@@ -498,8 +498,8 @@
CALL check("h5fclose_f", error, total_error)
!
- !Open the two files. Select two points in one file, write values to
- !those point locations, then do H5Scopy and write the values to the
+ !Open the two files. Select two points in one file, write values to
+ !those point locations, then do H5Scopy and write the values to the
!other file. Close files.
!
@@ -534,12 +534,12 @@
CALL check("h5screate_simple_f", error, total_error)
!
- !Set the selected point positions.Because Fortran array index starts
+ !Set the selected point positions.Because Fortran array index starts
! from 1, so add one to the actual select points in C
!
- coord(1,1) = 1
- coord(2,1) = 2
- coord(1,2) = 1
+ coord(1,1) = 1
+ coord(2,1) = 2
+ coord(1,2) = 1
coord(2,2) = 4
!
@@ -560,7 +560,7 @@
!
!Copy the daspace1 into dataspace2
!
- CALL h5scopy_f(dataspace1, dataspace2, error)
+ CALL h5scopy_f(dataspace1, dataspace2, error)
CALL check("h5scopy_f", error, total_error)
!
@@ -683,25 +683,25 @@
SUBROUTINE test_basic_select(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 "testselect.h5"
!
CHARACTER(LEN=10), PARAMETER :: filename = "testselect"
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
!
- !dataspace rank
+ !dataspace rank
!
INTEGER, PARAMETER :: RANK = 2
!
- !select NUMP_POINTS points from the file
+ !select NUMP_POINTS points from the file
!
INTEGER(SIZE_T), PARAMETER :: NUMPS = 10
@@ -710,86 +710,86 @@
!
CHARACTER(LEN=10), PARAMETER :: dsetname = "testselect"
- 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) :: dataspace ! Dataspace identifier
!
- !Dataset dimensions
+ !Dataset dimensions
!
INTEGER(HSIZE_T), DIMENSION(2) :: dimsf = (/5,6/)
!
- !Size of the hyperslab in the file
+ !Size of the hyperslab in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: count = (/2,2/)
!
- !hyperslab offset in the file
+ !hyperslab offset in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: offset = (/0,0/)
!
- !start block for getting the selected hyperslab
+ !start block for getting the selected hyperslab
!
INTEGER(HSIZE_T) :: startblock = 0
!
- !start point for getting the selected elements
+ !start point for getting the selected elements
!
INTEGER(HSIZE_T) :: startpoint = 0
!
- !Stride of the hyperslab in the file
+ !Stride of the hyperslab in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: stride = (/3,3/)
!
- !BLock size of the hyperslab in the file
+ !BLock size of the hyperslab in the file
!
INTEGER(HSIZE_T), DIMENSION(2) :: block = (/2,2/)
!
- !array to give selected points' coordinations
+ !array to give selected points' coordinations
!
INTEGER(HSIZE_T), DIMENSION(RANK, NUMPS) :: coord
!
- !Number of hyperslabs selected in the current dataspace
+ !Number of hyperslabs selected in the current dataspace
!
INTEGER(HSSIZE_T) :: num_blocks
!
!allocatable array for putting a list of hyperslabs
- !selected in the current file dataspace
+ !selected in the current file dataspace
!
INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:) :: blocklist
!
- !Number of points selected in the current dataspace
+ !Number of points selected in the current dataspace
!
INTEGER(HSSIZE_T) :: num_points
INTEGER(HSIZE_T) :: num1_points
!
!allocatable array for putting a list of points
- !selected in the current file dataspace
+ !selected in the current file dataspace
!
INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:) :: pointlist
!
- !start and end bounds in the current dataspace selection
+ !start and end bounds in the current dataspace selection
!
INTEGER(HSIZE_T), DIMENSION(RANK) :: startout, endout
!
- !data to write
+ !data to write
!
INTEGER, DIMENSION(5,6) :: data
!
- !flag to check operation success
+ !flag to check operation success
!
INTEGER :: error
INTEGER(HSIZE_T), DIMENSION(3) :: data_dims
@@ -797,7 +797,7 @@
INTEGER :: i
!
- !initialize the coord array to give the selected points' position
+ !initialize the coord array to give the selected points' position
!
coord(1,1) = 1
coord(2,1) = 1
@@ -822,7 +822,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"
@@ -832,7 +832,7 @@
CALL check("h5fcreate_f", error, total_error)
!
- !Create the data space for the dataset.
+ !Create the data space for the dataset.
!
CALL h5screate_simple_f(RANK, dimsf, dataspace, error)
CALL check("h5screate_simple_f", error, total_error)
@@ -875,7 +875,7 @@
!
CALL h5fopen_f (fix_filename, H5F_ACC_RDONLY_F, file_id, error)
CALL check("h5fopen_f", error, total_error)
-
+
!
!Open the dataset.
!
@@ -892,11 +892,11 @@
!Select hyperslab in the dataset.
!
CALL h5sselect_hyperslab_f(dataspace, H5S_SELECT_SET_F, &
- offset, count, error, stride, block)
+ offset, count, error, stride, block)
CALL check("h5sselect_hyperslab_f", error, total_error)
!
- !get the number of hyperslab blocks in the current dataspac selection
+ !get the number of hyperslab blocks in the current dataspac selection
!
CALL h5sget_select_hyper_nblocks_f(dataspace, num_blocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
@@ -911,16 +911,16 @@
if(error .NE. 0) then
STOP
endif
-
+
!
- !get the list of hyperslabs selected in the current dataspac selection
+ !get the list of hyperslabs selected in the current dataspac selection
!
CALL h5sget_select_hyper_blocklist_f(dataspace, startblock, &
num_blocks, blocklist, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
! write(*,*) (blocklist(i), i =1, num_blocks*RANK*2)
!result of blocklist selected is:
- !1, 1, 2, 2, 4, 1, 5, 2, 1, 4, 2, 5, 4, 4, 5, 5
+ !1, 1, 2, 2, 4, 1, 5, 2, 1, 4, 2, 5, 4, 4, 5, 5
!
!deallocate the blocklist array
@@ -928,7 +928,7 @@
DEALLOCATE(blocklist)
!
- !get the selection bounds in the current dataspac selection
+ !get the selection bounds in the current dataspac selection
!
CALL h5sget_select_bounds_f(dataspace, startout, endout, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -967,7 +967,7 @@
CALL h5sget_select_elem_npoints_f(dataspace, num_points, error)
CALL check("h5sget_select_elem_npoints_f", error, total_error)
IF (num_points .NE. 10) write(*,*) "error occured with num_points"
- !write(*,*) num_points
+ !write(*,*) num_points
! result of num_points is 10
!
@@ -977,11 +977,11 @@
CALL h5sget_select_elem_pointlist_f(dataspace, startpoint, &
num1_points, pointlist, error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
- !write(*,*) (pointlist(i), i =1, num1_points*RANK)
+ !write(*,*) (pointlist(i), i =1, num1_points*RANK)
!result of pintlist is:
- !1, 1, 3, 1, 5, 1, 1, 3, 3, 3, 5, 3, 3,
+ !1, 1, 3, 1, 5, 1, 1, 3, 3, 3, 5, 3, 3,
!4, 1, 4, 3, 5, 5, 5
-
+
!
!deallocate the pointlist array
!
@@ -1021,13 +1021,13 @@
!****************************************************************/
SUBROUTINE test_select_point(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(HID_T) :: xfer_plist
-
+
INTEGER, PARAMETER :: SPACE1_DIM1=3
INTEGER, PARAMETER :: SPACE1_DIM2=15
INTEGER, PARAMETER :: SPACE1_DIM3=13
@@ -1035,11 +1035,11 @@ SUBROUTINE test_select_point(cleanup, total_error)
INTEGER, PARAMETER :: SPACE2_DIM2=26
INTEGER, PARAMETER :: SPACE3_DIM1=15
INTEGER, PARAMETER :: SPACE3_DIM2=26
-
+
INTEGER, PARAMETER :: SPACE1_RANK=3
INTEGER, PARAMETER :: SPACE2_RANK=2
INTEGER, PARAMETER :: SPACE3_RANK=2
-
+
! /* Element selection information */
INTEGER, PARAMETER :: POINT1_NPOINTS=10
INTEGER(hid_t) ::fid1 ! /* HDF5 File IDs */
@@ -1048,7 +1048,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
INTEGER(hsize_t), DIMENSION(1:3) :: dims1 = (/SPACE1_DIM1, SPACE1_DIM2, SPACE1_DIM3/)
INTEGER(hsize_t), DIMENSION(1:2) :: dims2 = (/SPACE2_DIM1, SPACE2_DIM2/)
INTEGER(hsize_t), DIMENSION(1:2) :: dims3 = (/SPACE3_DIM1, SPACE3_DIM2/)
-
+
INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: coord1 !/* Coordinates for point selection */
INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: temp_coord1 !/* Coordinates for point selection */
INTEGER(hsize_t), DIMENSION(1:SPACE2_RANK,1:POINT1_NPOINTS) :: coord2 !/* Coordinates for point selection */
@@ -1064,7 +1064,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
! struct pnt_iter pi; /* Custom Pointer iterator struct */
INTEGER :: error !/* Generic return value */
CHARACTER(LEN=9) :: filename = 'h5s_hyper'
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=1), DIMENSION(1:SPACE2_DIM1,1:SPACE2_DIM2) :: wbuf, rbuf
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
@@ -1090,11 +1090,11 @@ SUBROUTINE test_select_point(cleanup, total_error)
!!$ for(i=0, tbuf=wbuf; i<SPACE2_DIM1; i++)
!!$ for(j=0; j<SPACE2_DIM2; j++)
!!$ *tbuf++=(uint8_t)((i*SPACE2_DIM2)+j);
-
+
!/* Create file */
CALL h5fcreate_f(fix_filename, H5F_ACC_TRUNC_F, fid1, error)
CALL check("h5fcreate_f", error, total_error)
-
+
!/* Create dataspace for dataset */
CALL h5screate_simple_f(SPACE1_RANK, dims1, sid1, error)
CALL check("h5screate_simple_f", error, total_error)
@@ -1151,7 +1151,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL h5sselect_elements_f(sid1, H5S_SELECT_APPEND_F, SPACE1_RANK, INT(POINT1_NPOINTS,size_t), coord1, error)
CALL check("h5sselect_elements_f", error, total_error)
! /* Verify correct elements selected */
-
+
CALL h5sget_select_elem_pointlist_f(sid1, INT(POINT1_NPOINTS,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord1,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1182,7 +1182,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
!/* Verify correct elements selected */
-
+
CALL h5sget_select_elem_pointlist_f(sid2, INT(0,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord2,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1349,8 +1349,8 @@ END SUBROUTINE test_select_point
!****************************************************************/
SUBROUTINE test_select_combine(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
@@ -1358,7 +1358,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
INTEGER, PARAMETER :: SPACE7_RANK = 2
INTEGER, PARAMETER :: SPACE7_DIM1 = 10
INTEGER, PARAMETER :: SPACE7_DIM2 = 10
-
+
INTEGER(hid_t) :: base_id ! /* Base dataspace for test */
INTEGER(hid_t) :: all_id ! /* Dataspace for "all" selection */
INTEGER(hid_t) :: none_id ! /* Dataspace for "none" selection */
@@ -1378,7 +1378,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5screate_simple_f", error, total_error)
! /* Copy base dataspace and set selection to "all" */
- CALL h5scopy_f(base_id, all_id, error)
+ CALL h5scopy_f(base_id, all_id, error)
CALL check("h5scopy_f", error, total_error)
CALL H5Sselect_all_f(all_id, error)
@@ -1389,7 +1389,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_ALL_F), total_error)
!/* Copy base dataspace and set selection to "none" */
- CALL h5scopy_f(base_id, none_id, error)
+ CALL h5scopy_f(base_id, none_id, error)
CALL check("h5scopy_f", error, total_error)
CALL H5Sselect_none_f(none_id, error)
@@ -1398,9 +1398,9 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL H5Sget_select_type_f(none_id, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_NONE_F), total_error)
-
+
!/* Copy "all" selection & space */
- CALL H5Scopy_f(all_id, space1, error)
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
!/* 'OR' "all" selection with another hyperslab */
@@ -1409,7 +1409,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
icount(1:2) = 1
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_OR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
!/* Verify that it's still "all" selection */
@@ -1422,7 +1422,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
!/* Copy "all" selection & space */
- CALL H5Scopy_f(all_id, space1, error)
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'AND' "all" selection with another hyperslab */
@@ -1431,7 +1431,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
icount(1:2) = 1
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_AND_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
!/* Verify that the new selection is the same at the original block */
@@ -1443,7 +1443,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL VERIFY("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error)
-
+
!/* Retrieve the block defined */
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
@@ -1460,7 +1460,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
!/* Copy "all" selection & space */
- CALL H5Scopy_f(all_id, space1, error)
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'XOR' "all" selection with another hyperslab */
@@ -1470,7 +1470,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_XOR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is an inversion of the original block */
@@ -1491,7 +1491,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
! /* Verify that the correct block is defined */
- ! No guarantee is implied as the order in which blocks are listed.
+ ! No guarantee is implied as the order in which blocks are listed.
! So this will ONLY work for square domains iblock(1:2) = (/5,5/)
!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 5, total_error)
@@ -1512,7 +1512,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "all" selection & space */
- CALL H5Scopy_f(all_id, space1, error)
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'NOTB' "all" selection with another hyperslab */
@@ -1522,7 +1522,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTB_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is an inversion of the original block */
@@ -1540,9 +1540,9 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! /* Verify that the correct block is defined */
+ ! /* Verify that the correct block is defined */
- ! No guarantee is implied as the order in which blocks are listed.
+ ! No guarantee is implied as the order in which blocks are listed.
! So this will ONLY work for square domains iblock(1:2) = (/5,5/)
!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
@@ -1564,7 +1564,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "all" selection & space */
- CALL H5Scopy_f(all_id, space1, error)
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'NOTA' "all" selection with another hyperslab */
@@ -1574,7 +1574,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTA_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
!/* Verify that the new selection is the "none" selection */
@@ -1587,7 +1587,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "none" selection & space */
- CALL H5Scopy_f(none_id, space1, error)
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'OR' "none" selection with another hyperslab */
@@ -1597,14 +1597,14 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_OR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is the same as the original hyperslab */
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
+
! /* Verify that there is only one block */
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
@@ -1627,7 +1627,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "none" selection & space */
- CALL H5Scopy_f(none_id, space1, error)
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'AND' "none" selection with another hyperslab */
@@ -1637,7 +1637,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_AND_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is the "none" selection */
@@ -1650,7 +1650,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "none" selection & space */
- CALL H5Scopy_f(none_id, space1, error)
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'XOR' "none" selection with another hyperslab */
@@ -1660,14 +1660,14 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_XOR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is the same as the original hyperslab */
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
+
! /* Verify that there is only one block */
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
@@ -1683,13 +1683,13 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
-
+
! /* Close temporary dataspace */
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "none" selection & space */
- CALL H5Scopy_f(none_id, space1, error)
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'NOTB' "none" selection with another hyperslab */
@@ -1699,7 +1699,7 @@ SUBROUTINE test_select_combine(cleanup, total_error)
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTB_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is the "none" selection */
@@ -1712,23 +1712,23 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL check("h5sclose_f", error, total_error)
! /* Copy "none" selection & space */
- CALL H5Scopy_f(none_id, space1, error)
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
! /* 'NOTA' "none" selection with another hyperslab */
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
- iblock(1:2) = (/5,4/) !5
+ iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTA_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
! /* Verify that the new selection is the same as the original hyperslab */
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
+
! /* Verify that there is ONLY one BLOCK */
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
@@ -1747,13 +1747,13 @@ SUBROUTINE test_select_combine(cleanup, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
-
+
! /* Close temporary dataspace */
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
! /* Close dataspaces */
-
+
CALL h5sclose_f(base_id, error)
CALL check("h5sclose_f", error, total_error)
CALL h5sclose_f(all_id, error)
@@ -1771,8 +1771,8 @@ END SUBROUTINE test_select_combine
!****************************************************************/
SUBROUTINE test_select_bounds(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
@@ -1781,7 +1781,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
INTEGER, PARAMETER :: SPACE11_DIM1=100
INTEGER, PARAMETER :: SPACE11_DIM2=50
INTEGER, PARAMETER :: SPACE11_NPOINTS=4
-
+
INTEGER(hid_t) :: sid ! /* Dataspace ID */
INTEGER(hsize_t), DIMENSION(1:SPACE11_RANK) :: dims = (/SPACE11_DIM1, SPACE11_DIM2/) !Dataspace dimensions
INTEGER(hsize_t), DIMENSION(SPACE11_RANK, SPACE11_NPOINTS) :: coord !/* Coordinates for point selection
@@ -1792,7 +1792,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
INTEGER(hssize_t), DIMENSION(SPACE11_RANK) :: offset !/* Offset amount for selection */
INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: low_bounds !/* The low bounds for the selection */
INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: high_bounds !/* The high bounds for the selection */
-
+
INTEGER :: error
!/* Create dataspace */
@@ -1836,7 +1836,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error)
!/* Set point selection */
-
+
coord(1,1)= 3; coord(2,1)= 3;
coord(1,2)= 3; coord(2,2)= 46;
coord(1,3)= 96; coord(2,3)= 3;
@@ -1863,7 +1863,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
! /* Get bounds for hyperslab selection with negative offset */
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error)
-
+
! /* Set valid offset for selection */
offset(1:2) = (/2,-2/)
CALL H5Soffset_simple_f(sid, offset, error)
@@ -1888,9 +1888,9 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
stride(1:2) = 10
count(1:2) = 4
block(1:2) = 5
-
+
CALL h5sselect_hyperslab_f(sid, H5S_SELECT_SET_F, start, &
- count, error, stride, block)
+ count, error, stride, block)
CALL check("h5sselect_hyperslab_f", error, total_error)
!/* Get bounds for hyperslab selection */
@@ -1929,7 +1929,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
offset(1:2) = 0
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
-
+
! /* Make "irregular" hyperslab selection */
start(1:2) = 20
stride(1:2) = 20
@@ -1937,7 +1937,7 @@ SUBROUTINE test_select_bounds(cleanup, total_error)
block(1:2) = 10
CALL h5sselect_hyperslab_f(sid, H5S_SELECT_OR_F, start, &
- count, error, stride, block)
+ count, error, stride, block)
CALL check("h5sselect_hyperslab_f", error, total_error)
!/* Get bounds for hyperslab selection */