From ea346d804278515f168ec5df8037b8724f9b0fe8 Mon Sep 17 00:00:00 2001 From: Elena Pourmal Date: Wed, 4 Jun 2003 17:53:23 -0500 Subject: [svn-r6965] Purpose: Maintenace fro 1.6 release Description: Man pages for the following functions have been added h5pset(get)_fapl_core_f h5pset(get)_fapl_family_f h5pset(get)_fapl_multi_f h5pset_fapl_sec2_f h5pset_fapl_sdio_f h5pset_fapl_split_f h5pget_driver_f h5pset_szip_f h5pget_nfilters_f h5pset(get)_preserve_f Solution: Platforms tested: IE Misc. update: --- doc/html/fortran/h5p_FORTRAN.html | 453 ++++++++++++++++++++++++++++++++------ 1 file changed, 381 insertions(+), 72 deletions(-) diff --git a/doc/html/fortran/h5p_FORTRAN.html b/doc/html/fortran/h5p_FORTRAN.html index f0913ec..e91c2b2 100644 --- a/doc/html/fortran/h5p_FORTRAN.html +++ b/doc/html/fortran/h5p_FORTRAN.html @@ -301,7 +301,7 @@ FORTRAN Property List API -- h5p SUBROUTINE h5pset_userblock_f (prp_id, size, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier - INTEGER(HSIZE_T), INTENT(IN) :: size !Size of the user-block in bytes + INTEGER(HSIZE_T), INTENT(IN) :: size ! Size of the user-block in bytes INTEGER, INTENT(OUT) :: hdferr ! Error code ! 0 on success and -1 on failure END SUBROUTINE h5pset_userblock_f @@ -347,10 +347,10 @@ FORTRAN Property List API -- h5p SUBROUTINE h5pset_sizes_f (prp_id, sizeof_addr, sizeof_size, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier - INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr !Size of an object - !offset in bytes - INTEGER(SIZE_T), INTENT(IN) :: sizeof_size !Size of an object - !length in bytes + INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr ! Size of an object + ! offset in bytes + INTEGER(SIZE_T), INTENT(IN) :: sizeof_size ! Size of an object + ! length in bytes INTEGER, INTENT(OUT) :: hdferr ! Error code ! 0 on success and -1 on failure @@ -469,7 +469,7 @@ FORTRAN Property List API -- h5p SUBROUTINE h5pget_istore_k_f(prp_id, ik, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier - INTEGER, INTENT(OUT) :: ik !1/2 rank of chunked storage B-tree + INTEGER, INTENT(OUT) :: ik ! 1/2 rank of chunked storage B-tree INTEGER, INTENT(OUT) :: hdferr ! Error code ! 0 on success and -1 on failure END SUBROUTINE h5pget_istore_k_f @@ -822,70 +822,33 @@ FORTRAN Property List API -- h5p

 


  - +

  -

FORTRAN interface:   h5pset_split_f +
FORTRAN interface:   h5pset_fapl_split_f
 
 
-          SUBROUTINE h5pset_split_f(prp_id, meta_ext, meta_plist, raw_ext, raw_plist, hdferr)
+          SUBROUTINE h5pset_fapl_split_f(prp_id, meta_ext, meta_plist, raw_ext, raw_plist, hdferr)
             IMPLICIT NONE
-            INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
-            CHARACTER(LEN=*), INTENT(IN) :: meta_ext  !Name of the extension for
-                                                      !the metafile filename
-            INTEGER(HID_T), INTENT(IN) :: meta_plist  ! Identifier of the meta file
+            INTEGER(HID_T),INTENT(IN)   :: prp_id     ! Property list identifier
+            CHARACTER(LEN=*),INTENT(IN) :: meta_ext   ! Name of the extension for
+                                                      ! the metafile filename
+            INTEGER(HID_T),INTENT(IN)   :: meta_plist ! Identifier of the meta file
                                                       ! access property list
-            CHARACTER(LEN=*), INTENT(IN) :: raw_ext  !Name extension for the raw file filename
-            INTEGER(HID_T), INTENT(IN) :: raw_plist  !Identifier of the raw file
-                                                     !access property list
-            INTEGER, INTENT(OUT) :: hdferr  ! Error code
-                                           ! 0 on success and -1 on failure
-
-          END SUBROUTINE h5pset_split_f
-
- - -

  -

  -


-

  - -

  - - - -

FORTRAN interface:   h5pget_split_f -
-
-
-
-          SUBROUTINE h5pget_split_f(prp_id, meta_ext_size, meta_ext, meta_plist,raw_ext_size,&
-                                     raw_ext, raw_plist, hdferr)
-            IMPLICIT NONE
-            INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
-            INTEGER(SIZE_T), INTENT(IN) :: meta_ext_size ! Number of characters of the meta
-                                                         ! file extension to be copied to the
-                                                         ! meta_ext buffer
-
-            CHARACTER(LEN=*), INTENT(OUT) :: meta_ext  ! Name of the extension for
-                                                       ! the metafile filename
-            INTEGER(HID_T), INTENT(OUT) :: meta_plist  ! Identifier of the meta file
-                                                       ! access property list
-            INTEGER(SIZE_T), INTENT(IN) :: raw_ext_size ! Number of characters of the raw
-                                                         ! file extension to be copied to the
-                                                         ! raw_ext buffer
-            CHARACTER(LEN=*), INTENT(OUT) :: raw_ext  ! Name extension for the raw file filename
-            INTEGER(HID_T), INTENT(OUT) :: raw_plist  ! Identifier of the raw file
+            CHARACTER(LEN=*),INTENT(IN) :: raw_ext    ! Name extension for the raw file filename
+            INTEGER(HID_T),INTENT(IN)   :: raw_plist  ! Identifier of the raw file
                                                       ! access property list
             INTEGER, INTENT(OUT) :: hdferr  ! Error code
                                             ! 0 on success and -1 on failure
-          END SUBROUTINE h5pget_split_f
+
+          END SUBROUTINE h5pset_fapl_split_f
 
+

 

 


@@ -1272,7 +1235,6 @@ FORTRAN Property List API -- h5p END SUBROUTINE h5pget_fapl_mpio_f -

 

 


@@ -1322,6 +1284,224 @@ FORTRAN Property List API -- h5p END SUBROUTINE h5pget_dxpl_mpio_f +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_core_f +
+
+          SUBROUTINE h5pset_fapl_core_f(prp_id, increment, backing_store, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)  :: prp_id    ! Property list identifier
+            INTEGER(SIZE_T), INTENT(IN) :: increment ! File block size in bytes
+            LOGICAL, INTENT(IN) :: backing_store     ! flag to indicate that
+                                   ! entire file contents are flushed to a file
+                                   ! with the same name as this core file
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_core_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_fapl_core_f +
+
+          SUBROUTINE h5pget_fapl_core_f(prp_id, increment, backing_store, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)  :: prp_id     ! Property list identifier
+            INTEGER(SIZE_T), INTENT(OUT) :: increment ! File block size in bytes
+            LOGICAL, INTENT(OUT) :: backing_store     ! flag to indicate that
+                                   ! entire file contents are flushed to a file
+                                   ! with the same name as this core file
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pget_fapl_core_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_multi_f +
+
+          SUBROUTINE h5pset_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, &
+                                         memb_addr, relax, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T),INTENT(IN)   :: prp_id    ! Property list identifier
+            INTEGER,DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN)          :: memb_map
+            INTEGER(HID_T),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN)   :: memb_fapl
+            CHARACTER(LEN=*),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN) :: memb_name
+            REAL, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN)           :: memb_addr
+                  ! Numbers in the interval [0,1) (e.g. 0.0 0.1 0.5 0.2 0.3 0.4)
+                  ! real address in the file will be calculated as X*HADDR_MAX 
+            LOGICAL, INTENT(IN)  :: relax
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_multi_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_multi_f +
+
+          SUBROUTINE h5pset_fapl_multi_f(prp_id, relax, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T),INTENT(IN)   :: prp_id    ! Property list identifier
+            LOGICAL, INTENT(IN)  :: relax
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_multi_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_fapl_multi_f +
+
+          SUBROUTINE h5pget_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, &
+                                         memb_addr, relax, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T),INTENT(IN)   :: prp_id    ! Property list identifier
+            INTEGER,DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT)          :: memb_map
+            INTEGER(HID_T),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT)   :: memb_fapl
+            CHARACTER(LEN=*),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT) :: memb_name
+            REAL, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT)           :: memb_addr
+                  ! Numbers in the interval [0,1) (e.g. 0.0 0.1 0.5 0.2 0.3 0.4)
+                  ! real address in the file will be calculated as X*HADDR_MAX 
+            LOGICAL, INTENT(OUT) :: relax
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pget_fapl_multi_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_family_f +
+
+          SUBROUTINE h5pset_fapl_family_f(prp_id, imemb_size, memb_plist, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)   :: prp_id    ! Property list identifier
+            INTEGER(HSIZE_T), INTENT(IN) :: memb_size ! Logical size, in bytes,
+                                                      ! of each family member
+            INTEGER(HID_T), INTENT(IN) :: memb_plist  ! identifier of the file 
+                                                      ! access property list to 
+                                                      ! be used for each family 
+                                                      ! member
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_family_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_fapl_family_f +
+
+          SUBROUTINE h5pget_fapl_family_f(prp_id, imemb_size, memb_plist, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)    :: prp_id    ! Property list identifier
+            INTEGER(HSIZE_T), INTENT(OUT) :: memb_size ! Logical size, in bytes,
+                                                       ! of each family member
+            INTEGER(HID_T), INTENT(OUT) :: memb_plist  ! identifier of the file 
+                                                       ! access property list to 
+                                                       ! be used for each family 
+                                                       ! member
+            INTEGER, INTENT(OUT) :: hdferr  ! Error code
+                                            ! 0 on success and -1 on failure
+          END SUBROUTINE h5pget_fapl_family_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_sec2_f +
+
+          SUBROUTINE h5pset_fapl_sec2_f(prp_id, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)    :: prp_id    ! Property list identifier
+            INTEGER, INTENT(OUT)          :: hdferr    ! Error code
+                                                       ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_sec2_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_fapl_stdio_f +
+
+          SUBROUTINE h5pset_fapl_stdio_f(prp_id, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)    :: prp_id  ! Property list identifier
+            INTEGER, INTENT(OUT)          :: hdferr  ! Error code
+                                                     ! 0 on success and -1 on failure
+          END SUBROUTINE h5pset_fapl_stdio_f
+
+ +

 

  @@ -1403,6 +1583,30 @@ FORTRAN Property List API -- h5p +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_driver_f +
