summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Fff.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2002-10-01 18:55:47 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2002-10-01 18:55:47 (GMT)
commit01a577a4e90c6fcd66888e69705292cd57232da8 (patch)
treeb5e5eeb79887d20a98b397f3a13d05dfa5573202 /fortran/src/H5Fff.f90
parent09325c1da67ed0b747b70951f1e373ddd42f9478 (diff)
downloadhdf5-01a577a4e90c6fcd66888e69705292cd57232da8.zip
hdf5-01a577a4e90c6fcd66888e69705292cd57232da8.tar.gz
hdf5-01a577a4e90c6fcd66888e69705292cd57232da8.tar.bz2
[svn-r5956]
Purpose: Added new F90 APIs Description: I added new F90 APIs, tests, and documentation for the following functions: h5fget_obj_count_f h5pequal_f h5tget_member_index_f h5fget_obj_ids_f h5pget_fclose_degree_f h5pset_fclose_degree_f Documentation for exisiting functions was missing: h5freopen_f, h5fflush_f, h5fmount_f, h5unmount_f, h5fget_create_plist_f, h5fget_access_plist_f. Platforms tested: Solaris 2.7, Linux 2.2 and IRIX64-6.5
Diffstat (limited to 'fortran/src/H5Fff.f90')
-rw-r--r--fortran/src/H5Fff.f90119
1 files changed, 118 insertions, 1 deletions
diff --git a/fortran/src/H5Fff.f90 b/fortran/src/H5Fff.f90
index 6e0cb3a..7b995a5 100644
--- a/fortran/src/H5Fff.f90
+++ b/fortran/src/H5Fff.f90
@@ -102,7 +102,6 @@
! H5F_SCOPE_GLOBAL_F
! H5F_SCOPE_LOCAL_F
! Outputs:
-! file_id - file identifier
! hdferr: - error code
! Success: 0
! Failure: -1
@@ -669,4 +668,122 @@
END SUBROUTINE h5fclose_f
+!----------------------------------------------------------------------
+! Name: h5fget_obj_count_f
+!
+! Purpose: Gets number of the objects open within a file
+!
+! Inputs:
+! file_id - file identifier
+! obj_type - type of the object; possible values are:
+! H5F_OBJ_FILE_F
+! H5F_OBJ_DATASET_F
+! H5F_OBJ_GROUP_F
+! H5F_OBJ_DATATYPE_F
+! H5F_OBJ_ALL_F
+! Outputs:
+! obj_count - number of open objects
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+! Optional parameters:
+! NONE
+!
+! Programmer: Elena Pourmal
+! September 30, 2002
+!
+! Modifications:
+!
+! Comment:
+!----------------------------------------------------------------------
+
+ SUBROUTINE h5fget_obj_count_f(file_id, obj_type, obj_count, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5fget_obj_count_f
+!DEC$endif
+!
+
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
+ INTEGER, INTENT(IN) :: obj_type ! Object type
+ INTEGER, INTENT(OUT) :: obj_count ! Number of open objects
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTERFACE
+ INTEGER FUNCTION h5fget_obj_count_c(file_id, obj_type, obj_count)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !MS$ATTRIBUTES C,reference,alias:'_H5FGET_OBJ_COUNT_C':: h5fget_obj_count_c
+ !DEC$ ENDIF
+ INTEGER(HID_T), INTENT(IN) :: file_id
+ INTEGER, INTENT(IN) :: obj_type ! Object type
+ INTEGER, INTENT(OUT) :: obj_count ! Number of open objects
+ END FUNCTION h5fget_obj_count_c
+ END INTERFACE
+
+ hdferr = h5fget_obj_count_c(file_id, obj_type, obj_count)
+
+ END SUBROUTINE h5fget_obj_count_f
+
+!----------------------------------------------------------------------
+! Name: h5fget_obj_ids_f
+!
+! Purpose: Get list of open objects identifiers within a file
+!
+! Inputs:
+! file_id - file identifier
+! obj_type - type of the object; possible values are:
+! H5F_OBJ_FILE_F
+! H5F_OBJ_DATASET_F
+! H5F_OBJ_GROUP_F
+! H5F_OBJ_DATATYPE_F
+! H5F_OBJ_ALL_F
+! Outputs:
+! obj_ids - array of open object identifiers
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+! Optional parameters:
+! NONE
+!
+! Programmer: Elena Pourmal
+! September 30, 2002
+!
+! Modifications:
+!
+! Comment:
+!----------------------------------------------------------------------
+
+ SUBROUTINE h5fget_obj_ids_f(file_id, obj_type, obj_ids, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5fget_obj_ids_f
+!DEC$endif
+!
+
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
+ INTEGER, INTENT(IN) :: obj_type ! Object type
+ INTEGER(HID_T), DIMENSION(*), INTENT(INOUT) :: obj_ids
+ ! Array of open objects iidentifiers
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTERFACE
+ INTEGER FUNCTION h5fget_obj_ids_c(file_id, obj_type, obj_ids)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !MS$ATTRIBUTES C,reference,alias:'_H5FGET_OBJ_IDS_C':: h5fget_obj_ids_c
+ !DEC$ ENDIF
+ INTEGER(HID_T), INTENT(IN) :: file_id
+ INTEGER, INTENT(IN) :: obj_type
+ INTEGER(HID_T), DIMENSION(*), INTENT(INOUT) :: obj_ids
+ END FUNCTION h5fget_obj_ids_c
+ END INTERFACE
+
+ hdferr = h5fget_obj_ids_c(file_id, obj_type, obj_ids)
+
+ END SUBROUTINE h5fget_obj_ids_f
END MODULE H5F