summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Iff.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2001-03-05 20:25:50 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2001-03-05 20:25:50 (GMT)
commit2453130d96acf1e63c79208792126d235accc9d7 (patch)
treea21bea0d63168aef26db167842740b9e74ed8615 /fortran/src/H5Iff.f90
parentc501c12cdabc0504ece42365fe6928c7e18a3405 (diff)
downloadhdf5-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/H5Iff.f90')
-rw-r--r--fortran/src/H5Iff.f9046
1 files changed, 43 insertions, 3 deletions
diff --git a/fortran/src/H5Iff.f90 b/fortran/src/H5Iff.f90
index cd50da3..7f73242 100644
--- a/fortran/src/H5Iff.f90
+++ b/fortran/src/H5Iff.f90
@@ -3,11 +3,40 @@
!
MODULE H5I
- USE H5FORTRAN_TYPES
- USE H5FORTRAN_FLAGS
+ USE H5GLOBAL
CONTAINS
+!----------------------------------------------------------------------
+! Name: h5iget_type_f
+!
+! Purpose: Retrieves the type of an object.
+!
+! Inputs: obj_id - object identifier
+! Outputs:
+! type - type of the object, possible values:
+! H5I_FILE_F(1)
+! H5I_GROUP_F(2)
+! H5I_DATATYPE_F(3)
+! H5I_DATASPACE_F(4)
+! H5I_DATASET_F(5)
+! H5I_ATTR_F(6)
+! H5I_BADID_F(-1)
+! 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 5, 2001
+!
+! Comment:
+!----------------------------------------------------------------------
SUBROUTINE h5iget_type_f(obj_id, type, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: obj_id !Object identifier
@@ -21,7 +50,18 @@
!H5I_ATTR_F(6)
!H5I_BADID_F(-1)
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER, EXTERNAL :: h5iget_type_c
+
+! INTEGER, EXTERNAL :: h5iget_type_c
+! Interface is needed for MS FORTRAN
+!
+ INTERFACE
+ INTEGER FUNCTION h5iget_type_c(obj_id, type)
+ USE H5GLOBAL
+ !MS$ATTRIBUTES C,reference,alias:'_H5IGET_TYPE_C':: h5iget_type_c
+ INTEGER(HID_T), INTENT(IN) :: obj_id
+ INTEGER, INTENT(OUT) :: type
+ END FUNCTION h5iget_type_c
+ END INTERFACE
hdferr = h5iget_type_c(obj_id, type)
END SUBROUTINE h5iget_type_f