diff options
author | Elena Pourmal <epourmal@hdfgroup.org> | 2001-03-05 20:25:50 (GMT) |
---|---|---|
committer | Elena Pourmal <epourmal@hdfgroup.org> | 2001-03-05 20:25:50 (GMT) |
commit | 2453130d96acf1e63c79208792126d235accc9d7 (patch) | |
tree | a21bea0d63168aef26db167842740b9e74ed8615 /fortran/src/H5Rff.f90 | |
parent | c501c12cdabc0504ece42365fe6928c7e18a3405 (diff) | |
download | hdf5-2453130d96acf1e63c79208792126d235accc9d7.zip hdf5-2453130d96acf1e63c79208792126d235accc9d7.tar.gz hdf5-2453130d96acf1e63c79208792126d235accc9d7.tar.bz2 |
[svn-r3546]
Purpose:
Windows port and maintenance
Description:
Windows Fortran requires interface blocks for each C function
called from F90 stub.
I also added comment blocks for each F90 API.
Solution:
Added interface blocks.
Platforms tested:
Linux (eirene)
Diffstat (limited to 'fortran/src/H5Rff.f90')
-rw-r--r-- | fortran/src/H5Rff.f90 | 278 |
1 files changed, 270 insertions, 8 deletions
diff --git a/fortran/src/H5Rff.f90 b/fortran/src/H5Rff.f90 index 860fba3..05e4139 100644 --- a/fortran/src/H5Rff.f90 +++ b/fortran/src/H5Rff.f90 @@ -46,6 +46,32 @@ CONTAINS +!---------------------------------------------------------------------- +! Name: h5rcreate_object_f +! +! Purpose: Creates reference to the object +! +! Inputs: +! loc_id - location identifier +! name - name of the object at the specified location +! Outputs: +! ref - reference to the specified object +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rcreate_f +! subroutine. +!---------------------------------------------------------------------- SUBROUTINE h5rcreate_object_f(loc_id, name, ref, hdferr) IMPLICIT NONE @@ -57,15 +83,58 @@ INTEGER :: namelen ! Name length INTEGER :: ref_f(REF_OBJ_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rcreate_object_c + +! INTEGER, EXTERNAL :: h5fcreate_object_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rcreate_object_c(ref_f, loc_id, name, namelen) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RCREATE_OBJECT_C':: h5rcreate_object_c + !DEC$ATTRIBUTES reference :: name + INTEGER, PARAMETER :: REF_OBJ_BUF_LEN = 2 + INTEGER :: ref_f(REF_OBJ_BUF_LEN) + INTEGER(HID_T), INTENT(IN) :: loc_id + CHARACTER(LEN=*), INTENT(IN) :: name + INTEGER :: namelen + END FUNCTION h5rcreate_object_c + END INTERFACE + namelen = LEN(name) ref_f = 0 hdferr = h5rcreate_object_c(ref_f, loc_id, name, namelen ) ref%ref = ref_f END SUBROUTINE h5rcreate_object_f - +!---------------------------------------------------------------------- +! Name: h5rcreate_region_f +! +! Purpose: Creates r eference to the dataset region +! +! Inputs: +! loc_id - location identifier +! name - name of the dataset at the specified location +! space_id - dataspace identifier that describes selected region +! Outputs: +! ref - reference to the dataset region +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rcreate_f +! subroutine. +!---------------------------------------------------------------------- + SUBROUTINE h5rcreate_region_f(loc_id, name, space_id, ref, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier @@ -77,7 +146,24 @@ INTEGER :: namelen ! Name length INTEGER :: ref_f(REF_REG_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rcreate_region_c + +! INTEGER, EXTERNAL :: h5fcreate_region_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rcreate_region_c(ref_f, loc_id, name, namelen, space_id) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RCREATE_REGION_C':: h5rcreate_region_c + !DEC$ATTRIBUTES reference :: name + INTEGER, PARAMETER :: REF_REG_BUF_LEN = 3 + INTEGER :: ref_f(REF_REG_BUF_LEN) + INTEGER(HID_T), INTENT(IN) :: loc_id + CHARACTER(LEN=*), INTENT(IN) :: name + INTEGER :: namelen + INTEGER(HID_T), INTENT(IN) :: space_id + END FUNCTION h5rcreate_region_c + END INTERFACE + namelen = LEN(name) ref_f = 0 hdferr = h5rcreate_region_c(ref_f, loc_id, name, namelen, space_id ) @@ -85,6 +171,35 @@ END SUBROUTINE h5rcreate_region_f +!---------------------------------------------------------------------- +! Name: h5rdereference_object_f +! +! Purpose: Opens the HDF5 object referenced +! +! Inputs: +! dset_id - identifier of the dataset containing +! reference +! ref - reference to open +! Outputs: +! obj_id - object_identifier +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rdereference_f +! subroutine. +!---------------------------------------------------------------------- + + SUBROUTINE h5rdereference_object_f(dset_id, ref, obj_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier @@ -94,28 +209,114 @@ INTEGER :: ref_type ! Reference type INTEGER :: ref_f(REF_OBJ_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rdereference_object_c + +! INTEGER, EXTERNAL :: h5h5rdereference_object_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rdereference_object_c(dset_id, ref_f, obj_id) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RDEREFERENCE_OBJECT_C':: h5rdereference_object_c + INTEGER, PARAMETER :: REF_OBJ_BUF_LEN = 2 + INTEGER(HID_T), INTENT(IN) :: dset_id + INTEGER :: ref_f(REF_OBJ_BUF_LEN) + INTEGER(HID_T), INTENT(OUT) :: obj_id + END FUNCTION h5rdereference_object_c + END INTERFACE + ref_f = ref%ref hdferr = h5rdereference_object_c(dset_id, ref_f, obj_id ) END SUBROUTINE h5rdereference_object_f +!---------------------------------------------------------------------- +! Name: h5rdereference_region_f +! +! Purpose: Opens the dataset region +! +! Inputs: +! dset_id - identifier of the dataset containing +! reference to teh regions +! ref - reference to open +! Outputs: +! obj_id - dataspace identifier +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rdereference_f +! subroutine. +!---------------------------------------------------------------------- + + SUBROUTINE h5rdereference_region_f(dset_id, ref, obj_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref ! Object reference - INTEGER(HID_T), INTENT(OUT) :: obj_id ! Object identifier + INTEGER(HID_T), INTENT(OUT) :: obj_id ! Dataspace identifier INTEGER, INTENT(OUT) :: hdferr ! Error code INTEGER :: ref_type ! Reference type INTEGER :: ref_f(REF_REG_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rdereference_region_c + +! INTEGER, EXTERNAL :: h5rdereference_region_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rdereference_region_c(dset_id, ref_f, obj_id) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RDEREFERENCE_REGION_C':: h5rdereference_region_c + INTEGER(HID_T), INTENT(IN) :: dset_id + INTEGER, PARAMETER :: REF_REG_BUF_LEN = 3 + INTEGER :: ref_f(REF_REG_BUF_LEN) + INTEGER(HID_T), INTENT(OUT) :: obj_id + END FUNCTION h5rdereference_region_c + END INTERFACE + ref_type = H5R_DATASET_REGION_F ref_f = ref%ref hdferr = h5rdereference_region_c(dset_id, ref_f, obj_id ) END SUBROUTINE h5rdereference_region_f +!---------------------------------------------------------------------- +! Name: h5rget_region_region_f +! +! Purpose: Retrieves a dataspace with the specified region selected +! +! Inputs: +! dset_id - identifier of the dataset containing +! reference to the regions +! ref - reference to open +! Outputs: +! space_id - dataspace identifier +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rget_region_f +! subroutine. +!---------------------------------------------------------------------- + + SUBROUTINE h5rget_region_region_f(dset_id, ref, space_id, hdferr) IMPLICIT NONE @@ -125,11 +326,59 @@ INTEGER, INTENT(OUT) :: hdferr ! Error code INTEGER :: ref_f(REF_REG_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rget_region_region_c +! INTEGER, EXTERNAL :: h5rget_region_region_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rget_region_region_c(dset_id, ref_f, space_id) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RGET_REGION_REGION_C':: h5rget_region_region_c + INTEGER(HID_T), INTENT(IN) :: dset_id + INTEGER, PARAMETER :: REF_REG_BUF_LEN = 3 + INTEGER :: ref_f(REF_REG_BUF_LEN) + INTEGER(HID_T), INTENT(OUT) :: space_id + END FUNCTION h5rget_region_region_c + END INTERFACE + ref_f = ref%ref hdferr = h5rget_region_region_c(dset_id, ref_f, space_id ) END SUBROUTINE h5rget_region_region_f + +!---------------------------------------------------------------------- +! Name: h5rget_object_type_obj_f +! +! Purpose: Retrieves the type of object that an object reference points to. +! +! Inputs: +! dset_id - identifier of the dataset containing +! reference to the objects +! ref - reference to open +! Outputs: +! obj_type - object_type, possible values: +! H5G_UNKNOWN_F (-1) +! H5G_LINK_F 0 +! H5G_GROUP_F 1 +! H5G_DATASET_F 2 +! H5G_TYPE_F 3 +! +! 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). February 28, 2001 +! +! Comment: This is a module procedure for the h5rget_object_type_f +! subroutine. +!---------------------------------------------------------------------- + SUBROUTINE h5rget_object_type_obj_f(dset_id, ref, obj_type, hdferr) IMPLICIT NONE @@ -145,7 +394,20 @@ INTEGER, INTENT(OUT) :: hdferr ! Error code INTEGER :: ref_f(REF_OBJ_BUF_LEN) ! Local buffer to pass reference - INTEGER, EXTERNAL :: h5rget_object_type_obj_c +! INTEGER, EXTERNAL :: h5rget_object_type_obj_c +! Interface is needed for MS FORTRAN +! + INTERFACE + INTEGER FUNCTION h5rget_object_type_obj_c(dset_id, ref_f, obj_type) + USE H5GLOBAL + !MS$ATTRIBUTES C,reference,alias:'_H5RGET_OBJECT_TYPE_OBJ_C':: h5rget_object_type_obj_c + INTEGER, PARAMETER :: REF_OBJ_BUF_LEN = 2 + INTEGER(HID_T), INTENT(IN) :: dset_id + INTEGER :: ref_f(REF_OBJ_BUF_LEN) + INTEGER, INTENT(OUT) :: obj_type + END FUNCTION h5rget_object_type_obj_c + END INTERFACE + ref_f = ref%ref hdferr = h5rget_object_type_obj_c(dset_id, ref_f, obj_type ) |