+
+         SUBROUTINE h5pget_driver_f(prp_id, driver_id, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN)  :: prp_id    !  File access or data
+                                                     !  transfer property list 
+                                                     !  identifier
+            INTEGER(HID_T), INTENT(OUT) :: driver_id !  low-level file driver identifier
+            INTEGER, INTENT(OUT)        :: hdferr    ! Error code
+                                                     ! 0 on success and -1 on failure
+          END SUBROUTINE h5pget_driver_f 
+
+
+

 

  @@ -1418,11 +1622,11 @@ FORTRAN Property List API -- h5p SUBROUTINE h5pset_buffer_f(plist_id, size, hdferr) IMPLICIT NONE - INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer - ! property list identifier - INTEGER(HSIZE_T), INTENT(IN) :: size ! Conversion buffer size - INTEGER, INTENT(OUT) :: hdferr ! Error code - ! 0 on success and -1 on failure + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer + ! property list identifier + INTEGER(HSIZE_T), INTENT(IN) :: size ! Conversion buffer size + INTEGER, INTENT(OUT) :: hdferr ! Error code + ! 0 on success and -1 on failure END SUBROUTINE h5pset_buffer_f @@ -1442,11 +1646,11 @@ FORTRAN Property List API -- h5p SUBROUTINE h5pget_buffer_f(plist_id, size, hdferr) IMPLICIT NONE - INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer - ! property list identifier - INTEGER(HSIZE_T), INTENT(OUT) :: size ! Conversion buffer size - INTEGER, INTENT(OUT) :: hdferr ! Error code - ! 0 on success and -1 on failure + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer + ! property list identifier + INTEGER(HSIZE_T), INTENT(OUT) :: size ! Conversion buffer size + INTEGER, INTENT(OUT) :: hdferr ! Error code + ! 0 on success and -1 on failure END SUBROUTINE h5pget_buffer_f @@ -2109,7 +2313,7 @@ FORTRAN Property List API -- h5p INTEGER(HID_T), INTENT(IN) :: src_id ! Source property list identifier CHARACTER(LEN=*), INTENT(IN) :: name ! Property name INTEGER, INTENT(OUT) :: hdferr ! Error code - ! 0 on success and -1 on failure + ! 0 on success and -1 on failure END SUBROUTINE h5pcopy_prop_f @@ -2132,7 +2336,7 @@ FORTRAN Property List API -- h5p INTEGER(HID_T), INTENT(IN) :: plid ! property list identifier CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove INTEGER, INTENT(OUT) :: hdferr ! Error code - ! 0 on success and -1 on failure + ! 0 on success and -1 on failure END SUBROUTINE h5premove_f @@ -2155,7 +2359,7 @@ FORTRAN Property List API -- h5p INTEGER(HID_T), INTENT(IN) :: class ! property list class identifier CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove INTEGER, INTENT(OUT) :: hdferr ! Error code - ! 0 on success and -1 on failure + ! 0 on success and -1 on failure END SUBROUTINE h5punregister_f @@ -2248,16 +2452,65 @@ FORTRAN Property List API -- h5p

