summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Gff.f90
diff options
context:
space:
mode:
authorQuincey Koziol <koziol@hdfgroup.org>2008-10-21 19:10:01 (GMT)
committerQuincey Koziol <koziol@hdfgroup.org>2008-10-21 19:10:01 (GMT)
commit27ae4bccfd866a9bf334dc191631499d3cea1b19 (patch)
tree828abaa9099bc36b176c8440f0d905ae267d5b02 /fortran/src/H5Gff.f90
parent22378dbd24c08d7153f4f295b5bca057191edc38 (diff)
downloadhdf5-27ae4bccfd866a9bf334dc191631499d3cea1b19.zip
hdf5-27ae4bccfd866a9bf334dc191631499d3cea1b19.tar.gz
hdf5-27ae4bccfd866a9bf334dc191631499d3cea1b19.tar.bz2
[svn-r15922] Description:
Bring revisions 15289:15457 from trunk into metadata journaling branch. Tested on: FreeBSD/32 6.2 (duty) in debug mode FreeBSD/64 6.2 (liberty) w/C++ & FORTRAN, in debug mode Linux/32 2.6 (kagiso) w/PGI compilers, w/C++ & FORTRAN, w/threadsafe, in debug mode Linux/64-amd64 2.6 (smirom) w/default API=1.6.x, w/C++ & FORTRAN, in production mode Linux/64-ia64 2.6 (cobalt) w/Intel compilers, w/C++ & FORTRAN, in production mode Solaris/32 2.10 (linew) w/deprecated symbols disabled, w/C++ & FORTRAN, w/szip filter, in production mode Mac OS X/32 10.5.2 (amazon) in debug mode Linux/64-ia64 2.4 (tg-login3) w/parallel, w/FORTRAN, in production mode
Diffstat (limited to 'fortran/src/H5Gff.f90')
-rw-r--r--fortran/src/H5Gff.f9078
1 files changed, 61 insertions, 17 deletions
diff --git a/fortran/src/H5Gff.f90 b/fortran/src/H5Gff.f90
index 1e4b2b1..13baa94 100644
--- a/fortran/src/H5Gff.f90
+++ b/fortran/src/H5Gff.f90
@@ -1197,16 +1197,19 @@ CONTAINS
! Success: 0
! Failure: -1
! Optional parameters:
-! NONE
+! mounted - Whether group has a file mounted on it
!
! Programmer: M. S. Breitenfeld
! February 15, 2008
!
-! Modifications: N/A
+! Modifications:
+! - Added 'mounted' paramater
+! M.S. Breitenfeld
+! July 16, 2008
!
!----------------------------------------------------------------------
- SUBROUTINE h5gget_info_f(group_id, storage_type, nlinks, max_corder, hdferr)
+ SUBROUTINE h5gget_info_f(group_id, storage_type, nlinks, max_corder, hdferr, mounted)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5gget_info_f
@@ -1222,11 +1225,14 @@ CONTAINS
INTEGER, INTENT(OUT) :: max_corder ! Current maximum creation order value for group
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
+ LOGICAL, INTENT(OUT), OPTIONAL :: mounted ! Whether group has a file mounted on it
+
+ INTEGER :: mounted_c
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5gget_info_c(group_id, storage_type, nlinks, max_corder)
+ INTEGER FUNCTION h5gget_info_c(group_id, storage_type, nlinks, max_corder, mounted_c)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5GGET_INFO_C'::h5gget_info_c
@@ -1235,10 +1241,19 @@ CONTAINS
INTEGER, INTENT(OUT) :: storage_type
INTEGER, INTENT(OUT) :: nlinks
INTEGER, INTENT(OUT) :: max_corder
+ INTEGER :: mounted_c
END FUNCTION h5gget_info_c
END INTERFACE
- hdferr = h5gget_info_c(group_id, storage_type, nlinks, max_corder)
+ hdferr = h5gget_info_c(group_id, storage_type, nlinks, max_corder, mounted_c)
+
+ IF(PRESENT(mounted))THEN
+ IF(mounted_c.EQ.0) THEN
+ mounted = .FALSE.
+ ELSE
+ mounted = .TRUE.
+ ENDIF
+ ENDIF
END SUBROUTINE h5gget_info_f
@@ -1266,17 +1281,21 @@ CONTAINS
! Success: 0
! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
+! mounted - Whether group has a file mounted on it
!
! Programmer: M. S. Breitenfeld
! February 18, 2008
!
-! Modifications: N/A
+! Modifications:
+! - Added 'mounted' paramater
+! M.S. Breitenfeld
+! July 16, 2008
!
!----------------------------------------------------------------------
SUBROUTINE h5gget_info_by_idx_f(loc_id, group_name, index_type, order, n, &
- storage_type, nlinks, max_corder, hdferr, lapl_id)
+ storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5gget_info_by_idx_f
@@ -1297,7 +1316,9 @@ CONTAINS
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
+ LOGICAL, INTENT(OUT), OPTIONAL :: mounted ! Whether group has a file mounted on it
+ INTEGER :: mounted_c
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: group_name_len ! length of group name
@@ -1305,7 +1326,7 @@ CONTAINS
!
INTERFACE
INTEGER FUNCTION h5gget_info_by_idx_c(loc_id, group_name, group_name_len, index_type, order, n, lapl_id_default, &
- storage_type, nlinks, max_corder)
+ storage_type, nlinks, max_corder, mounted_c)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5GGET_INFO_BY_IDX_C'::h5gget_info_by_idx_c
@@ -1321,6 +1342,7 @@ CONTAINS
INTEGER, INTENT(OUT) :: max_corder
INTEGER(SIZE_T) :: group_name_len
+ INTEGER :: mounted_c
END FUNCTION h5gget_info_by_idx_c
END INTERFACE
@@ -1328,11 +1350,19 @@ CONTAINS
group_name_len = LEN(group_name)
lapl_id_default = H5P_DEFAULT_F
- IF(present(lapl_id)) lapl_id_default = lapl_id
+ IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
hdferr = h5gget_info_by_idx_c(loc_id, group_name, group_name_len, &
index_type, order, n, lapl_id_default, &
- storage_type, nlinks, max_corder)
+ storage_type, nlinks, max_corder, mounted_c)
+
+ IF(PRESENT(mounted))THEN
+ IF(mounted_c.EQ.0) THEN
+ mounted = .FALSE.
+ ELSE
+ mounted = .TRUE.
+ ENDIF
+ ENDIF
END SUBROUTINE h5gget_info_by_idx_f
@@ -1357,17 +1387,20 @@ CONTAINS
! Success: 0
! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
+! mounted - Whether group has a file mounted on it
!
! Programmer: M. S. Breitenfeld
! February 18, 2008
!
-! Modifications: N/A
-!
+! Modifications:
+! - Added 'mounted' paramater
+! M.S. Breitenfeld
+! July 16, 2008
!----------------------------------------------------------------------
SUBROUTINE h5gget_info_by_name_f(loc_id, group_name, &
- storage_type, nlinks, max_corder, hdferr, lapl_id)
+ storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5gget_info_by_name_f
@@ -1385,7 +1418,9 @@ CONTAINS
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
+ LOGICAL, INTENT(OUT), OPTIONAL :: mounted ! Whether group has a file mounted on it
+ INTEGER :: mounted_c
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: group_name_len ! length of group name
@@ -1393,7 +1428,7 @@ CONTAINS
!
INTERFACE
INTEGER FUNCTION h5gget_info_by_name_c(loc_id, group_name, group_name_len, lapl_id_default, &
- storage_type, nlinks, max_corder)
+ storage_type, nlinks, max_corder, mounted_c)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5GGET_INFO_BY_NAME_C'::h5gget_info_by_name_c
@@ -1406,6 +1441,7 @@ CONTAINS
INTEGER, INTENT(OUT) :: max_corder
INTEGER(SIZE_T) :: group_name_len
+ INTEGER :: mounted_c
END FUNCTION h5gget_info_by_name_c
END INTERFACE
@@ -1416,7 +1452,15 @@ CONTAINS
IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
hdferr = h5gget_info_by_name_c(loc_id, group_name, group_name_len, lapl_id_default, &
- storage_type, nlinks, max_corder)
+ storage_type, nlinks, max_corder, mounted_c)
+
+ IF(PRESENT(mounted))THEN
+ IF(mounted_c.EQ.0) THEN
+ mounted = .FALSE.
+ ELSE
+ mounted = .TRUE.
+ ENDIF
+ ENDIF
END SUBROUTINE h5gget_info_by_name_f