diff options
author | Elena Pourmal <epourmal@hdfgroup.org> | 2003-03-05 20:18:31 (GMT) |
---|---|---|
committer | Elena Pourmal <epourmal@hdfgroup.org> | 2003-03-05 20:18:31 (GMT) |
commit | ff5c7fe0d55373fb636364d8e02239ad1ac2dd17 (patch) | |
tree | 74c9fd25a6dfbe5f9e2dd357e10b6c5679e0faca /fortran/src/H5Sff.f90 | |
parent | 1e7558dbd00e68b02a295c049a5b4b8bc175fe10 (diff) | |
download | hdf5-ff5c7fe0d55373fb636364d8e02239ad1ac2dd17.zip hdf5-ff5c7fe0d55373fb636364d8e02239ad1ac2dd17.tar.gz hdf5-ff5c7fe0d55373fb636364d8e02239ad1ac2dd17.tar.bz2 |
[svn-r6464]
Purpose:
Maintenance
Description:
* Added support for generic properties.
* Added support for time allocation properties.
* Added support for variable length datatypes (only datatypes based
on INTEGER, REAL and CHARACTER Fortran types are supported).
* added some missing functions
Solution:
I am checking in new Fortran APIs and their man pages to support
1.5 features listed above.
Not all APIs have tests yet. APIs were written in Fall 2002, and I am afraid
that I will loose the code or totally forget what I did if I wait longer. ;-)
Platforms tested:
arabica (fortran), eirene (fortran), modi4 (parallel, fortran)
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r-- | fortran/src/H5Sff.f90 | 371 |
1 files changed, 366 insertions, 5 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90 index d5d1c48..a458945 100644 --- a/fortran/src/H5Sff.f90 +++ b/fortran/src/H5Sff.f90 @@ -350,7 +350,7 @@ IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier - INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: startblock + INTEGER(HSIZE_T), INTENT(IN) :: startblock !Hyperslab block to start with. INTEGER(HSIZE_T), INTENT(IN) :: num_blocks !number of hyperslab blocks @@ -372,8 +372,8 @@ !MS$ATTRIBUTES C,reference,alias:'_H5SGET_SELECT_HYPER_BLOCKLIST_C'::h5sget_select_hyper_blocklist_c !DEC$ ENDIF INTEGER(HID_T), INTENT(IN) :: space_id - INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: startblock - INTEGER(HSSIZE_T), INTENT(IN) :: num_blocks + 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 @@ -544,7 +544,7 @@ ! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier - INTEGER(HSIZE_T),DIMENSION(*), INTENT(IN) :: startpoint + INTEGER(HSIZE_T), INTENT(IN) :: startpoint !Element point to start with. INTEGER(HSIZE_T), INTENT(IN) :: num_points !Number of element points to get @@ -563,7 +563,7 @@ !MS$ATTRIBUTES C,reference,alias:'_H5SGET_SELECT_ELEM_POINTLIST_C'::h5sget_select_elem_pointlist_c !DEC$ ENDIF INTEGER(HID_T), INTENT(IN) :: space_id - INTEGER(HSIZE_T),DIMENSION(*), INTENT(IN) :: startpoint + 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 @@ -1562,5 +1562,366 @@ 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) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5scombine_hyperslab_f +!DEC$endif +! +! 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 + ! 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(HSSIZE_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 +! 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 + ! 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) + !MS$ATTRIBUTES C,reference,alias:'_H5SCOMBINE_HYPERSLAB_C'::h5scombine_hyperslab_c + !DEC$ ENDIF +! INTEGER(HID_T), INTENT(IN) :: space_id +! INTEGER, INTENT(IN) :: operator +! INTEGER(HSSIZE_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 + ! +! 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) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5scombine_select_f +!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, 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 +! 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) + !MS$ATTRIBUTES C,reference,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) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5sselect_select_f +!DEC$endif +! +! 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: + ! 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 +! INTEGER FUNCTION h5sselect_select_c(space1_id, operator, & +! space2_id) +! USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !MS$ATTRIBUTES C,reference,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: +!---------------------------------------------------------------------- + + SUBROUTINE h5sget_select_type_f(space_id, type, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5sget_select_type_f +!DEC$endif +! + 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 + INTEGER, INTENT(OUT) :: hdferr ! Error code + + INTERFACE + INTEGER FUNCTION h5sget_select_type_c(space_id, type) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !MS$ATTRIBUTES C,reference,alias:'_H5SGET_SELECT_TYPEC'::h5sget_select_type_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: space_id + INTEGER, INTENT(OUT) :: type + END FUNCTION h5sget_select_type_c + END INTERFACE + + hdferr = h5sget_select_type_c(space_id, type) + return + + END SUBROUTINE h5sget_select_type_f END MODULE H5S |