summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Gff.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2002-09-25 22:24:55 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2002-09-25 22:24:55 (GMT)
commit11b0fad3fa6249922b37c8a35117fb3340df2020 (patch)
tree61c9d8759bc32b9280b3e0bd1d44709fbbec6ef4 /fortran/src/H5Gff.f90
parent12e30dc9b284cae8dd821ffec93c344b7fb0d96b (diff)
downloadhdf5-11b0fad3fa6249922b37c8a35117fb3340df2020.zip
hdf5-11b0fad3fa6249922b37c8a35117fb3340df2020.tar.gz
hdf5-11b0fad3fa6249922b37c8a35117fb3340df2020.tar.bz2
[svn-r5948]
Purpose: Added new fortran functions Description: Source code, tests and documentation for h5glink2_f and h5gmove2_f functions were added. I also added missing man page for h5glink_f Platforms tested: Solaris 2.7, IRIX64-6.5 and Liniux 2.2
Diffstat (limited to 'fortran/src/H5Gff.f90')
-rw-r--r--fortran/src/H5Gff.f90151
1 files changed, 151 insertions, 0 deletions
diff --git a/fortran/src/H5Gff.f90 b/fortran/src/H5Gff.f90
index 96bc374..87024e7 100644
--- a/fortran/src/H5Gff.f90
+++ b/fortran/src/H5Gff.f90
@@ -426,6 +426,88 @@
END SUBROUTINE h5glink_f
!----------------------------------------------------------------------
+! Name: h5glink2_f
+!
+! Purpose: Creates a link of the specified type from new_name
+! to current_name. current_name and new_name are interpreted
+! releative to current and new location identifiers.
+!
+! Inputs:
+! cur_loc_id - location identifier
+! cur_name - name of the existing object if link is a
+! hard link. Can be anything for the soft link.
+! link_type - link type
+! Possible values are:
+! H5G_LINK_HARD_F (0) or
+! H5G_LINK_SOFT_F (1)
+! new_loc_id - new location identifier
+! new_name - new name for the object
+! Outputs:
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+! Optional parameters:
+! NONE
+!
+! Programmer: Elena Pourmal
+! September 25, 2002
+!
+! Comment:
+!----------------------------------------------------------------------
+
+ SUBROUTINE h5glink2_f(cur_loc_id, cur_name, link_type, new_loc_id, &
+ new_name, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5glink_f
+!DEC$endif
+!
+
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN) :: cur_loc_id ! File or group identifier
+ CHARACTER(LEN=*), INTENT(IN) :: cur_name
+ ! Current name of an object
+ INTEGER, INTENT(IN) :: link_type ! link type
+ ! Possible values are:
+ ! H5G_LINK_HARD_F (0) or
+ ! H5G_LINK_SOFT_F (1)
+
+ INTEGER(HID_T), INTENT(IN) :: new_loc_id ! File or group identifier
+ CHARACTER(LEN=*), INTENT(IN) :: new_name ! New name of an object
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTEGER :: cur_namelen ! Lenghth of the current_name string
+ INTEGER :: new_namelen ! Lenghth of the new_name string
+
+ INTERFACE
+ INTEGER FUNCTION h5glink2_c(cur_loc_id, cur_name, cur_namelen, &
+ link_type, new_loc_id, &
+ new_name, new_namelen)
+
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !MS$ATTRIBUTES C,reference,alias:'_H5GLINK2_C'::h5glink2_c
+ !DEC$ ENDIF
+ !DEC$ATTRIBUTES reference :: cur_name
+ !DEC$ATTRIBUTES reference :: new_name
+ INTEGER(HID_T), INTENT(IN) :: cur_loc_id
+ INTEGER(HID_T), INTENT(IN) :: new_loc_id
+ INTEGER, INTENT(IN) :: link_type
+ CHARACTER(LEN=*), INTENT(IN) :: cur_name
+ CHARACTER(LEN=*), INTENT(IN) :: new_name
+ INTEGER :: cur_namelen
+ INTEGER :: new_namelen
+ END FUNCTION h5glink2_c
+ END INTERFACE
+
+ cur_namelen = LEN(cur_name)
+ new_namelen = LEN(new_name)
+ hdferr = h5glink2_c(cur_loc_id, cur_name, cur_namelen, link_type, &
+ new_loc_id, new_name, new_namelen)
+ END SUBROUTINE h5glink2_f
+
+!----------------------------------------------------------------------
! Name: h5gunlink_f
!
! Purpose: Removes the specified name from the group graph and
@@ -556,6 +638,75 @@
END SUBROUTINE h5gmove_f
!----------------------------------------------------------------------
+! Name: h5gmove2_f
+!
+! Purpose: Renames an object within an HDF5 file.
+!
+! Inputs:
+! src_loc_id - original location identifier
+! src_name - object's name at specified original location
+! dst_loc_id - original location identifier
+! dst_name - object's new name
+! Outputs:
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+! Optional parameters:
+! NONE
+!
+! Programmer: Elena Pourmal
+! September 25, 2002
+!
+! Comment:
+!----------------------------------------------------------------------
+
+
+ SUBROUTINE h5gmove2_f(src_loc_id, src_name, dst_loc_id, dst_name, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gmove2_f
+!DEC$endif
+!
+
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN) :: src_loc_id ! File or group identifier
+ CHARACTER(LEN=*), INTENT(IN) :: src_name ! Original name of an object
+ INTEGER(HID_T), INTENT(IN) :: dst_loc_id ! File or group identifier
+ CHARACTER(LEN=*), INTENT(IN) :: dst_name ! New name of an object
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTEGER :: src_namelen ! Length of the current_name string
+ INTEGER :: dst_namelen ! Lenghth of the new_name string
+
+! INTEGER, EXTERNAL :: h5gmove2_c
+! MS FORTRAN needs explicit interface for C functions called here.
+!
+ INTERFACE
+ INTEGER FUNCTION h5gmove2_c(src_loc_id, src_name, src_namelen, &
+ dst_loc_id, dst_name, dst_namelen)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !MS$ATTRIBUTES C,reference,alias:'_H5GMOVE2_C'::h5gmove2_c
+ !DEC$ ENDIF
+ !DEC$ATTRIBUTES reference :: src_name
+ !DEC$ATTRIBUTES reference :: dst_name
+ INTEGER(HID_T), INTENT(IN) :: src_loc_id
+ INTEGER(HID_T), INTENT(IN) :: dst_loc_id
+ CHARACTER(LEN=*), INTENT(IN) :: src_name
+ CHARACTER(LEN=*), INTENT(IN) :: dst_name
+ INTEGER :: src_namelen
+ INTEGER :: dst_namelen
+ END FUNCTION h5gmove2_c
+ END INTERFACE
+
+ src_namelen = LEN(src_name)
+ dst_namelen = LEN(dst_name)
+ hdferr = h5gmove2_c(src_loc_id, src_name, src_namelen,&
+ dst_loc_id, dst_name, dst_namelen)
+ END SUBROUTINE h5gmove2_f
+
+!----------------------------------------------------------------------
! Name: h5gget_linkval_f
!
! Purpose: Returns the name of the object that the symbolic link