summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
authorQuincey Koziol <koziol@hdfgroup.org>2014-11-03 20:13:25 (GMT)
committerQuincey Koziol <koziol@hdfgroup.org>2014-11-03 20:13:25 (GMT)
commit89e2c8822ddacd982bd326be153e30fc5cbc3d3a (patch)
treecc0adbefb22b72392b505283eda0ebb1456bf5a4 /fortran/src/H5Sff.f90
parent2fcec016a8c827cae8bb0f0caa7c74b4dc005285 (diff)
downloadhdf5-89e2c8822ddacd982bd326be153e30fc5cbc3d3a.zip
hdf5-89e2c8822ddacd982bd326be153e30fc5cbc3d3a.tar.gz
hdf5-89e2c8822ddacd982bd326be153e30fc5cbc3d3a.tar.bz2
[svn-r25766] Description:
Revert r25273, 25283 & 25439 (the hyperslab improvement changes). They are buggy and it's taking me a long time to correct the problem. I'll check in a revised form of the changes when I've got them straightened out. Tested on: Mac OSX 10.10.0 (amazon) w/gcc 4.9.x, C++, FORTRAN Linux 2.6.x (jam) w/parallel
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f9014
1 files changed, 7 insertions, 7 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index 651c2c0..c493d46 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.f90
@@ -1611,7 +1611,7 @@ CONTAINS
! !$!****s* H5S/
! !$!
! !$! NAME
-! !$! h5smodify_select_f
+! !$! h5sselect_select_f
! !$!
! !$! PURPOSE
! !$! Refine a hyperslab selection with an operation
@@ -1648,7 +1648,7 @@ CONTAINS
! !$!
! ! SOURCE
-! SUBROUTINE h5smodify_select_f(space1_id, operator, space2_id, &
+! SUBROUTINE h5sselect_select_f(space1_id, operator, space2_id, &
! hdferr)
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to
@@ -1668,22 +1668,22 @@ CONTAINS
! INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTERFACE
-! INTEGER FUNCTION h5smodify_select_c(space1_id, operator, &
+! INTEGER FUNCTION h5sselect_select_c(space1_id, operator, &
! space2_id)
! USE H5GLOBAL
! !DEC$IF DEFINED(HDF5F90_WINDOWS)
-! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SMODIFY_SELECT_C'::h5smodify_select_c
+! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SSELECT_SELECT_C'::h5sselect_select_c
! !DEC$ENDIF
! INTEGER(HID_T), INTENT(INOUT) :: space1_id
! INTEGER(HID_T), INTENT(IN) :: space2_id
! INTEGER, INTENT(IN) :: operator
-! END FUNCTION h5smodify_select_c
+! END FUNCTION h5sselect_select_c
! END INTERFACE
-! hdferr = h5smodify_select_c(space1_id, operator, space2_id)
+! hdferr = h5sselect_select_c(space1_id, operator, space2_id)
! return
-! END SUBROUTINE h5smodify_select_f
+! END SUBROUTINE h5sselect_select_f
!
!****s* H5S/h5sget_select_type_f