summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f901880
1 files changed, 928 insertions, 952 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index 06bebef..9ef8ca8 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.f90
@@ -1,3 +1,18 @@
+!****h* ROBODoc/H5S
+!
+! NAME
+! MODULE H5S
+!
+! FILE
+! fortran/src/H5Sff.f90
+!
+! PURPOSE
+! This file contains Fortran interfaces for H5S functions. It includes
+! all the functions that are independent on whether the Fortran 2003 functions
+! are enabled or disabled.
+!
+!
+! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
@@ -13,44 +28,50 @@
! access to either file, you may request a copy from help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
+! NOTES
+! *** IMPORTANT ***
+! If you add a new H5S function you must add the function name to the
+! Windows dll file 'hdf5_fortrandll.def' in the fortran/src directory.
+! This is needed for Windows based operating systems.
!
-! This file contains Fortran90 interfaces for H5S functions.
-!
- MODULE H5S
- USE H5GLOBAL
+!*****
- CONTAINS
+MODULE H5S
+ USE H5GLOBAL
-!----------------------------------------------------------------------
-! Name: h5screate_simple_f
+CONTAINS
+
+!
+!****s* H5S/h5screate_simple_f
!
-! Purpose: Creates a new simple data space and opens it for access .
+! NAME
+! h5screate_simple_f
!
-! Inputs:
-! rank - number of dimensions
-! dims - an array of the size of each dimension
-! Outputs:
-! space_id - dataspace identifier
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! maxdims - an array of the maximum size of each
-! dimension
+! PURPOSE
+! Creates a new simple data space and opens it for access .
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! INPUTS
+! rank - number of dimensions
+! dims - an array of the size of each dimension
+! OUTPUTS
+! space_id - dataspace identifier
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! maxdims - an array of the maximum size of each dimension
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+! SOURCE
SUBROUTINE h5screate_simple_f(rank, dims, space_id, hdferr, maxdims)
IMPLICIT NONE
- INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions
+ INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions
INTEGER(HSIZE_T), INTENT(IN) :: dims(rank)
! Array with the dimension
! sizes
@@ -59,11 +80,9 @@
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
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5screate_simple_c(rank, dims, maxdims, space_id)
USE H5GLOBAL
@@ -92,38 +111,34 @@
END SUBROUTINE h5screate_simple_f
-!----------------------------------------------------------------------
-! Name: h5sclose_f
!
-! Purpose: Releases and terminates access to a dataspace.
+!****s* H5S/h5sclose_f
!
-! Inputs:
-! space_id - identifier of dataspace to release
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sclose_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Releases and terminates access to a dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - identifier of dataspace to release
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sclose_f(space_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sclose_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sclose_c(space_id)
USE H5GLOBAL
@@ -138,31 +153,34 @@
END SUBROUTINE h5sclose_f
-!----------------------------------------------------------------------
-! Name: h5screate_f
!
-! Purpose: Creates a new dataspace of a specified type.
+!****s* H5S/h5screate_f
+!
+! NAME
+! h5screate_f
+!
+! PURPOSE
+! Creates a new dataspace of a specified type.
!
-! Inputs:
-! classtype - the type of the dataspace to be created
-! Outputs:
-! space_id - dataspace identifier
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! INPUTS
+! classtype - the type of the dataspace to be created
+! OUTPUTS
+! space_id - dataspace identifier
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! NOTES
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5screate_f(classtype, space_id, hdferr)
IMPLICIT NONE
INTEGER, INTENT(IN) :: classtype ! The type of the dataspace
@@ -173,10 +191,7 @@
! H5S_NULL_F(2)
INTEGER(HID_T), INTENT(OUT) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5screate_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5screate_c(classtype, space_id)
USE H5GLOBAL
@@ -192,41 +207,41 @@
END SUBROUTINE h5screate_f
-!----------------------------------------------------------------------
-! Name: h5scopy_f
!
-! Purpose: Creates an exact copy of a dataspace.
+!****s* H5S/h5scopy_f
+!
+! NAME
+! h5scopy_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! new_space_id - identifier of dataspace's copy
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Creates an exact copy of a dataspace.
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! new_space_id - identifier of dataspace's copy
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! NOTES
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5scopy_f(space_id, new_space_id, hdferr)
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, 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)
USE H5GLOBAL
@@ -242,31 +257,31 @@
END SUBROUTINE h5scopy_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_hyper_nblocks_f
!
-! Purpose: Get number of hyperslab blocks.
+!****s* H5S/h5sget_select_hyper_nblocks_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! num_blocks - number of hyperslab blocks in the current
-! hyperslab selection
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_select_hyper_nblocks_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Get number of hyperslab blocks.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! num_blocks - number of hyperslab blocks in the current
+! hyperslab selection
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_select_hyper_nblocks_f(space_id, num_blocks, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -275,15 +290,12 @@
!in the current dataspace
!selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sget_select_hyper_nblocks_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sget_select_hyper_nblocks_c (space_id, num_blocks)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
-!DEC$ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_HYPER_NBLOCKS_C'::h5sget_select_hyper_nblocks_c
+! 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
@@ -294,33 +306,32 @@
END SUBROUTINE h5sget_select_hyper_nblocks_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_hyper_blocklist_f
!
-! Purpose: Gets the list of hyperslab blocks currently selected.
+!****s* H5S/h5sget_select_hyper_blocklist_f
!
-! Inputs:
-! space_id - dataspace identifier
-! startblock - hyperslab block to start with
-! num_blocks - number of blocks to get
-! Outputs:
-! buf - buffer to hold block list
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_select_hyper_blocklist_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Gets the list of hyperslab blocks currently selected.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! startblock - hyperslab block to start with
+! num_blocks - number of blocks to get
+! OUTPUTS
+! buf - buffer to hold block list
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+! SOURCE
SUBROUTINE h5sget_select_hyper_blocklist_f(space_id, startblock, &
num_blocks, buf, hdferr)
IMPLICIT NONE
@@ -334,11 +345,8 @@
INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
!List of hyperslab blocks selected
INTEGER, INTENT(OUT) :: hdferr ! Error code
+!*****
-
-! INTEGER, EXTERNAL :: h5sget_select_hyper_blocklist_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5sget_select_hyper_blocklist_c(space_id, startblock, &
num_blocks, buf )
@@ -359,33 +367,34 @@
END SUBROUTINE h5sget_select_hyper_blocklist_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_bounds_f
!
-! Purpose: Gets the bounding box containing the current selection.
+!****s* H5S/h5sget_select_bounds_f
!
-! Inputs:
-! space_id - dataspace identifier
+! NAME
+! h5sget_select_bounds_f
!
-! Outputs:
-! start - starting coordinates of bounding box
-! end - ending coordinates of bounding box
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Gets the bounding box containing the current selection.
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! INPUTS
+! space_id - dataspace identifier
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! OUTPUTS
+! start - starting coordinates of bounding box
+! end - ending coordinates of bounding box
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! NONE
!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+! SOURCE
SUBROUTINE h5sget_select_bounds_f(space_id, start, END, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -396,7 +405,7 @@
!i.e., the coordinates of the diagonally
!opposite corner
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTERFACE
INTEGER FUNCTION h5sget_select_bounds_c(space_id, start, END)
USE H5GLOBAL
@@ -413,31 +422,31 @@
END SUBROUTINE h5sget_select_bounds_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_elem_npoints_f
!
-! Purpose: Gets the number of element points in the current selection
+!****s* H5S/h5sget_select_elem_npoints_f
+!
+! NAME
+! h5sget_select_elem_npoints_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! num_points - number of element points in the current
-! dataspace selection
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Gets the number of element points in the current selection
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! num_points - number of element points in the current
+! dataspace selection
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5sget_select_elem_npoints_f(space_id, num_points, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -446,15 +455,12 @@
!in the current dataspace
!selection
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sget_select_elem_npoints_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sget_select_elem_npoints_c (space_id, num_points)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
-!DEC$ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_ELEM_NPOINTS_C'::h5sget_select_elem_npoints_c
+! 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
@@ -465,33 +471,32 @@
END SUBROUTINE h5sget_select_elem_npoints_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_elem_pointlist_f
!
-! Purpose: Gets the list of element points currently selected.
+!****s* H5S/h5sget_select_elem_pointlist_f
!
-! Inputs:
-! space_id - dataspace identifier
-! startpoint - element point to start with
-! num_points - number of elemnt points to get
-! Outputs:
-! buf - buffer with element points selected
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_select_elem_pointlist_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Gets the list of element points currently selected.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! startpoint - element point to start with
+! num_points - number of elemnt points to get
+! OUTPUTS
+! buf - buffer with element points selected
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_select_elem_pointlist_f(space_id, startpoint, &
num_points, buf, hdferr)
IMPLICIT NONE
@@ -503,13 +508,13 @@
INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf
!List of element points selected
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTERFACE
INTEGER FUNCTION h5sget_select_elem_pointlist_c(space_id, startpoint, &
num_points, buf )
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
-!DEC$ATTRIBUTES C,reference,decorate,alias:'H5SGET_SELECT_ELEM_POINTLIST_C'::h5sget_select_elem_pointlist_c
+! 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
@@ -523,52 +528,48 @@
END SUBROUTINE h5sget_select_elem_pointlist_f
-!----------------------------------------------------------------------
-! Name: h5sselect_elements_f
-!
-! Purpose: Selects elements to be included in the selection for
-! a dataspace
-!
-! 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
-! elements coordinates
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
-!
-! Programmer: Elena Pourmal
-! August 12, 1999
-!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
-!
-! Comment:
-!----------------------------------------------------------------------
+!
+!****s* H5S/h5sselect_elements_f
+!
+! NAME
+! h5sselect_elements_f
+!
+! PURPOSE
+! Selects elements to be included in the selection for
+! a dataspace
+!
+! INPUTS
+! space_id - dataspace identifier
+! operator - flag, valid values are:
+! H5S_SELECT_SET_F
+! H5S_SELECT_APPEND_F
+! H5S_SELECT_PREPEND_F
+! rank - number of dataspace dimensions
+! num_elements - number of elements to be selected
+! coord - 2D (rank x num_elements) array with the
+! elements coordinates ( 1-based); in C the
+! array is stored in 2D as (num_element x rank)
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+! SOURCE
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(HID_T), INTENT(IN) :: space_id
+ INTEGER, INTENT(IN) :: OPERATOR
+ INTEGER, INTENT(IN) :: rank
+ INTEGER(SIZE_T), INTENT(IN) :: num_elements
+ INTEGER(HSIZE_T), INTENT(IN) , DIMENSION(rank,num_elements) :: coord
+ INTEGER, INTENT(OUT) :: hdferr
+!*****
INTEGER(HSIZE_T), ALLOCATABLE, DIMENSION(:,:) :: c_coord
INTEGER :: error, i
@@ -596,43 +597,49 @@
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
-!----------------------------------------------------------------------
-! Name: h5sselect_all_f
!
-! Purpose: Selects the entire dataspace.
+!****s* H5S/h5sselect_all_f
!
-! Inputs:
-! space_id - identifier for the dataspace in which
-! selection being made
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sselect_all_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Selects the entire dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - Identifier for the dataspace in which
+! selection being made
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sselect_all_f(space_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sselect_all_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sselect_all_c(space_id)
USE H5GLOBAL
@@ -647,39 +654,36 @@
END SUBROUTINE h5sselect_all_f
-!----------------------------------------------------------------------
-! Name: h5sselect_none_f
!
-! Purpose: Resets the selection region to include no elements.
+!****s* H5S/h5sselect_none_f
!
-! Inputs:
-! space_id - the identifier for the dataspace in which
-! the selection is being reset.
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sselect_none_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Resets the selection region to include no elements.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - the identifier for the dataspace in which
+! the selection is being reset.
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sselect_none_f(space_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sselect_none_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sselect_none_c(space_id)
USE H5GLOBAL
@@ -694,31 +698,32 @@
END SUBROUTINE h5sselect_none_f
-!----------------------------------------------------------------------
-! Name: h5sselect_valid_f
!
-! Purpose: Verifies that the selection is within the extent of
-! the dataspace.
+!****s* H5S/h5sselect_valid_f
+!
+! NAME
+! h5sselect_valid_f
!
-! Inputs:
-! space_id - identifier for the dataspace for which
-! selection is verified
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Verifies that the selection is within the extent of
+! the dataspace.
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! INPUTS
+! space_id - identifier for the dataspace for which
+! selection is verified
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sselect_valid_f(space_id, status, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -726,11 +731,9 @@
! contained within the extent,
! FALSE otherwise.
INTEGER, INTENT(OUT) :: hdferr ! Error code
+!*****
INTEGER :: flag ! "TRUE/FALSE/ERROR" flag from C routine
-! INTEGER, EXTERNAL :: h5sselect_valid_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5sselect_valid_c(space_id, flag)
USE H5GLOBAL
@@ -748,41 +751,38 @@
END SUBROUTINE h5sselect_valid_f
-!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_npoints_f
!
-! Purpose: Determines the number of elements in a dataspace.
+!****s* H5S/h5sget_simple_extent_npoints_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! npoints - number of elements in the dataspace
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_simple_extent_npoints_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Determines the number of elements in a dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! npoints - number of elements in the dataspace
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_simple_extent_npoints_f(space_id, npoints, hdferr)
IMPLICIT NONE
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
-
-! INTEGER, EXTERNAL :: h5sget_simple_extent_npoints_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sget_simple_extent_npoints_c( space_id, npoints)
USE H5GLOBAL
@@ -798,41 +798,36 @@
END SUBROUTINE h5sget_simple_extent_npoints_f
-!----------------------------------------------------------------------
-! Name: h5sget_select_npoints_f
!
-! Purpose: Determines the number of elements in a dataspace selection.
+!****s* H5S/h5sget_select_npoints_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! npoints - number of points in the dataspace selection
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_select_npoints_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Determines the number of elements in a dataspace selection.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! npoints - number of points in the dataspace selection
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+! SOURCE
SUBROUTINE h5sget_select_npoints_f(space_id, npoints, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER(HSSIZE_T), INTENT(OUT) :: npoints ! Number of elements in the
! 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)
USE H5GLOBAL
@@ -848,40 +843,36 @@
END SUBROUTINE h5sget_select_npoints_f
-!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_ndims_f
!
-! Purpose: Determines the dimensionality of a dataspace
+!****s* H5S/h5sget_simple_extent_ndims_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! rank - number of dataspace dimensions
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_simple_extent_ndims_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Determines the dimensionality of a dataspace
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! rank - number of dataspace dimensions
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
IMPLICIT NONE
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)
USE H5GLOBAL
@@ -896,34 +887,32 @@
hdferr = h5sget_simple_extent_ndims_c(space_id, rank)
END SUBROUTINE h5sget_simple_extent_ndims_f
-
-!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_dims_f
!
-! Purpose: Retrieves dataspace dimension size and maximum size.
+!****s* H5S/h5sget_simple_extent_dims_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! dims - array to store size of each dimension
-! maxdims - array to store maximum size of each
-! dimension
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_simple_extent_dims_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Retrieves dataspace dimension size and maximum size.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! dims - array to store size of each dimension
+! maxdims - array to store maximum size of each
+! dimension
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_simple_extent_dims_f(space_id, dims, maxdims, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -935,10 +924,7 @@
INTEGER, INTENT(OUT) :: hdferr ! Error code: -1 on failure,
! number of dimensions on
! on success
-
-! INTEGER, EXTERNAL :: h5sget_simple_extent_dims_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sget_simple_extent_dims_c(space_id, dims, maxdims)
USE H5GLOBAL
@@ -955,35 +941,34 @@
END SUBROUTINE h5sget_simple_extent_dims_f
-!----------------------------------------------------------------------
-! Name: h5sget_simple_extent_type_f
!
-! Purpose: Determine the current class of a dataspace
+!****s* H5S/h5sget_simple_extent_type_f
!
-! Inputs:
-! space_id - dataspace identifier
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sget_simple_extent_type_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Determine the current class of a dataspace
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! 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 - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sget_simple_extent_type_f(space_id, classtype, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -994,10 +979,7 @@
! H5S_SIMPLE_F (1)
! H5S_NULL_F (2)
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sget_simple_extent_type_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sget_simple_extent_type_c(space_id, classtype)
USE H5GLOBAL
@@ -1012,35 +994,33 @@
hdferr = h5sget_simple_extent_type_c(space_id, classtype)
END SUBROUTINE h5sget_simple_extent_type_f
-
-!----------------------------------------------------------------------
-! Name: h5sset_extent_simple_f
!
-! Purpose: Sets or resets the size of an existing dataspace.
+!****s* H5S/h5sset_extent_simple_f
!
-! 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
-! dimensions
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sset_extent_simple_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Sets or resets the size of an existing dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! 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
+! dimensions
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sset_extent_simple_f(space_id, rank, current_size, &
maximum_size, hdferr)
IMPLICIT NONE
@@ -1054,10 +1034,7 @@
! sizes of dimensions
! sizes
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sset_extent_simple_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sset_extent_simple_c(space_id, rank, &
current_size, maximum_size)
@@ -1076,33 +1053,31 @@
maximum_size)
END SUBROUTINE h5sset_extent_simple_f
-
-!----------------------------------------------------------------------
-! Name: h5sis_simple_f
!
-! Purpose: Determines whether a dataspace is a simple dataspace.
+!****s* H5S/h5sis_simple_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! status - flag to indicate if dataspace
-! is simple or not
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sis_simple_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Determines whether a dataspace is a simple dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! status - flag to indicate if dataspace
+! is simple or not
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
-
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sis_simple_f(space_id, status, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1110,11 +1085,9 @@
! is simple or not ( TRUE or
! FALSE)
INTEGER, INTENT(OUT) :: hdferr ! Error code
+!*****
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)
USE H5GLOBAL
@@ -1132,31 +1105,34 @@
END SUBROUTINE h5sis_simple_f
-!----------------------------------------------------------------------
-! Name: h5soffset_simple_f
!
-! Purpose: Sets the offset of a simple dataspace.
+!****s* H5S/h5soffset_simple_f
!
-! Inputs:
-! space_id - dataspace identifier
-! offset - the offset at which to position the
-! selection
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5soffset_simple_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Sets the offset of a simple dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! offset - the offset at which to position the
+! selection
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! NONE
!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5soffset_simple_f(space_id, offset, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1164,10 +1140,7 @@
! The offset at which to position
! 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)
USE H5GLOBAL
@@ -1183,33 +1156,38 @@
END SUBROUTINE h5soffset_simple_f
-!----------------------------------------------------------------------
-! Name: h5sextent_copy_f
!
-! Purpose: Copies the extent of a dataspace.
+!****s* H5S/h5sextent_copy_f
+!
+! NAME
+! h5sextent_copy_f
+!
+! 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
+! which the extent is copied
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! NONE
!
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! NOTES
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5sextent_copy_f(dest_space_id, source_space_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dest_space_id ! Identifier of destination
@@ -1217,10 +1195,7 @@
INTEGER(HID_T), INTENT(IN) :: source_space_id ! Identifier of source
! dataspace
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTEGER, EXTERNAL :: h5sextent_copy_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5sextent_copy_c(dest_space_id, source_space_id)
USE H5GLOBAL
@@ -1236,37 +1211,34 @@
END SUBROUTINE h5sextent_copy_f
-!----------------------------------------------------------------------
-! Name: h5sset_extent_none_f
!
-! Purpose: Removes the extent from a dataspace.
+!****s* H5S/h5sset_extent_none_f
!
-! Inputs:
-! space_id - dataspace identifier
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! NAME
+! h5sset_extent_none_f
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! PURPOSE
+! Removes the extent from a dataspace.
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
+! INPUTS
+! space_id - dataspace identifier
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Comment:
-!----------------------------------------------------------------------
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sset_extent_none_f(space_id, hdferr)
IMPLICIT NONE
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)
USE H5GLOBAL
@@ -1281,38 +1253,40 @@
END SUBROUTINE h5sset_extent_none_f
-!----------------------------------------------------------------------
-! Name: h5sselect_hyperslab_f
-!
-! Purpose: Selects a hyperslab region to add to the current selected
-! region
-!
-! 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
-! hyperslab
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! stride - array with hyperslab strides
-! block - array with hyperslab block sizes
-!
-! Programmer: Elena Pourmal
-! August 12, 1999
-!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). March 6, 2001
-!
-! Comment:
-!----------------------------------------------------------------------
-
+!
+!****s* H5S/h5sselect_hyperslab_f
+!
+! NAME
+! h5sselect_hyperslab_f
+!
+! PURPOSE
+! Selects a hyperslab region to add to the current selected
+! region
+!
+! 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
+! hyperslab
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! stride - array with hyperslab strides
+! block - array with hyperslab block sizes
+!
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). March 6, 2001
+!
+! SOURCE
SUBROUTINE h5sselect_hyperslab_f(space_id, operator, start, count, &
hdferr, stride, block)
IMPLICIT NONE
@@ -1332,14 +1306,12 @@
! in each direction
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_stride
INTEGER :: rank
INTEGER :: error1, error2
-! INTEGER, EXTERNAL :: h5sselect_hyperslab_c
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5sselect_hyperslab_c(space_id, operator, &
start, count, stride, block)
@@ -1408,49 +1380,56 @@
deallocate(def_stride)
END SUBROUTINE h5sselect_hyperslab_f
-!----------------------------------------------------------------------
-! Name: h5scombine_hyperslab_f
-!
-! Purpose: Combine a hyperslab selection with the current
-! selection for a dataspace
-!
-! 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
-! start - array with hyperslab offsets
-! count - number of blocks included in the
-! hyperslab
-! Outputs:
-! hyper_id - identifier for the new hyperslab
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! stride - array with hyperslab strides
-! block - array with hyperslab block sizes
-!
-! Programmer: Elena Pourmal
-! October 7, 2002
-!
-! Modifications:
-!
-! Comment: Commented out until 1.6 ? 10/08/2002
-!----------------------------------------------------------------------
-
-! SUBROUTINE h5scombine_hyperslab_f(space_id, operator, start, count, &
-! hyper_id, hdferr, stride, block)
-! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
-! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
+! !$!
+! !$!****s* H5S/h5scombine_hyperslab_f
+! !$!
+! !$! NAME
+! !$! h5scombine_hyperslab_f
+! !$!
+! !$! PURPOSE
+! !$! Combine a hyperslab selection with the current
+! !$! selection for a dataspace
+! !$!
+! !$! 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
+! !$! start - array with hyperslab offsets
+! !$! count - number of blocks included in the
+! !$! hyperslab
+! !$! OUTPUTS
+! !$! hyper_id - identifier for the new hyperslab
+! !$! hdferr: - error code
+! !$! Success: 0
+! !$! Failure: -1
+! !$! OPTIONAL PARAMETERS
+! !$! stride - array with hyperslab strides
+! !$! block - array with hyperslab block sizes
+! !$!
+! !$! AUTHOR
+! !$! Elena Pourmal
+! !$! October 7, 2002
+! !$!
+! !$! HISTORY
+! !$!
+! !$!
+! !$! NOTES
+! !$! Commented out until 1.6 ? 10/08/2002
+! !$!
+! !$! SOURCE
+! SUBROUTINE h5scombine_hyperslab_f(space_id, operator, start, count, &
+! hyper_id, hdferr, stride, block)
+! IMPLICIT NONE
+! 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
@@ -1461,133 +1440,140 @@
! H5S_SELECT_APPEND_F
! H5S_SELECT_PREPEND_F
!
-! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
+! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: start
! Starting coordinates of the hyperslab
-! INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: count
+! 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
+! 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_stride
-! INTEGER :: rank
-! INTEGER :: error1, error2
-
-! INTERFACE
-! INTEGER FUNCTION h5scombine_hyperslab_c(space_id, operator, &
-! start, count, stride, block, hyper_id)
-! USE H5GLOBAL
-! !DEC$IF DEFINED(HDF5F90_WINDOWS)
-! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SCOMBINE_HYPERSLAB_C'::h5scombine_hyperslab_c
-! !DEC$ENDIF
-! INTEGER(HID_T), INTENT(IN) :: space_id
-! INTEGER, INTENT(IN) :: operator
-! 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(HID_T), INTENT(OUT) :: hyper_id
-! END FUNCTION h5scombine_hyperslab_c
-! END INTERFACE
-
-! if (present(stride).and. present(block)) then
-! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
-! stride, block, hyper_id)
-! return
-! endif
+! INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_block
+! INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: def_stride
+! INTEGER :: rank
+! INTEGER :: error1, error2
+
+! INTERFACE
+! INTEGER FUNCTION h5scombine_hyperslab_c(space_id, operator, &
+! start, count, stride, block, hyper_id)
+! USE H5GLOBAL
+! !DEC$IF DEFINED(HDF5F90_WINDOWS)
+! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SCOMBINE_HYPERSLAB_C'::h5scombine_hyperslab_c
+! !DEC$ENDIF
+! INTEGER(HID_T), INTENT(IN) :: space_id
+! INTEGER, INTENT(IN) :: operator
+! 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(HID_T), INTENT(OUT) :: hyper_id
+! END FUNCTION h5scombine_hyperslab_c
+! END INTERFACE
+
+! if (present(stride).and. present(block)) then
+! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
+! stride, block, hyper_id)
+! return
+! endif
! Case of optional parameters.
!
! Find the rank of the dataspace to allocate memery for
! default stride and block arrays.
!
-! CALL h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
-! if( hdferr .EQ. -1) return
+! CALL h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
+! if( hdferr .EQ. -1) return
!
-! if (present(stride).and. .not.present(block)) then
-! allocate(def_block(rank), stat=error1)
-! if (error1.NE.0) then
-! hdferr = -1
-! return
-! endif
-! def_block = 1
-! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
-! stride, def_block, hyper_id)
-! deallocate(def_block)
-! return
-! endif
-
-! if (.not.present(stride).and. present(block)) then
-! allocate(def_stride(rank), stat=error2)
-! if (error2.NE.0) then
-! hdferr = -1
-! return
-! endif
-! def_stride = 1
-! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
-! def_stride, block, hyper_id)
-! deallocate(def_stride)
-! return
-! endif
-! allocate(def_block(rank), stat=error1)
-! allocate(def_stride(rank), stat=error2)
-! if ((error1.NE.0) .OR. (error2.NE.0)) then
-! hdferr = -1
-! return
-! endif
-! def_block = 1
-! def_stride = 1
-! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
-! def_stride, def_block, hyper_id)
-! deallocate(def_block)
-! deallocate(def_stride)
-
-! END SUBROUTINE h5scombine_hyperslab_f
-
-!----------------------------------------------------------------------
-! Name: h5scombine_select_f
-!
-! Purpose: Combine two hyperslab selections with an operation
-! and return a dataspace with resulting selection.
-!
-! 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:
-! ds_id - idataspace identifier with the new selection
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters: - NONE
-!
-! Programmer: Elena Pourmal
-! October 7, 2002
-!
-! Modifications:
-!
-! Comment: commented out until 1.6 release(?) 10/08/2002
-!----------------------------------------------------------------------
-
-! SUBROUTINE h5scombine_select_f(space1_id, operator, space2_id, &
-! ds_id, hdferr)
-! IMPLICIT NONE
-! 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:
+! if (present(stride).and. .not.present(block)) then
+! allocate(def_block(rank), stat=error1)
+! if (error1.NE.0) then
+! hdferr = -1
+! return
+! endif
+! def_block = 1
+! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
+! stride, def_block, hyper_id)
+! deallocate(def_block)
+! return
+! endif
+
+! if (.not.present(stride).and. present(block)) then
+! allocate(def_stride(rank), stat=error2)
+! if (error2.NE.0) then
+! hdferr = -1
+! return
+! endif
+! def_stride = 1
+! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
+! def_stride, block, hyper_id)
+! deallocate(def_stride)
+! return
+! endif
+! allocate(def_block(rank), stat=error1)
+! allocate(def_stride(rank), stat=error2)
+! if ((error1.NE.0) .OR. (error2.NE.0)) then
+! hdferr = -1
+! return
+! endif
+! def_block = 1
+! def_stride = 1
+! hdferr = h5scombine_hyperslab_c(space_id, operator, start, count, &
+! def_stride, def_block, hyper_id)
+! deallocate(def_block)
+! deallocate(def_stride)
+
+! END SUBROUTINE h5scombine_hyperslab_f
+
+! !$!
+! !$!****s* H5S/
+! !$!
+! !$! NAME
+! !$! h5scombine_select_f
+! !$!
+! !$! PURPOSE
+! !$! Combine two hyperslab selections with an operation
+! !$! and return a dataspace with resulting selection.
+! !$!
+! !$! 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
+! !$! ds_id - idataspace identifier with the new selection
+! !$! hdferr: - error code
+! !$! Success: 0
+! !$! Failure: -1
+! !$! OPTIONAL PARAMETERS - NONE
+! !$!
+! !$! AUTHOR
+! !$! Elena Pourmal
+! !$! October 7, 2002
+! !$!
+! !$! HISTORY
+! !$!
+! !$!
+! !$! NOTES commented out until 1.6 release(?) 10/08/2002
+! !$!
+
+! ! SOURCE
+! !$ SUBROUTINE h5scombine_select_f(space1_id, operator, space2_id, &
+! ds_id, hdferr)
+! IMPLICIT NONE
+! 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
@@ -1598,70 +1584,77 @@
! 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
-! INTEGER FUNCTION h5scombine_select_c(space1_id, operator, &
-! space2_id, ds_id)
-! USE H5GLOBAL
-! !DEC$IF DEFINED(HDF5F90_WINDOWS)
-! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SCOMBINE_SELECT_C'::h5scombine_select_c
-! !DEC$ENDIF
-! INTEGER(HID_T), INTENT(IN) :: space1_id
-! INTEGER(HID_T), INTENT(IN) :: space2_id
-! INTEGER, INTENT(IN) :: operator
-! INTEGER(HID_T), INTENT(OUT) :: ds_id
-! END FUNCTION h5scombine_select_c
-! END INTERFACE
-
-! hdferr = h5scombine_select_c(space1_id, operator, space2_id, &
-! ds_id)
-! return
-
-! END SUBROUTINE h5scombine_select_f
-
-!----------------------------------------------------------------------
-! Name: h5sselect_select_f
-!
-! Purpose: Refine a hyperslab selection with an operation
-! using second hyperslab
-!
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters: - NONE
-!
-! Programmer: Elena Pourmal
-! October 7, 2002
-!
-! Modifications:
-!
-! Comment:Commented out until 1.6 release(?) 10/08/2002 EIP
-!----------------------------------------------------------------------
-
-! SUBROUTINE h5sselect_select_f(space1_id, operator, space2_id, &
-! hdferr)
-! IMPLICIT NONE
-! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to
+! INTEGER(HID_T), INTENT(OUT) :: ds_id ! New dataspace identifier
+! INTEGER, INTENT(OUT) :: hdferr ! Error code
+!
+! INTERFACE
+! INTEGER FUNCTION h5scombine_select_c(space1_id, operator, &
+! space2_id, ds_id)
+! USE H5GLOBAL
+! !DEC$IF DEFINED(HDF5F90_WINDOWS)
+! !DEC$ATTRIBUTES C,reference,decorate,alias:'H5SCOMBINE_SELECT_C'::h5scombine_select_c
+! !DEC$ENDIF
+! INTEGER(HID_T), INTENT(IN) :: space1_id
+! INTEGER(HID_T), INTENT(IN) :: space2_id
+! INTEGER, INTENT(IN) :: operator
+! INTEGER(HID_T), INTENT(OUT) :: ds_id
+! END FUNCTION h5scombine_select_c
+! END INTERFACE
+
+! hdferr = h5scombine_select_c(space1_id, operator, space2_id, &
+! ds_id)
+! return
+
+! END SUBROUTINE h5scombine_select_f
+
+! !$!
+! !$!****s* H5S/
+! !$!
+! !$! NAME
+! !$! h5sselect_select_f
+! !$!
+! !$! PURPOSE
+! !$! Refine a hyperslab selection with an operation
+! !$! using second hyperslab
+! !$!
+! !$! 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
+! !$! Success: 0
+! !$! Failure: -1
+! !$! OPTIONAL PARAMETERS - NONE
+! !$!
+! !$! AUTHOR
+! !$! Elena Pourmal
+! !$! October 7, 2002
+! !$!
+! !$! HISTORY
+! !$!
+! !$!
+! !$! NOTESCommented out until 1.6 release(?) 10/08/2002 EIP
+! !$!
+
+! ! SOURCE
+! SUBROUTINE h5sselect_select_f(space1_id, operator, space2_id, &
+! hdferr)
+! IMPLICIT NONE
+! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to
! modify
-! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
-! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
+! 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
@@ -1672,53 +1665,50 @@
! H5S_SELECT_APPEND_F
! H5S_SELECT_PREPEND_F
!
-! INTEGER, INTENT(OUT) :: hdferr ! Error code
-
-! INTERFACE
-! INTEGER FUNCTION h5sselect_select_c(space1_id, operator, &
-! space2_id)
-! USE H5GLOBAL
-! !DEC$IF DEFINED(HDF5F90_WINDOWS)
-! !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 h5sselect_select_c
-! END INTERFACE
-
-! hdferr = h5sselect_select_c(space1_id, operator, space2_id)
-! return
-
-! END SUBROUTINE h5sselect_select_f
-
-!----------------------------------------------------------------------
-! Name: h5sget_select_type_f
-!
-! Purpose: Retrieve the type of selection
-!
-! Inputs:
-! space_id - dataspace iidentifier with selection
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters: - NONE
-!
-! Programmer: Elena Pourmal
-! October 7, 2002
-!
-! Modifications:
-!
-! Comment:
-!----------------------------------------------------------------------
-
+! INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+! INTERFACE
+! INTEGER FUNCTION h5sselect_select_c(space1_id, operator, &
+! space2_id)
+! USE H5GLOBAL
+! !DEC$IF DEFINED(HDF5F90_WINDOWS)
+! !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 h5sselect_select_c
+! END INTERFACE
+
+! hdferr = h5sselect_select_c(space1_id, operator, space2_id)
+! return
+
+! END SUBROUTINE h5sselect_select_f
+
+!
+!****s* H5S/h5sget_select_type_f
+!
+! NAME
+! h5sget_select_type_f
+!
+! PURPOSE
+! Retrieve the type of selection
+!
+! INPUTS
+! space_id - dataspace iidentifier with selection
+! 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 - Returns 0 if successful and -1 if fails
+! AUTHOR
+! Elena Pourmal
+! October 7, 2002
+!
+! SOURCE
SUBROUTINE h5sget_select_type_f(space_id, type, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(INOUT) :: space_id ! Dataspace identifier to
@@ -1729,7 +1719,7 @@
! H5S_SEL_HYPERSLABS_F
! H5S_SEL_ALL_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTERFACE
INTEGER FUNCTION h5sget_select_type_c(space_id, type)
USE H5GLOBAL
@@ -1746,35 +1736,31 @@
END SUBROUTINE h5sget_select_type_f
-!----------------------------------------------------------------------
-! Name: H5Sdecode_f
-!
-! Purpose: Decode a binary object description of data space and return a new object handle.
!
-! Inputs:
-! buf - Buffer for the data space object to be decoded.
-! obj_id - Object ID
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
+!****s* H5S/H5Sdecode_f
!
-! Optional parameters: - NONE
+! NAME
+! H5Sdecode_f
!
-! Programmer: M.S. Breitenfeld
-! March 26, 2008
+! PURPOSE
+! Decode a binary object description of data space and return a new object handle.
!
-! Modifications:
+! INPUTS
+! buf - Buffer for the data space object to be decoded.
+! obj_id - Object ID
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! M. Scot Breitenfeld
+! March 26, 2008
+! SOURCE
SUBROUTINE h5sdecode_f(buf, obj_id, hdferr)
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: buf ! Buffer for the data space object to be decoded.
INTEGER(HID_T), INTENT(OUT) :: obj_id ! Object ID
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTERFACE
INTEGER FUNCTION h5sdecode_c(buf, obj_id)
USE H5GLOBAL
@@ -1791,38 +1777,34 @@
END SUBROUTINE h5sdecode_f
-!----------------------------------------------------------------------
-! Name: H5Sencode_f
!
-! Purpose: Encode a data space object description into a binary buffer.
+!****s* H5S/H5Sencode_f
!
-! Inputs:
-! obj_id - Identifier of the object to be encoded.
-! buf - Buffer for the object to be encoded into.
-! nalloc - The size of the allocated buffer.
-! Outputs:
-! nalloc - The size of the buffer needed.
-! hdferr: - error code
-! Success: 0
-! Failure: -1
+! NAME
+! H5Sencode_f
!
-! Optional parameters: - NONE
+! PURPOSE
+! Encode a data space object description into a binary buffer.
!
-! Programmer: M.S. Breitenfeld
-! March 26, 2008
+! INPUTS
+! obj_id - Identifier of the object to be encoded.
+! buf - Buffer for the object to be encoded into.
+! nalloc - The size of the allocated buffer.
+! OUTPUTS
+! nalloc - The size of the buffer needed.
+! hdferr - Returns 0 if successful and -1 if fails.
!
-! Modifications:
-!
-! Comment:
-!----------------------------------------------------------------------
-
+! AUTHOR
+! M. Scot Breitenfeld
+! March 26, 2008
+! SOURCE
SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: obj_id ! Identifier of the object to be encoded.
CHARACTER(LEN=*), INTENT(OUT) :: buf ! Buffer for the object to be encoded into.
INTEGER(SIZE_T), INTENT(INOUT) :: nalloc ! The size of the allocated buffer.
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTERFACE
INTEGER FUNCTION h5sencode_c(buf, obj_id, nalloc)
@@ -1841,38 +1823,32 @@
END SUBROUTINE h5sencode_f
-
-!----------------------------------------------------------------------
-! Name: h5sextent_equal_f
+!****s* H5S/h5sextent_equal_f
!
-! Purpose: Determines whether two dataspace extents are equal.
+! NAME
+! h5sextent_equal_f
!
-! Inputs:
-! space1_id - First dataspace identifier.
-! space2_id - Second dataspace identifier.
-! Outputs:
-! Equal - .TRUE. if equal, .FALSE. if unequal.
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Determines whether two dataspace extents are equal.
!
-! Programmer: M.S. Breitenfeld
-! April 2, 2008
+! INPUTS
+! space1_id - First dataspace identifier.
+! space2_id - Second dataspace identifier.
+! OUTPUTS
+! Equal - .TRUE. if equal, .FALSE. if unequal.
+! hdferr - Returns 0 if successful and -1 if fails
+! AUTHOR
+! M. Scot Breitenfeld
+! April 2, 2008
!
-! Modifications:
-!
-! Comment:
-!----------------------------------------------------------------------
-
+! SOURCE
SUBROUTINE h5sextent_equal_f(space1_id, space2_id, equal, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier.
INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier.
LOGICAL, INTENT(OUT) :: Equal ! .TRUE. if equal, .FALSE. if unequal.
INTEGER, INTENT(OUT) :: hdferr ! Error code
-
+!*****
INTEGER(HID_T) :: c_equal
INTERFACE