diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-09-24 16:26:32 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-09-24 16:26:32 (GMT) |
commit | 8866806873cd1ff5a1cc1bbbd59d186aa8065cca (patch) | |
tree | 33b7a4219c5e08c6b1cdf8561334d4a701d22fcd /fortran/src/H5Sff.f90 | |
parent | acf7dd2c744555b30b10f0915b713eadeda45571 (diff) | |
download | hdf5-8866806873cd1ff5a1cc1bbbd59d186aa8065cca.zip hdf5-8866806873cd1ff5a1cc1bbbd59d186aa8065cca.tar.gz hdf5-8866806873cd1ff5a1cc1bbbd59d186aa8065cca.tar.bz2 |
[svn-r15690] Description:
In nH5Sget_select_bounds_c swapped array bounds to account for C and Fortran reversed array notation.
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r-- | fortran/src/H5Sff.f90 | 133 |
1 files changed, 65 insertions, 68 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90 index 003b946..17c8012 100644 --- a/fortran/src/H5Sff.f90 +++ b/fortran/src/H5Sff.f90 @@ -386,35 +386,32 @@ ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5sget_select_bounds_f(space_id, start, end, hdferr) - IMPLICIT NONE - INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier - INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start - !Starting coordinates of the bounding box. - INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: end - !Ending coordinates of the bounding box, - !i.e., the coordinates of the diagonally - !opposite corner - INTEGER, INTENT(OUT) :: hdferr ! Error code - -! INTEGER, EXTERNAL :: h5sget_select_bounds_c -! MS FORTRAN needs explicit interface for C functions called here. -! - INTERFACE - INTEGER FUNCTION h5sget_select_bounds_c(space_id, start, end) - USE H5GLOBAL - !DEC$ IF DEFINED(HDF5F90_WINDOWS) -!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_BOUNDS_C'::h5sget_select_bounds_c - !DEC$ ENDIF - INTEGER(HID_T), INTENT(IN) :: space_id - INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start - INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: end - END FUNCTION h5sget_select_bounds_c - END INTERFACE + SUBROUTINE h5sget_select_bounds_f(space_id, start, END, hdferr) + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier + INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start + ! Starting coordinates of the bounding box. + INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: END + !Ending coordinates of the bounding box, + !i.e., the coordinates of the diagonally + !opposite corner + INTEGER, INTENT(OUT) :: hdferr ! Error code - hdferr = h5sget_select_bounds_c(space_id, start, end) + INTERFACE + INTEGER FUNCTION h5sget_select_bounds_c(space_id, start, END) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_BOUNDS_C'::h5sget_select_bounds_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: space_id + INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start + INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: END + END FUNCTION h5sget_select_bounds_c + END INTERFACE + + hdferr = h5sget_select_bounds_c(space_id, start, END) - END SUBROUTINE h5sget_select_bounds_f + END SUBROUTINE h5sget_select_bounds_f !---------------------------------------------------------------------- ! Name: h5sget_select_elem_npoints_f @@ -557,49 +554,49 @@ ! ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5sselect_elements_f(space_id, operator, rank, & - num_elements, coord, hdferr) - IMPLICIT NONE - INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier - INTEGER, INTENT(IN) :: operator ! Flag, valid values are: - ! H5S_SELECT_SET_F (0) - ! H5S_SELECT_OR_F (1) - INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions - INTEGER(SIZE_T), INTENT(IN) :: num_elements ! Number of elements to be - ! selected - INTEGER(HSIZE_T), & - DIMENSION(rank,num_elements), INTENT(IN) :: coord + SUBROUTINE h5sselect_elements_f(space_id, OPERATOR, rank, & + num_elements, coord, hdferr) + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier + INTEGER, INTENT(IN) :: OPERATOR ! Flag, valid values are: + ! H5S_SELECT_SET_F (0) + ! H5S_SELECT_OR_F (1) + INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions + INTEGER(SIZE_T), INTENT(IN) :: num_elements ! Number of elements to be + ! selected + INTEGER(HSIZE_T), & + DIMENSION(rank,num_elements), INTENT(IN) :: coord ! Array with the coordinates ! of the selected elements ! coord(rank, num_elements) - INTEGER, INTENT(OUT) :: hdferr ! Error code - INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:,:) :: c_coord - INTEGER :: error, i,j - - INTERFACE - INTEGER FUNCTION h5sselect_elements_c(space_id, operator,& - num_elements,c_c_coord) - USE H5GLOBAL - !DEC$ IF DEFINED(HDF5F90_WINDOWS) - !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSELECT_ELEMENTS_C'::h5sselect_elements_c - !DEC$ ENDIF - INTEGER(HID_T), INTENT(IN) :: space_id - INTEGER, INTENT(IN) :: operator - INTEGER(SIZE_T), INTENT(IN) :: num_elements - INTEGER(HSIZE_T),DIMENSION(*) :: c_c_coord - END FUNCTION h5sselect_elements_c - END INTERFACE - - ALLOCATE(c_coord(rank,num_elements), stat = error) - IF (error.NE. 0) THEN - hdferr = -1 - RETURN - ENDIF - DO i = 1, rank - c_coord(i,:) = coord(rank-i+1, :) - 1 - ENDDO - hdferr = h5sselect_elements_c(space_id, OPERATOR, num_elements, c_coord) + INTEGER, INTENT(OUT) :: hdferr ! Error code + INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:,:) :: c_coord + INTEGER :: error, i,j + INTERFACE + INTEGER FUNCTION h5sselect_elements_c(space_id, OPERATOR,& + num_elements,c_c_coord) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSELECT_ELEMENTS_C'::h5sselect_elements_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: space_id + INTEGER, INTENT(IN) :: OPERATOR + INTEGER(SIZE_T), INTENT(IN) :: num_elements + INTEGER(HSIZE_T),DIMENSION(*) :: c_c_coord + END FUNCTION h5sselect_elements_c + END INTERFACE + + ALLOCATE(c_coord(rank,num_elements), stat = error) + IF (error.NE. 0) THEN + hdferr = -1 + RETURN + ENDIF + DO i = 1, rank + c_coord(i,:) = coord(rank-i+1, :) - 1 + ENDDO + hdferr = h5sselect_elements_c(space_id, OPERATOR, num_elements, c_coord) + ! ALLOCATE(c_coord(num_elements,rank), stat = error) ! IF (error.NE. 0) THEN ! hdferr = -1 @@ -610,9 +607,9 @@ ! hdferr = h5sselect_elements_c(space_id, OPERATOR, INT(rank,size_t), c_coord) - DEALLOCATE(c_coord) + DEALLOCATE(c_coord) - END SUBROUTINE h5sselect_elements_f + END SUBROUTINE h5sselect_elements_f !---------------------------------------------------------------------- ! Name: h5sselect_all_f |