summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
authorQuincey Koziol <koziol@hdfgroup.org>2010-01-30 04:11:10 (GMT)
committerQuincey Koziol <koziol@hdfgroup.org>2010-01-30 04:11:10 (GMT)
commit49d1722c303c7aed3b02052448111a0d1241df7a (patch)
tree848ea2afd8fa4cb38d60f97ab3cb43b11d5a579b /fortran/src/H5Sff.f90
parent855dd92b0e72771df86ec81f5334ffd2add1bfb7 (diff)
downloadhdf5-49d1722c303c7aed3b02052448111a0d1241df7a.zip
hdf5-49d1722c303c7aed3b02052448111a0d1241df7a.tar.gz
hdf5-49d1722c303c7aed3b02052448111a0d1241df7a.tar.bz2
[svn-r18195] Description:
Remove trailing whitespace from source code files. Tested on: None - just eyeballed
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f901146
1 files changed, 573 insertions, 573 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index c212d9a..91429e0 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.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,43 +11,43 @@
! 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. *
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
!
! This file contains Fortran90 interfaces for H5S functions.
-!
+!
MODULE H5S
USE H5GLOBAL
-
+
CONTAINS
-
+
!----------------------------------------------------------------------
-! Name: h5screate_simple_f
+! Name: h5screate_simple_f
!
! Purpose: Creates a new simple data space and opens it for access .
!
-! Inputs:
+! Inputs:
! rank - number of dimensions
! dims - an array of the size of each dimension
-! Outputs:
+! Outputs:
! space_id - dataspace identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! maxdims - an array of the maximum size of each
+! maxdims - an array of the maximum size of each
! dimension
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5screate_simple_f(rank, dims, space_id, hdferr, maxdims)
+ SUBROUTINE h5screate_simple_f(rank, dims, space_id, hdferr, maxdims)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -56,15 +56,15 @@
!
IMPLICIT NONE
- INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions
- INTEGER(HSIZE_T), INTENT(IN) :: dims(rank)
- ! Array with the dimension
- ! sizes
- INTEGER(HID_T), INTENT(OUT) :: space_id ! Dataspace identifier
+ INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions
+ INTEGER(HSIZE_T), INTENT(IN) :: dims(rank)
+ ! Array with the dimension
+ ! sizes
+ INTEGER(HID_T), INTENT(OUT) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HSIZE_T), OPTIONAL, INTENT(IN) :: maxdims(rank)
- ! Array with the maximum
- ! dimension sizes
+ INTEGER(HSIZE_T), OPTIONAL, INTENT(IN) :: maxdims(rank)
+ ! Array with the maximum
+ ! dimension sizes
INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:) :: f_maxdims
! INTEGER, EXTERNAL :: h5screate_simple_c
@@ -82,44 +82,44 @@
INTEGER(HID_T), INTENT(OUT) :: space_id
END FUNCTION h5screate_simple_c
END INTERFACE
-
+
allocate (f_maxdims(rank), stat=hdferr)
- if (hdferr .NE. 0) then
+ if (hdferr .NE. 0) then
hdferr = -1
return
- endif
- if (present(maxdims)) then
- f_maxdims = maxdims
+ endif
+ if (present(maxdims)) then
+ f_maxdims = maxdims
else
f_maxdims = dims
- endif
+ endif
hdferr = h5screate_simple_c(rank, dims, f_maxdims, space_id)
deallocate(f_maxdims)
END SUBROUTINE h5screate_simple_f
-
+
!----------------------------------------------------------------------
-! Name: h5sclose_f
+! Name: h5sclose_f
!
-! Purpose: Releases and terminates access to a dataspace.
+! Purpose: Releases and terminates access to a dataspace.
!
-! Inputs:
+! Inputs:
! space_id - identifier of dataspace to release
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sclose_f(space_id, hdferr)
@@ -152,31 +152,31 @@
END SUBROUTINE h5sclose_f
!----------------------------------------------------------------------
-! Name: h5screate_f
+! Name: h5screate_f
!
-! Purpose: Creates a new dataspace of a specified type.
+! Purpose: Creates a new dataspace of a specified type.
!
-! Inputs:
+! Inputs:
! classtype - the type of the dataspace to be created
-! Outputs:
+! Outputs:
! space_id - dataspace identifier
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5screate_f(classtype, space_id, hdferr)
+ SUBROUTINE h5screate_f(classtype, space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -186,12 +186,12 @@
IMPLICIT NONE
INTEGER, INTENT(IN) :: classtype ! The type of the dataspace
- ! to be created.
+ ! to be created.
! Possible values are:
! H5S_SCALAR_F (0)
! H5S_SIMPLE_F(1)
! H5S_NULL_F(2)
- INTEGER(HID_T), INTENT(OUT) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(OUT) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5screate_c
@@ -213,31 +213,31 @@
END SUBROUTINE h5screate_f
!----------------------------------------------------------------------
-! Name: h5scopy_f
+! Name: h5scopy_f
!
-! Purpose: Creates an exact copy of a dataspace.
+! Purpose: Creates an exact copy of a dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! new_space_id - identifier of dataspace's copy
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5scopy_f(space_id, new_space_id, hdferr)
+ SUBROUTINE h5scopy_f(space_id, new_space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -246,16 +246,16 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HID_T), INTENT(OUT) :: new_space_id
- ! Identifier of dataspace's copy
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(OUT) :: new_space_id
+ ! Identifier of dataspace's copy
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5scopy_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5scopy_c(space_id, new_space_id)
+ INTEGER FUNCTION h5scopy_c(space_id, new_space_id)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SCOPY_C'::h5scopy_c
@@ -266,35 +266,35 @@
END INTERFACE
hdferr = h5scopy_c(space_id, new_space_id)
-
+
END SUBROUTINE h5scopy_f
!----------------------------------------------------------------------
-! Name: h5sget_select_hyper_nblocks_f
+! Name: h5sget_select_hyper_nblocks_f
!
-! Purpose: Get number of hyperslab blocks.
+! Purpose: Get number of hyperslab blocks.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! num_blocks - number of hyperslab blocks in the current
! hyperslab selection
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_select_hyper_nblocks_f(space_id, num_blocks, hdferr)
+ SUBROUTINE h5sget_select_hyper_nblocks_f(space_id, num_blocks, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -303,11 +303,11 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks
- !number of hyperslab blocks
- !in the current dataspace
- !selection
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks
+ !number of hyperslab blocks
+ !in the current dataspace
+ !selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sget_select_hyper_nblocks_c
@@ -320,43 +320,43 @@
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_HYPER_NBLOCKS_C'::h5sget_select_hyper_nblocks_c
!DEC$ ENDIF
INTEGER(HID_T), INTENT(IN) :: space_id
- INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks
+ INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks
END FUNCTION h5sget_select_hyper_nblocks_c
END INTERFACE
hdferr = h5sget_select_hyper_nblocks_c (space_id, num_blocks)
-
+
END SUBROUTINE h5sget_select_hyper_nblocks_f
!----------------------------------------------------------------------
-! Name: h5sget_select_hyper_blocklist_f
+! Name: h5sget_select_hyper_blocklist_f
!
-! Purpose: Gets the list of hyperslab blocks currently selected.
+! Purpose: Gets the list of hyperslab blocks currently selected.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
! startblock - hyperslab block to start with
! num_blocks - number of blocks to get
-! Outputs:
+! Outputs:
! buf - buffer to hold block list
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sget_select_hyper_blocklist_f(space_id, startblock, &
- num_blocks, buf, hdferr)
+ num_blocks, buf, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -365,14 +365,14 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSIZE_T), INTENT(IN) :: startblock
- !Hyperslab block to start with.
- INTEGER(HSIZE_T), INTENT(IN) :: num_blocks
- !number of hyperslab blocks
- !to get in the current dataspace
- !selection
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSIZE_T), INTENT(IN) :: startblock
+ !Hyperslab block to start with.
+ INTEGER(HSIZE_T), INTENT(IN) :: num_blocks
+ !number of hyperslab blocks
+ !to get in the current dataspace
+ !selection
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
!List of hyperslab blocks selected
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -387,44 +387,44 @@
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_HYPER_BLOCKLIST_C'::h5sget_select_hyper_blocklist_c
!DEC$ ENDIF
- INTEGER(HID_T), INTENT(IN) :: space_id
- INTEGER(HSIZE_T), INTENT(IN) :: startblock
- INTEGER(HSIZE_T), INTENT(IN) :: num_blocks
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
+ INTEGER(HID_T), INTENT(IN) :: space_id
+ INTEGER(HSIZE_T), INTENT(IN) :: startblock
+ INTEGER(HSIZE_T), INTENT(IN) :: num_blocks
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
END FUNCTION h5sget_select_hyper_blocklist_c
END INTERFACE
-
+
hdferr = h5sget_select_hyper_blocklist_c(space_id, startblock, &
num_blocks, buf )
-
+
END SUBROUTINE h5sget_select_hyper_blocklist_f
!----------------------------------------------------------------------
-! Name: h5sget_select_bounds_f
+! Name: h5sget_select_bounds_f
!
-! Purpose: Gets the bounding box containing the current selection.
+! Purpose: Gets the bounding box containing the current selection.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-!
-! Outputs:
+!
+! Outputs:
! start - starting coordinates of bounding box
! end - ending coordinates of bounding box
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sget_select_bounds_f(space_id, start, end, hdferr)
@@ -436,13 +436,13 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start
- !Starting coordinates of the bounding box.
+ !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
+ !i.e., the coordinates of the diagonally
+ !opposite corner
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sget_select_bounds_c
@@ -461,35 +461,35 @@
END INTERFACE
hdferr = h5sget_select_bounds_c(space_id, start, end)
-
+
END SUBROUTINE h5sget_select_bounds_f
!----------------------------------------------------------------------
-! Name: h5sget_select_elem_npoints_f
+! Name: h5sget_select_elem_npoints_f
!
-! Purpose: Gets the number of element points in the current selection
+! Purpose: Gets the number of element points in the current selection
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
-! num_points - number of element points in the current
+! Outputs:
+! num_points - number of element points in the current
! dataspace selection
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_select_elem_npoints_f(space_id, num_points, hdferr)
+ SUBROUTINE h5sget_select_elem_npoints_f(space_id, num_points, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -498,11 +498,11 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSSIZE_T), INTENT(OUT) :: num_points
- !number of element points
- !in the current dataspace
- !selection
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSSIZE_T), INTENT(OUT) :: num_points
+ !number of element points
+ !in the current dataspace
+ !selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sget_select_elem_npoints_c
@@ -515,43 +515,43 @@
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_ELEM_NPOINTS_C'::h5sget_select_elem_npoints_c
!DEC$ ENDIF
INTEGER(HID_T), INTENT(IN) :: space_id
- INTEGER(HSSIZE_T), INTENT(OUT) :: num_points
+ INTEGER(HSSIZE_T), INTENT(OUT) :: num_points
END FUNCTION h5sget_select_elem_npoints_c
END INTERFACE
hdferr = h5sget_select_elem_npoints_c (space_id, num_points)
-
+
END SUBROUTINE h5sget_select_elem_npoints_f
!----------------------------------------------------------------------
-! Name: h5sget_select_elem_pointlist_f
+! Name: h5sget_select_elem_pointlist_f
!
-! Purpose: Gets the list of element points currently selected.
+! Purpose: Gets the list of element points currently selected.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! startpoint - element point to start with
+! startpoint - element point to start with
! num_points - number of elemnt points to get
-! Outputs:
+! Outputs:
! buf - buffer with element points selected
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sget_select_elem_pointlist_f(space_id, startpoint, &
- num_points, buf, hdferr)
+ num_points, buf, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -559,12 +559,12 @@
!DEC$endif
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSIZE_T), INTENT(IN) :: startpoint
- !Element point to start with.
- INTEGER(HSIZE_T), INTENT(IN) :: num_points
- !Number of element points to get
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSIZE_T), INTENT(IN) :: startpoint
+ !Element point to start with.
+ INTEGER(HSIZE_T), INTENT(IN) :: num_points
+ !Number of element points to get
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
!List of element points selected
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -579,9 +579,9 @@
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_ELEM_POINTLIST_C'::h5sget_select_elem_pointlist_c
!DEC$ ENDIF
INTEGER(HID_T), INTENT(IN) :: space_id
- INTEGER(HSIZE_T), INTENT(IN) :: startpoint
- INTEGER(HSIZE_T), INTENT(IN) :: num_points
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
+ INTEGER(HSIZE_T), INTENT(IN) :: startpoint
+ INTEGER(HSIZE_T), INTENT(IN) :: num_points
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
END FUNCTION h5sget_select_elem_pointlist_c
END INTERFACE
@@ -590,38 +590,38 @@
END SUBROUTINE h5sget_select_elem_pointlist_f
!----------------------------------------------------------------------
-! Name: h5sselect_elements_f
+! Name: h5sselect_elements_f
!
-! Purpose: Selects elements to be included in the selection for
-! a dataspace
+! Purpose: Selects elements to be included in the selection for
+! a dataspace
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
! operator - flag, valid values are:
! H5S_SELECT_SET_F (0)
! H5S_SELECT_OR_F (1)
! rank - number of dataspace dimensions
! num_elements - number of elements to be selected
-! coord - 2D (rank x num_elements) array with the
+! coord - 2D (rank x num_elements) array with the
! elements coordinates
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sselect_elements_f(space_id, operator, rank, &
- num_elements, coord, hdferr)
+ SUBROUTINE h5sselect_elements_f(space_id, operator, rank, &
+ num_elements, coord, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -629,15 +629,15 @@
!DEC$endif
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ 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, 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
+ INTEGER(HSIZE_T), &
+ DIMENSION(rank,num_elements), INTENT(IN) :: coord
! Array with the coordinates
! of the selected elements
! coord(rank, num_elements)
@@ -669,39 +669,39 @@
endif
do i = 1, rank
c_coord(i,:) = coord(rank-i+1, :) - 1
- enddo
+ enddo
hdferr = h5sselect_elements_c(space_id, operator, num_elements, &
c_coord)
deallocate(c_coord)
-
+
END SUBROUTINE h5sselect_elements_f
!----------------------------------------------------------------------
-! Name: h5sselect_all_f
+! Name: h5sselect_all_f
!
-! Purpose: Selects the entire dataspace.
+! Purpose: Selects the entire dataspace.
!
-! Inputs:
+! Inputs:
! space_id - identifier for the dataspace in which
! selection being made
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sselect_all_f(space_id, hdferr)
+ SUBROUTINE h5sselect_all_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -709,7 +709,7 @@
!DEC$endif
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sselect_all_c
@@ -730,31 +730,31 @@
END SUBROUTINE h5sselect_all_f
!----------------------------------------------------------------------
-! Name: h5sselect_none_f
+! Name: h5sselect_none_f
!
-! Purpose: Resets the selection region to include no elements.
+! Purpose: Resets the selection region to include no elements.
!
-! Inputs:
-! space_id - the identifier for the dataspace in which
-! the selection is being reset.
-! Outputs:
-! hdferr: - error code
+! Inputs:
+! space_id - the identifier for the dataspace in which
+! the selection is being reset.
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sselect_none_f(space_id, hdferr)
+ SUBROUTINE h5sselect_none_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -763,7 +763,7 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sselect_none_c
@@ -775,7 +775,7 @@
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSELECT_NONE_C'::h5sselect_none_c
!DEC$ ENDIF
- INTEGER(HID_T), INTENT(IN) :: space_id
+ INTEGER(HID_T), INTENT(IN) :: space_id
END FUNCTION h5sselect_none_c
END INTERFACE
@@ -784,31 +784,31 @@
END SUBROUTINE h5sselect_none_f
!----------------------------------------------------------------------
-! Name: h5sselect_valid_f
+! Name: h5sselect_valid_f
!
-! Purpose: Verifies that the selection is within the extent of
-! the dataspace.
+! Purpose: Verifies that the selection is within the extent of
+! the dataspace.
!
-! Inputs:
-! space_id - identifier for the dataspace for which
+! Inputs:
+! space_id - identifier for the dataspace for which
! selection is verified
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sselect_valid_f(space_id, status, hdferr)
+ SUBROUTINE h5sselect_valid_f(space_id, status, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -817,10 +817,10 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
LOGICAL, INTENT(OUT) :: status ! TRUE if the selection is
! contained within the extent,
- ! FALSE otherwise.
+ ! FALSE otherwise.
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER :: flag ! "TRUE/FALSE/ERROR" flag from C routine
@@ -828,14 +828,14 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sselect_valid_c(space_id, flag)
+ INTEGER FUNCTION h5sselect_valid_c(space_id, flag)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSELECT_VALID_C'::h5sselect_valid_c
!DEC$ ENDIF
INTEGER(HID_T), INTENT(IN) :: space_id
INTEGER :: flag
- END FUNCTION h5sselect_valid_c
+ END FUNCTION h5sselect_valid_c
END INTERFACE
hdferr = h5sselect_valid_c(space_id, flag)
@@ -845,31 +845,31 @@
END SUBROUTINE h5sselect_valid_f
!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_npoints_f
+! Name: h5sget_simple_extent_npoints_f
!
-! Purpose: Determines the number of elements in a dataspace.
+! Purpose: Determines the number of elements in a dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! npoints - number of elements in the dataspace
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_simple_extent_npoints_f(space_id, npoints, hdferr)
+ SUBROUTINE h5sget_simple_extent_npoints_f(space_id, npoints, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -878,8 +878,8 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSIZE_T), INTENT(OUT) :: npoints ! Number of elements in
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSIZE_T), INTENT(OUT) :: npoints ! Number of elements in
! dataspace
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -887,7 +887,7 @@
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sget_simple_extent_npoints_c( space_id, npoints)
+ INTEGER FUNCTION h5sget_simple_extent_npoints_c( space_id, npoints)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SIMPLE_EXTENT_NPOINTS_C'::h5sget_simple_extent_npoints_c
@@ -898,35 +898,35 @@
END INTERFACE
hdferr = h5sget_simple_extent_npoints_c( space_id, npoints)
-
+
END SUBROUTINE h5sget_simple_extent_npoints_f
!----------------------------------------------------------------------
-! Name: h5sget_select_npoints_f
+! Name: h5sget_select_npoints_f
!
-! Purpose: Determines the number of elements in a dataspace selection.
+! Purpose: Determines the number of elements in a dataspace selection.
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
+! Inputs:
+! space_id - dataspace identifier
+! Outputs:
! npoints - number of points in the dataspace selection
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_select_npoints_f(space_id, npoints, hdferr)
+ SUBROUTINE h5sget_select_npoints_f(space_id, npoints, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -935,16 +935,16 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER(HSSIZE_T), INTENT(OUT) :: npoints ! Number of elements in the
- ! selection
+ ! selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sget_select_npoints_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sget_select_npoints_c(space_id, npoints)
+ INTEGER FUNCTION h5sget_select_npoints_c(space_id, npoints)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_NPOINTS_C'::h5sget_select_npoints_c
@@ -955,35 +955,35 @@
END INTERFACE
hdferr = h5sget_select_npoints_c(space_id, npoints)
-
+
END SUBROUTINE h5sget_select_npoints_f
!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_ndims_f
+! Name: h5sget_simple_extent_ndims_f
!
-! Purpose: Determines the dimensionality of a dataspace
+! Purpose: Determines the dimensionality of a dataspace
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! rank - number of dataspace dimensions
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
+ SUBROUTINE h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -992,15 +992,15 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER, INTENT(OUT) :: rank ! Number of dimensions
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER, INTENT(OUT) :: rank ! Number of dimensions
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sget_simple_extent_ndims_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sget_simple_extent_ndims_c(space_id, rank)
+ INTEGER FUNCTION h5sget_simple_extent_ndims_c(space_id, rank)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SGET_SIMPLE_EXTENT_NDIMS_C'::h5sget_simple_extent_ndims_c
@@ -1011,37 +1011,37 @@
END INTERFACE
hdferr = h5sget_simple_extent_ndims_c(space_id, rank)
-
+
END SUBROUTINE h5sget_simple_extent_ndims_f
!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_dims_f
+! Name: h5sget_simple_extent_dims_f
!
-! Purpose: Retrieves dataspace dimension size and maximum size.
+! Purpose: Retrieves dataspace dimension size and maximum size.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! dims - array to store size of each dimension
-! maxdims - array to store maximum size of each
+! maxdims - array to store maximum size of each
! dimension
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_simple_extent_dims_f(space_id, dims, maxdims, hdferr)
+ SUBROUTINE h5sget_simple_extent_dims_f(space_id, dims, maxdims, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1050,12 +1050,12 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: dims
- ! Array to store dimension sizes
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: maxdims
- ! Array to store max dimension
- ! sizes
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: dims
+ ! Array to store dimension sizes
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: maxdims
+ ! Array to store max dimension
+ ! sizes
INTEGER, INTENT(OUT) :: hdferr ! Error code: -1 on failure,
! number of dimensions on
! on success
@@ -1076,39 +1076,39 @@
END INTERFACE
hdferr = h5sget_simple_extent_dims_c(space_id, dims, maxdims)
-
+
END SUBROUTINE h5sget_simple_extent_dims_f
!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_type_f
+! Name: h5sget_simple_extent_type_f
!
-! Purpose: Determine the current class of a dataspace
+! Purpose: Determine the current class of a dataspace
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! classtype - class type, possible values are:
! H5S_NO_CLASS_F (-1)
! H5S_SCALAR_F (0)
! H5S_SIMPLE_F (1)
! H5S_NULL_F (2)
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_simple_extent_type_f(space_id, classtype, hdferr)
+ SUBROUTINE h5sget_simple_extent_type_f(space_id, classtype, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1117,9 +1117,9 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: classtype ! Class type , possible values
- ! are:
+ ! are:
! H5S_NO_CLASS_F (-1)
! H5S_SCALAR_F (0)
! H5S_SIMPLE_F (1)
@@ -1141,39 +1141,39 @@
END INTERFACE
hdferr = h5sget_simple_extent_type_c(space_id, classtype)
-
+
END SUBROUTINE h5sget_simple_extent_type_f
!----------------------------------------------------------------------
-! Name: h5sset_extent_simple_f
+! Name: h5sset_extent_simple_f
!
-! Purpose: Sets or resets the size of an existing dataspace.
+! Purpose: Sets or resets the size of an existing dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
! rank - dataspace number of dimensions
! current_size - array with the new sizes of dimensions
-! maximum_size - array with the new maximum sizes of
+! maximum_size - array with the new maximum sizes of
! dimensions
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sset_extent_simple_f(space_id, rank, current_size, &
- maximum_size, hdferr)
+ maximum_size, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1182,15 +1182,15 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
- INTEGER, INTENT(IN) :: rank ! Dataspace rank
- INTEGER(HSIZE_T), DIMENSION(rank), INTENT(IN) :: current_size
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER, INTENT(IN) :: rank ! Dataspace rank
+ INTEGER(HSIZE_T), DIMENSION(rank), INTENT(IN) :: current_size
! Array with the new sizes
- ! of dimensions
- INTEGER(HSIZE_T), DIMENSION(rank), INTENT(IN) :: maximum_size
+ ! of dimensions
+ INTEGER(HSIZE_T), DIMENSION(rank), INTENT(IN) :: maximum_size
! Array with the new maximum
- ! sizes of dimensions
- ! sizes
+ ! sizes of dimensions
+ ! sizes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sset_extent_simple_c
@@ -1198,7 +1198,7 @@
!
INTERFACE
INTEGER FUNCTION h5sset_extent_simple_c(space_id, rank, &
- current_size, maximum_size)
+ current_size, maximum_size)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSET_EXTENT_SIMPLE_C'::h5sset_extent_simple_c
@@ -1212,36 +1212,36 @@
hdferr = h5sset_extent_simple_c(space_id, rank, current_size, &
maximum_size)
-
+
END SUBROUTINE h5sset_extent_simple_f
!----------------------------------------------------------------------
-! Name: h5sis_simple_f
+! Name: h5sis_simple_f
!
-! Purpose: Determines whether a dataspace is a simple dataspace.
+! Purpose: Determines whether a dataspace is a simple dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
+! Outputs:
! status - flag to indicate if dataspace
-! is simple or not
-! hdferr: - error code
+! is simple or not
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sis_simple_f(space_id, status, hdferr)
+ SUBROUTINE h5sis_simple_f(space_id, status, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1250,18 +1250,18 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
LOGICAL, INTENT(OUT) :: status ! Flag, idicates if dataspace
! is simple or not ( TRUE or
- ! FALSE)
+ ! FALSE)
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER :: flag ! "TRUE/FALSE/ERROR from C"
+ INTEGER :: flag ! "TRUE/FALSE/ERROR from C"
! INTEGER, EXTERNAL :: h5sis_simple_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sis_simple_c(space_id, flag)
+ INTEGER FUNCTION h5sis_simple_c(space_id, flag)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SIS_SIMPLE_C'::h5sis_simple_c
@@ -1274,35 +1274,35 @@
hdferr = h5sis_simple_c(space_id, flag)
status = .TRUE.
if (flag .EQ. 0) status = .FALSE.
-
+
END SUBROUTINE h5sis_simple_f
!----------------------------------------------------------------------
-! Name: h5soffset_simple_f
+! Name: h5soffset_simple_f
!
-! Purpose: Sets the offset of a simple dataspace.
+! Purpose: Sets the offset of a simple dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! offset - the offset at which to position the
-! selection
-! Outputs:
-! hdferr: - error code
+! offset - the offset at which to position the
+! selection
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5soffset_simple_f(space_id, offset, hdferr)
+ SUBROUTINE h5soffset_simple_f(space_id, offset, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1311,17 +1311,17 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER(HSSIZE_T), DIMENSION(*), INTENT(IN) :: offset
! The offset at which to position
- ! the selection
+ ! the selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5soffset_simple_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5soffset_simple_c(space_id, offset)
+ INTEGER FUNCTION h5soffset_simple_c(space_id, offset)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SOFFSET_SIMPLE_C'::h5soffset_simple_c
@@ -1332,37 +1332,37 @@
END INTERFACE
hdferr = h5soffset_simple_c(space_id, offset)
-
+
END SUBROUTINE h5soffset_simple_f
!----------------------------------------------------------------------
-! Name: h5sextent_copy_f
+! Name: h5sextent_copy_f
!
-! Purpose: Copies the extent of a dataspace.
+! Purpose: Copies the extent of a dataspace.
!
-! Inputs:
-! dest_space_id - the identifier for the dataspace to which
-! the extent is copied
-! source_space_id - the identifier for the dataspace from
+! Inputs:
+! dest_space_id - the identifier for the dataspace to which
+! the extent is copied
+! source_space_id - the identifier for the dataspace from
! which the extent is copied
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sextent_copy_f(dest_space_id, source_space_id, hdferr)
+ SUBROUTINE h5sextent_copy_f(dest_space_id, source_space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1373,7 +1373,7 @@
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dest_space_id ! Identifier of destination
! dataspace
- INTEGER(HID_T), INTENT(IN) :: source_space_id ! Identifier of source
+ INTEGER(HID_T), INTENT(IN) :: source_space_id ! Identifier of source
! dataspace
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1392,33 +1392,33 @@
END INTERFACE
hdferr = h5sextent_copy_c(dest_space_id, source_space_id)
-
+
END SUBROUTINE h5sextent_copy_f
!----------------------------------------------------------------------
-! Name: h5sset_extent_none_f
+! Name: h5sset_extent_none_f
!
-! Purpose: Removes the extent from a dataspace.
+! Purpose: Removes the extent from a dataspace.
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sset_extent_none_f(space_id, hdferr)
+ SUBROUTINE h5sset_extent_none_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1427,14 +1427,14 @@
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5sset_extent_none_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5sset_extent_none_c(space_id)
+ INTEGER FUNCTION h5sset_extent_none_c(space_id)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SSET_EXTENT_NONE_C'::h5sset_extent_none_c
@@ -1444,43 +1444,43 @@
END INTERFACE
hdferr = h5sset_extent_none_c(space_id)
-
+
END SUBROUTINE h5sset_extent_none_f
!----------------------------------------------------------------------
-! Name: h5sselect_hyperslab_f
+! Name: h5sselect_hyperslab_f
!
-! Purpose: Selects a hyperslab region to add to the current selected
-! region
+! Purpose: Selects a hyperslab region to add to the current selected
+! region
!
-! Inputs:
+! Inputs:
! space_id - dataspace identifier
! operator - flag, valid values are:
! H5S_SELECT_SET_F (0)
! H5S_SELECT_OR_F (1)
! start - array with hyperslab offsets
-! count - number of blocks included in the
+! count - number of blocks included in the
! hyperslab
-! Outputs:
-! hdferr: - error code
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! stride - array with hyperslab strides
-! block - array with hyperslab block sizes
+! block - array with hyperslab block sizes
!
! Programmer: Elena Pourmal
-! August 12, 1999
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
+! Modifications: Explicit Fortran interfaces were added for
! called C functions (it is needed for Windows
-! port). March 6, 2001
+! port). March 6, 2001
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sselect_hyperslab_f(space_id, operator, start, count, &
- hdferr, stride, block)
+ hdferr, stride, block)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1488,26 +1488,26 @@
!DEC$endif
!
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+ 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(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
- ! Starting coordinates of the hyperslab
- INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
- ! Number of blocks to select
- ! from dataspace
+ ! Starting coordinates of the hyperslab
+ INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
+ ! Number of blocks to select
+ ! from dataspace
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: stride
! Array of how many elements to move
! in each direction
- INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: block
+ INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: block
! Sizes of element block
- INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_block
+ INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_block
INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_stride
INTEGER :: rank
- INTEGER :: error1, error2
+ INTEGER :: error1, error2
! INTEGER, EXTERNAL :: h5sselect_hyperslab_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1524,7 +1524,7 @@
INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: stride
- INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: block
+ INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: block
END FUNCTION h5sselect_hyperslab_c
END INTERFACE
@@ -1578,48 +1578,48 @@
def_stride, def_block)
deallocate(def_block)
deallocate(def_stride)
-
+
END SUBROUTINE h5sselect_hyperslab_f
!----------------------------------------------------------------------
-! Name: h5scombine_hyperslab_f
+! Name: h5scombine_hyperslab_f
!
-! Purpose: Combine a hyperslab selection with the current
-! selection for a dataspace
+! Purpose: Combine a hyperslab selection with the current
+! selection for a dataspace
!
-! Inputs:
-! space_id - dataspace of selection to use
+! Inputs:
+! space_id - dataspace of selection to use
! operator - flag, valid values are:
-! H5S_SELECT_NOOP_F
-! H5S_SELECT_SET_F
-! H5S_SELECT_OR_F
-! H5S_SELECT_AND_F
-! H5S_SELECT_XOR_F
-! H5S_SELECT_NOTB_F
-! H5S_SELECT_NOTA_F
-! H5S_SELECT_APPEND_F
-! H5S_SELECT_PREPEND_F
+! H5S_SELECT_NOOP_F
+! H5S_SELECT_SET_F
+! H5S_SELECT_OR_F
+! H5S_SELECT_AND_F
+! H5S_SELECT_XOR_F
+! H5S_SELECT_NOTB_F
+! H5S_SELECT_NOTA_F
+! H5S_SELECT_APPEND_F
+! H5S_SELECT_PREPEND_F
! start - array with hyperslab offsets
-! count - number of blocks included in the
+! count - number of blocks included in the
! hyperslab
-! Outputs:
+! Outputs:
! hyper_id - identifier for the new hyperslab
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! stride - array with hyperslab strides
-! block - array with hyperslab block sizes
+! block - array with hyperslab block sizes
!
! Programmer: Elena Pourmal
! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment: Commented out until 1.6 ? 10/08/2002
+! Comment: Commented out until 1.6 ? 10/08/2002
!----------------------------------------------------------------------
! SUBROUTINE h5scombine_hyperslab_f(space_id, operator, start, count, &
-! hyper_id, hdferr, stride, block)
+! hyper_id, hdferr, stride, block)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1627,34 +1627,34 @@
!DEC$endif
!
! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
+! INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
- ! H5S_SELECT_NOOP_F
- ! H5S_SELECT_SET_F
- ! H5S_SELECT_OR_F
- ! H5S_SELECT_AND_F
- ! H5S_SELECT_XOR_F
- ! H5S_SELECT_NOTB_F
- ! H5S_SELECT_NOTA_F
- ! H5S_SELECT_APPEND_F
- ! H5S_SELECT_PREPEND_F
- !
+ ! H5S_SELECT_NOOP_F
+ ! H5S_SELECT_SET_F
+ ! H5S_SELECT_OR_F
+ ! H5S_SELECT_AND_F
+ ! H5S_SELECT_XOR_F
+ ! H5S_SELECT_NOTB_F
+ ! H5S_SELECT_NOTA_F
+ ! H5S_SELECT_APPEND_F
+ ! H5S_SELECT_PREPEND_F
+ !
! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
- ! Starting coordinates of the hyperslab
-! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
- ! Number of blocks to select
- ! from dataspace
-! INTEGER(HID_T), INTENT(OUT) :: hyper_id ! New hyperslab identifier
+ ! Starting coordinates of the hyperslab
+! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
+ ! Number of blocks to select
+ ! from dataspace
+! INTEGER(HID_T), INTENT(OUT) :: hyper_id ! New hyperslab identifier
! INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: stride
! Array of how many elements to move
! in each direction
-! INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: block
+! INTEGER(HSIZE_T), DIMENSION(:), OPTIONAL, INTENT(IN) :: block
! Sizes of element block
-! INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_block
+! INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_block
! INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_stride
! INTEGER :: rank
-! INTEGER :: error1, error2
+! INTEGER :: error1, error2
! INTERFACE
! INTEGER FUNCTION h5scombine_hyperslab_c(space_id, operator, &
@@ -1668,7 +1668,7 @@
! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
! INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: stride
-! INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: block
+! INTEGER(HSIZE_T), DIMENSION(*), OPTIONAL, INTENT(IN) :: block
! INTEGER(HID_T), INTENT(OUT) :: hyper_id
! END FUNCTION h5scombine_hyperslab_c
! END INTERFACE
@@ -1723,45 +1723,45 @@
! def_stride, def_block, hyper_id)
! deallocate(def_block)
! deallocate(def_stride)
-
+
! END SUBROUTINE h5scombine_hyperslab_f
!----------------------------------------------------------------------
-! Name: h5scombine_select_f
+! Name: h5scombine_select_f
!
-! Purpose: Combine two hyperslab selections with an operation
+! Purpose: Combine two hyperslab selections with an operation
! and return a dataspace with resulting selection.
!
-! Inputs:
-! space1_id - dataspace of selection to use
+! Inputs:
+! space1_id - dataspace of selection to use
! operator - flag, valid values are:
-! H5S_SELECT_NOOP_F
-! H5S_SELECT_SET_F
-! H5S_SELECT_OR_F
-! H5S_SELECT_AND_F
-! H5S_SELECT_XOR_F
-! H5S_SELECT_NOTB_F
-! H5S_SELECT_NOTA_F
-! H5S_SELECT_APPEND_F
-! H5S_SELECT_PREPEND_F
-! space2_id - dataspace of selection to use
-! Outputs:
+! H5S_SELECT_NOOP_F
+! H5S_SELECT_SET_F
+! H5S_SELECT_OR_F
+! H5S_SELECT_AND_F
+! H5S_SELECT_XOR_F
+! H5S_SELECT_NOTB_F
+! H5S_SELECT_NOTA_F
+! H5S_SELECT_APPEND_F
+! H5S_SELECT_PREPEND_F
+! space2_id - dataspace of selection to use
+! Outputs:
! ds_id - idataspace identifier with the new selection
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters: - NONE
!
! Programmer: Elena Pourmal
! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment: commented out until 1.6 release(?) 10/08/2002
+! Comment: commented out until 1.6 release(?) 10/08/2002
!----------------------------------------------------------------------
! SUBROUTINE h5scombine_select_f(space1_id, operator, space2_id, &
-! ds_id, hdferr)
+! ds_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1769,20 +1769,20 @@
!DEC$endif
!
! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier
-! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
+! INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier
+! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
- ! H5S_SELECT_NOOP_F
- ! H5S_SELECT_SET_F
- ! H5S_SELECT_OR_F
- ! H5S_SELECT_AND_F
- ! H5S_SELECT_XOR_F
- ! H5S_SELECT_NOTB_F
- ! H5S_SELECT_NOTA_F
- ! H5S_SELECT_APPEND_F
- ! H5S_SELECT_PREPEND_F
- !
-! INTEGER(HID_T), INTENT(OUT) :: ds_id ! New dataspace identifier
+ ! H5S_SELECT_NOOP_F
+ ! H5S_SELECT_SET_F
+ ! H5S_SELECT_OR_F
+ ! H5S_SELECT_AND_F
+ ! H5S_SELECT_XOR_F
+ ! H5S_SELECT_NOTB_F
+ ! H5S_SELECT_NOTA_F
+ ! H5S_SELECT_APPEND_F
+ ! H5S_SELECT_PREPEND_F
+ !
+! INTEGER(HID_T), INTENT(OUT) :: ds_id ! New dataspace identifier
! INTEGER, INTENT(OUT) :: hdferr ! Error code
!
! INTERFACE
@@ -1802,45 +1802,45 @@
! hdferr = h5scombine_select_c(space1_id, operator, space2_id, &
! ds_id)
! return
-
+
! END SUBROUTINE h5scombine_select_f
!----------------------------------------------------------------------
-! Name: h5sselect_select_f
+! Name: h5sselect_select_f
!
-! Purpose: Refine a hyperslab selection with an operation
+! Purpose: Refine a hyperslab selection with an operation
! using second hyperslab
!
-! Inputs:
+! Inputs:
! space1_id - dataspace of selection to modify
! operator - flag, valid values are:
-! H5S_SELECT_NOOP_F
-! H5S_SELECT_SET_F
-! H5S_SELECT_OR_F
-! H5S_SELECT_AND_F
-! H5S_SELECT_XOR_F
-! H5S_SELECT_NOTB_F
-! H5S_SELECT_NOTA_F
-! H5S_SELECT_APPEND_F
-! H5S_SELECT_PREPEND_F
-! space2_id - dataspace of selection to use
-!
-! Outputs:
-! hdferr: - error code
+! H5S_SELECT_NOOP_F
+! H5S_SELECT_SET_F
+! H5S_SELECT_OR_F
+! H5S_SELECT_AND_F
+! H5S_SELECT_XOR_F
+! H5S_SELECT_NOTB_F
+! H5S_SELECT_NOTA_F
+! H5S_SELECT_APPEND_F
+! H5S_SELECT_PREPEND_F
+! space2_id - dataspace of selection to use
+!
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters: - NONE
!
! Programmer: Elena Pourmal
! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:Commented out until 1.6 release(?) 10/08/2002 EIP
+! Comment:Commented out until 1.6 release(?) 10/08/2002 EIP
!----------------------------------------------------------------------
! SUBROUTINE h5sselect_select_f(space1_id, operator, space2_id, &
-! hdferr)
+! hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1849,19 +1849,19 @@
!
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to
- ! modify
-! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
+ ! modify
+! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
- ! H5S_SELECT_NOOP_F
- ! H5S_SELECT_SET_F
- ! H5S_SELECT_OR_F
- ! H5S_SELECT_AND_F
- ! H5S_SELECT_XOR_F
- ! H5S_SELECT_NOTB_F
- ! H5S_SELECT_NOTA_F
- ! H5S_SELECT_APPEND_F
- ! H5S_SELECT_PREPEND_F
- !
+ ! H5S_SELECT_NOOP_F
+ ! H5S_SELECT_SET_F
+ ! H5S_SELECT_OR_F
+ ! H5S_SELECT_AND_F
+ ! H5S_SELECT_XOR_F
+ ! H5S_SELECT_NOTB_F
+ ! H5S_SELECT_NOTA_F
+ ! H5S_SELECT_APPEND_F
+ ! H5S_SELECT_PREPEND_F
+ !
! INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTERFACE
@@ -1879,37 +1879,37 @@
! hdferr = h5sselect_select_c(space1_id, operator, space2_id)
! return
-
+
! END SUBROUTINE h5sselect_select_f
!----------------------------------------------------------------------
-! Name: h5sget_select_type_f
+! Name: h5sget_select_type_f
!
! Purpose: Retrieve the type of selection
!
-! Inputs:
+! Inputs:
! space_id - dataspace iidentifier with selection
-! Outputs:
+! Outputs:
! type - flag, valid values are:
-! H5S_SEL_ERROR_F
-! H5S_SEL_NONE_F
-! H5S_SEL_POINTS_F
-! H5S_SEL_HYPERSLABS_F
-! H5S_SEL_ALL_F
-! hdferr: - error code
+! H5S_SEL_ERROR_F
+! H5S_SEL_NONE_F
+! H5S_SEL_POINTS_F
+! H5S_SEL_HYPERSLABS_F
+! H5S_SEL_ALL_F
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters: - NONE
!
! Programmer: Elena Pourmal
! October 7, 2002
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sget_select_type_f(space_id, type, hdferr)
+ SUBROUTINE h5sget_select_type_f(space_id, type, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1919,11 +1919,11 @@
IMPLICIT NONE
INTEGER(HID_T), INTENT(INOUT) :: space_id ! Dataspace identifier to
INTEGER, INTENT(OUT) :: type ! Selection type
- ! H5S_SEL_ERROR_F
- ! H5S_SEL_NONE_F
- ! H5S_SEL_POINTS_F
- ! H5S_SEL_HYPERSLABS_F
- ! H5S_SEL_ALL_F
+ ! H5S_SEL_ERROR_F
+ ! H5S_SEL_NONE_F
+ ! H5S_SEL_POINTS_F
+ ! H5S_SEL_HYPERSLABS_F
+ ! H5S_SEL_ALL_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
INTERFACE
@@ -1939,7 +1939,7 @@
hdferr = h5sget_select_type_c(space_id, type)
return
-
+
END SUBROUTINE h5sget_select_type_f
!----------------------------------------------------------------------
@@ -1947,11 +1947,11 @@
!
! Purpose: Decode a binary object description of data space and return a new object handle.
!
-! Inputs:
+! Inputs:
! buf - Buffer for the data space object to be decoded.
! obj_id - Object ID
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
!
@@ -1960,12 +1960,12 @@
! Programmer: M.S. Breitenfeld
! March 26, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sdecode_f(buf, obj_id, hdferr)
+ SUBROUTINE h5sdecode_f(buf, obj_id, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -1989,7 +1989,7 @@
END INTERFACE
hdferr = h5sdecode_c(buf, obj_id)
-
+
END SUBROUTINE h5sdecode_f
!----------------------------------------------------------------------
@@ -2003,7 +2003,7 @@
! nalloc - The size of the allocated buffer.
! Outputs:
! nalloc - The size of the buffer needed.
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
! Failure: -1
!
@@ -2012,12 +2012,12 @@
! Programmer: M.S. Breitenfeld
! March 26, 2008
!
-! Modifications:
+! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr)
+ SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr)
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
@@ -2042,25 +2042,25 @@
INTEGER(SIZE_T), INTENT(INOUT) :: nalloc
END FUNCTION h5sencode_c
END INTERFACE
-
+
hdferr = h5sencode_c(buf, obj_id, nalloc)
END SUBROUTINE h5sencode_f
-
+
!----------------------------------------------------------------------
-! Name: h5sextent_equal_f
+! Name: h5sextent_equal_f
!
! Purpose: Determines whether two dataspace extents are equal.
!
-! Inputs:
+! Inputs:
! space1_id - First dataspace identifier.
! space2_id - Second dataspace identifier.
-! Outputs:
+! Outputs:
! Equal - .TRUE. if equal, .FALSE. if unequal.
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! NONE
!
@@ -2069,7 +2069,7 @@
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5sextent_equal_f(space1_id, space2_id, equal, hdferr)
@@ -2098,14 +2098,14 @@
INTEGER(HID_T) :: c_equal
END FUNCTION h5sextent_equal_c
END INTERFACE
-
+
hdferr = h5sextent_equal_c(space1_id, space2_id, c_equal)
-
+
equal = .FALSE.
- IF(c_equal.GT.0) equal = .TRUE.
+ IF(c_equal.GT.0) equal = .TRUE.
+
-
END SUBROUTINE h5sextent_equal_f
END MODULE H5S