summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-23 21:51:07 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-23 21:51:07 (GMT)
commit9b4a0aea49bc59063e066ae73c006525d71fb81a (patch)
tree3ad9e730284126b5a3027f97f65e8e2f5f7e2b75 /fortran/src/H5Sff.f90
parent44e038362ba43d2f247fb08ab6dca4b2140a9d15 (diff)
downloadhdf5-9b4a0aea49bc59063e066ae73c006525d71fb81a.zip
hdf5-9b4a0aea49bc59063e066ae73c006525d71fb81a.tar.gz
hdf5-9b4a0aea49bc59063e066ae73c006525d71fb81a.tar.bz2
[svn-r15687] Description:
Fixed nh5sget_select_hyper_blocklist_c nh5sget_select_elem_pointlist_ for bug 1319. by transposing arrays for C-FORTRAN convention.
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f9039
1 files changed, 22 insertions, 17 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index d21b9e1..003b946 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.f90
@@ -507,9 +507,6 @@
!List of element points selected
INTEGER, INTENT(OUT) :: hdferr ! Error code
-! INTEGER, EXTERNAL :: h5sget_select_elem_pointlist_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5sget_select_elem_pointlist_c(space_id, startpoint, &
num_points, buf )
@@ -526,6 +523,7 @@
hdferr = h5sget_select_elem_pointlist_c(space_id, startpoint, &
num_points, buf )
+
END SUBROUTINE h5sget_select_elem_pointlist_f
!----------------------------------------------------------------------
@@ -568,7 +566,7 @@
! 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
+ ! selected
INTEGER(HSIZE_T), &
DIMENSION(rank,num_elements), INTENT(IN) :: coord
! Array with the coordinates
@@ -578,9 +576,6 @@
INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:,:) :: c_coord
INTEGER :: error, i,j
-! INTEGER, EXTERNAL :: h5sselect_elements_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5sselect_elements_c(space_id, operator,&
num_elements,c_c_coord)
@@ -595,17 +590,27 @@
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
+ 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)
- deallocate(c_coord)
+ 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
+! RETURN
+! ENDIF
+!
+! c_coord = TRANSPOSE(coord)
+! hdferr = h5sselect_elements_c(space_id, OPERATOR, INT(rank,size_t), c_coord)
+
+
+ DEALLOCATE(c_coord)
END SUBROUTINE h5sselect_elements_f