FORTRAN interface:   h5pset_shuffle_f
 
-          SUBROUTINE h5pset_shuffle_f(prp_id, type_size, hdferr) 
+          SUBROUTINE h5pset_shuffle_f(prp_id, hdferr) 
             IMPLICIT NONE
             INTEGER(HID_T), INTENT(IN) :: prp_id      ! Property list identifier 
-            INTEGER, INTENT(IN)        :: type_size   ! Datatype size in bytes
             INTEGER, INTENT(OUT)       :: hdferr      ! Error code
                                                       ! 0 on success and -1 on failure
  
           END SUBROUTINE h5pset_shuffle_f
 
+

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_preserve_f +
+
+          SUBROUTINE h5pset_preserve_f(prp_id, flag, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN) :: prp_id      ! Dataset transfer property 
+                                                      ! list identifier 
+            LOGICAL, INTENT(IN)        :: flag        ! Status of for the dataset 
+                                                      ! transfer property list 
+            INTEGER, INTENT(OUT)       :: hdferr      ! Error code
+                                                      ! 0 on success and -1 on failure
+ 
+          END SUBROUTINE h5pset_preserve_f
+
+ +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_preserve_f +
+
+          SUBROUTINE h5pget_preserve_f(prp_id, flag, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN) :: prp_id      ! Dataset transfer property 
+                                                      ! list identifier 
+            LOGICAL, INTENT(OUT)       :: flag        ! Status of for the dataset 
+                                                      ! transfer property list 
+            INTEGER, INTENT(OUT)       :: hdferr      ! Error code
+                                                      ! 0 on success and -1 on failure
+ 
+          END SUBROUTINE h5pget_preserve_f
+
+ + +

 

 

  @@ -2308,6 +2561,38 @@ FORTRAN Property List API -- h5p END SUBROUTINE h5pget_edc_check_f +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pset_szip_f +
+
+          SUBROUTINE h5pset_szip_f(prp_id, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN) :: prp_id      ! Dataset creation property 
+                                                      ! list identifier 
+            INTEGER, INTENT(IN) :: options_mask       ! A bit-mask conveying the 
+                                                      ! desired szip options
+                                                      ! Current possible values
+                                                      ! in Fortran:
+                                                      ! H5_SZIP_RAW_OM_F
+                                                      ! H5_SZIP_NN_OM_F
+                                                      ! H5_SZIP_RAWORNN_OM_F
+            INTEGER, INTENT(IN) :: pixels_per_block   ! The number of pixels or data
+                                                      ! elements in each data block
+            INTEGER, INTENT(OUT)       :: hdferr      ! Error code
+                                                      ! 0 on success and -1 on failure
+ 
+          END SUBROUTINE h5pset_szip_f
+
+ +

 

 

  @@ -2330,6 +2615,30 @@ FORTRAN Property List API -- h5p END SUBROUTINE h5pset_fletcher32_f +

  +

  +


+

  + +

  + + + +

FORTRAN interface:   h5pget_nfilters_f +
+
+          SUBROUTINE h5pget_nfilters_f(prp_id, nfilters, hdferr) 
+            IMPLICIT NONE
+            INTEGER(HID_T), INTENT(IN) :: prp_id      ! Dataset creation property 
+                                                      ! list identifier 
+            INTEGER, INTENT(OUT) :: nfilters          ! The number of filters in 
+                                                      ! the pipeline
+            INTEGER, INTENT(OUT)       :: hdferr      ! Error code
+                                                      ! 0 on success and -1 on failure
+ 
+          END SUBROUTINE h5pget_nfilters_f
+
+

 

  @@ -2343,7 +2652,7 @@ FORTRAN Property List API -- h5p Describes HDF5 Release 1.5, Unreleased Development Branch -Last modified: 7 April 2003 +Last modified: 4 June 2003 -- cgit v0.12