1!****h* ROBODoc/H5A
2!
3! NAME
4!  MODULE H5A
5!
6! PURPOSE
7!  This file contains Fortran interfaces for H5A functions. It includes
8!  all the functions that are independent on whether the Fortran 2003 functions
9!  are enabled or disabled.
10!
11!
12! COPYRIGHT
13! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
14!   Copyright by The HDF Group.                                               *
15!   Copyright by the Board of Trustees of the University of Illinois.         *
16!   All rights reserved.                                                      *
17!                                                                             *
18!   This file is part of HDF5.  The full HDF5 copyright notice, including     *
19!   terms governing use, modification, and redistribution, is contained in    *
20!   the COPYING file, which can be found at the root of the source code       *
21!   distribution tree, or in https://support.hdfgroup.org/ftp/HDF5/releases.  *
22!   If you do not have access to either file, you may request a copy from     *
23!   help@hdfgroup.org.                                                        *
24! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
25!
26! NOTES
27!                         *** IMPORTANT ***
28!  If you add a new H5A function you must add the function name to the
29!  Windows dll file 'hdf5_fortrandll.def.in' in the fortran/src directory.
30!  This is needed for Windows based operating systems.
31!
32!*****
33
34MODULE H5A
35
36  USE H5GLOBAL
37!
38!  On Windows there are no big (integer*8) integers, so overloading
39!  for bug #670 does not work. I have to use DEC compilation directives to make
40!  Windows DEC Visual Fortran and OSF compilers happy and do right things.
41!  05/01/02 EP
42!
43
44CONTAINS
45
46!
47!****s* H5A/h5acreate_f
48!
49! NAME
50!  h5acreate_f
51!
52! PURPOSE
53!  Creates a dataset as an attribute of a group, dataset, or named datatype
54!
55! INPUTS
56!  loc_id 	 - identifier of an object (group, dataset,
57!                  or named datatype) attribute is attached to
58!  name 	 - attribute name
59!  type_id 	 - attribute datatype identifier
60!  space_id 	 - attribute dataspace identifier
61!
62! OUTPUTS
63!  attr_id 	 - attribute identifier
64!  hdferr 	 - Returns 0 if successful and -1 if fails
65! OPTIONAL PARAMETERS
66!  acpl_id 	 - Attribute creation property list identifier
67!  appl_id 	 - Attribute access property list identifier
68!
69! AUTHOR
70!  Elena Pourmal
71!  August 12, 1999
72!
73! HISTORY
74!  Explicit Fortran interfaces are added for
75!  called C functions (it is needed for Windows
76!  port).  February 27, 2001
77!
78!
79! SOURCE
80  SUBROUTINE h5acreate_f(loc_id, name, type_id, space_id, attr_id, &
81                                 hdferr, acpl_id, aapl_id )
82    IMPLICIT NONE
83    INTEGER(HID_T), INTENT(IN) :: loc_id   ! Object identifier
84    CHARACTER(LEN=*), INTENT(IN) :: name   ! Attribute name
85    INTEGER(HID_T), INTENT(IN) :: type_id  ! Attribute datatype identifier
86    INTEGER(HID_T), INTENT(IN) :: space_id ! Attribute dataspace identifier
87    INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
88    INTEGER, INTENT(OUT) :: hdferr         ! Error code:
89                                           ! 0 on success and -1 on failure
90!*****
91    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: acpl_id ! Attribute creation property list identifier
92    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list identifier
93
94    INTEGER(HID_T) :: acpl_id_default
95    INTEGER(HID_T) :: aapl_id_default
96    INTEGER(SIZE_T) :: namelen
97    INTERFACE
98       INTEGER FUNCTION h5acreate_c(loc_id, name, namelen, type_id, &
99            space_id, acpl_id_default, aapl_id_default, attr_id)
100         USE H5GLOBAL
101         !DEC$IF DEFINED(HDF5F90_WINDOWS)
102         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ACREATE_C'::h5acreate_c
103         !DEC$ENDIF
104         !DEC$ATTRIBUTES reference :: name
105         INTEGER(HID_T), INTENT(IN) :: loc_id
106         CHARACTER(LEN=*), INTENT(IN) :: name
107         INTEGER(SIZE_T) :: namelen
108         INTEGER(HID_T), INTENT(IN) :: type_id
109         INTEGER(HID_T), INTENT(IN) :: space_id
110         INTEGER(HID_T) :: acpl_id_default
111         INTEGER(HID_T) :: aapl_id_default
112         INTEGER(HID_T), INTENT(OUT) :: attr_id
113       END FUNCTION h5acreate_c
114    END INTERFACE
115
116    acpl_id_default = H5P_DEFAULT_F
117    aapl_id_default = H5P_DEFAULT_F
118    namelen = LEN(name)
119    IF (PRESENT(acpl_id)) acpl_id_default = acpl_id
120    IF (PRESENT(aapl_id)) aapl_id_default = aapl_id
121
122    hdferr = h5acreate_c(loc_id, name, namelen, type_id, space_id, &
123         acpl_id_default, aapl_id_default, attr_id)
124
125  END SUBROUTINE h5acreate_f
126
127
128!
129!****s* H5A/h5aopen_name_f
130!
131! NAME
132!  h5aopen_name_f
133!
134! PURPOSE
135!  Opens an attribute specified by name.
136!
137! INPUTS
138!  obj_id 	 - identifier of a group, dataset, or named
139!                  datatype atttribute to be attached to
140!  name 	 - attribute name
141! OUTPUTS
142!  attr_id 	 - attribute identifier
143!  hdferr 	 - Returns 0 if successful and -1 if fails
144!
145! AUTHOR
146!  Elena Pourmal
147!  August 12, 1999
148!
149! HISTORY
150!  Explicit Fortran interfaces are added for
151!  called C functions (it is needed for Windows
152!  port).  February 27, 2001
153!
154! SOURCE
155  SUBROUTINE h5aopen_name_f(obj_id, name, attr_id, hdferr)
156    IMPLICIT NONE
157    INTEGER(HID_T), INTENT(IN) :: obj_id    ! Object identifier
158    CHARACTER(LEN=*), INTENT(IN) :: name    ! Attribute name
159    INTEGER(HID_T), INTENT(OUT) :: attr_id  ! Attribute identifier
160    INTEGER, INTENT(OUT) :: hdferr          ! Error code
161!*****
162    INTEGER(SIZE_T) :: namelen
163
164    INTERFACE
165       INTEGER FUNCTION h5aopen_name_c(obj_id, name, namelen, attr_id)
166         USE H5GLOBAL
167         !DEC$IF DEFINED(HDF5F90_WINDOWS)
168         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_NAME_C'::h5aopen_name_c
169         !DEC$ENDIF
170         !DEC$ATTRIBUTES reference :: name
171         INTEGER(HID_T), INTENT(IN) :: obj_id
172         CHARACTER(LEN=*), INTENT(IN) :: name
173         INTEGER(SIZE_T) :: namelen
174         INTEGER(HID_T), INTENT(OUT) :: attr_id
175       END FUNCTION h5aopen_name_c
176    END INTERFACE
177
178    namelen = LEN(name)
179    hdferr = h5aopen_name_c(obj_id, name, namelen, attr_id)
180  END SUBROUTINE h5aopen_name_f
181!
182!****s* H5A/h5aopen_idx_f
183!
184! NAME
185!  h5aopen_idx_f
186!
187! PURPOSE
188!  Opens the attribute specified by its index.
189!
190! INPUTS
191!  obj_id 	 - identifier of a group, dataset, or named
192!                  datatype an attribute to be attached to
193!  index 	 - index of the attribute to open (zero-based)
194! OUTPUTS
195!  attr_id 	 - attribute identifier
196!  hdferr 	 - Returns 0 if successful and -1 if fails
197!
198! AUTHOR
199!  Elena Pourmal
200!  August 12, 1999
201!
202! HISTORY
203!  Explicit Fortran interfaces are added for
204!  called C functions (it is needed for Windows
205!  port).  February 27, 2001
206!
207! SOURCE
208  SUBROUTINE h5aopen_idx_f(obj_id, index, attr_id, hdferr)
209    IMPLICIT NONE
210    INTEGER(HID_T), INTENT(IN) :: obj_id    ! Object identifier
211    INTEGER, INTENT(IN) :: index            ! Attribute index
212    INTEGER(HID_T), INTENT(OUT) :: attr_id  ! Attribute identifier
213    INTEGER, INTENT(OUT) :: hdferr          ! Error code
214!*****
215
216    INTERFACE
217       INTEGER FUNCTION h5aopen_idx_c(obj_id, index, attr_id)
218         USE H5GLOBAL
219         !DEC$IF DEFINED(HDF5F90_WINDOWS)
220         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_IDX_C'::h5aopen_idx_c
221         !DEC$ENDIF
222         INTEGER(HID_T), INTENT(IN) :: obj_id
223         INTEGER, INTENT(IN) :: index
224         INTEGER(HID_T), INTENT(OUT) :: attr_id
225       END FUNCTION h5aopen_idx_c
226    END INTERFACE
227
228    hdferr = h5aopen_idx_c(obj_id, index, attr_id)
229  END SUBROUTINE h5aopen_idx_f
230!
231!****s* H5A/h5aget_space_f
232!
233! NAME
234!  h5aget_space_f
235!
236! PURPOSE
237!  Gets a copy of the dataspace for an attribute.
238!
239! INPUTS
240!  attr_id 	 - attribute identifier
241!
242! OUTPUTS
243!  space_id 	 - attribite dataspace identifier
244!  hdferr 	 - Returns 0 if successful and -1 if fails
245!
246! AUTHOR
247!  Elena Pourmal
248!  August 12, 1999
249!
250! HISTORY
251!  Explicit Fortran interfaces are added for
252!  called C functions (it is needed for Windows
253!  port).  February 27, 2001
254!
255!
256! SOURCE
257  SUBROUTINE h5aget_space_f(attr_id, space_id, hdferr)
258    IMPLICIT NONE
259    INTEGER(HID_T), INTENT(IN) :: attr_id   ! Attribute identifier
260    INTEGER(HID_T), INTENT(OUT) :: space_id ! Attribute dataspace identifier
261    INTEGER, INTENT(OUT) :: hdferr          ! Error code
262!*****
263    INTERFACE
264       INTEGER FUNCTION h5aget_space_c(attr_id, space_id)
265         USE H5GLOBAL
266         !DEC$IF DEFINED(HDF5F90_WINDOWS)
267         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_SPACE_C'::h5aget_space_c
268         !DEC$ENDIF
269         INTEGER(HID_T), INTENT(IN) :: attr_id
270         INTEGER(HID_T), INTENT(OUT) :: space_id
271       END FUNCTION h5aget_space_c
272    END INTERFACE
273
274    hdferr = h5aget_space_c(attr_id, space_id)
275  END SUBROUTINE h5aget_space_f
276!
277!****s* H5A/h5aget_type_f
278!
279! NAME
280!  h5aget_type_f
281!
282! PURPOSE
283!  Gets an attribute datatype.
284!
285! INPUTS
286!  attr_id 	 - attribute identifier
287! OUTPUTS
288!  type_id 	 - attribute datatype identifier
289!  hdferr 	 - Returns 0 if successful and -1 if fails
290!
291! AUTHOR
292!  Elena Pourmal
293!  August 12, 1999
294!
295! HISTORY
296!  Explicit Fortran interfaces are added for
297!  called C functions (it is needed for Windows
298!  port).  February 27, 2001
299!
300! SOURCE
301  SUBROUTINE h5aget_type_f(attr_id, type_id, hdferr)
302    IMPLICIT NONE
303    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Attribute identifier
304    INTEGER(HID_T), INTENT(OUT) :: type_id ! Attribute datatype identifier
305    INTEGER, INTENT(OUT) :: hdferr         ! Error code
306!*****
307    INTERFACE
308       INTEGER FUNCTION h5aget_type_c(attr_id, type_id)
309         USE H5GLOBAL
310         !DEC$IF DEFINED(HDF5F90_WINDOWS)
311         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_TYPE_C'::h5aget_type_c
312         !DEC$ENDIF
313         INTEGER(HID_T), INTENT(IN) :: attr_id
314         INTEGER(HID_T), INTENT(OUT) :: type_id
315       END FUNCTION h5aget_type_c
316    END INTERFACE
317
318    hdferr = h5aget_type_c(attr_id, type_id)
319  END SUBROUTINE h5aget_type_f
320!
321!****s* H5A/h5aget_name_f
322!
323! NAME
324!  h5aget_name_f
325!
326! PURPOSE
327!  Gets an attribute name.
328!
329! INPUTS
330!  attr_id 	 - attribute identifier
331!  size 	 - size of a buffer to read name in
332! OUTPUTS
333!  buf 	         - buffer to read name in
334!  hdferr 	 - Returns 0 if successful and -1 if fails
335!
336! AUTHOR
337!  Elena Pourmal
338!  August 12, 1999
339!
340! HISTORY
341!  Explicit Fortran interfaces are added for
342!  called C functions (it is needed for Windows
343!  port).  February 27, 2001
344!
345!
346! SOURCE
347  SUBROUTINE h5aget_name_f(attr_id, size, buf, hdferr)
348    IMPLICIT NONE
349    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Attribute identifier
350    INTEGER(SIZE_T), INTENT(IN) :: size    ! Buffer size
351    CHARACTER(LEN=*), INTENT(INOUT) :: buf ! Buffer to hold attribute name
352    INTEGER, INTENT(OUT) :: hdferr ! Error code:
353                                   ! name length is successful, -1 if fail
354!*****
355    INTERFACE
356       INTEGER FUNCTION h5aget_name_c(attr_id, size, buf)
357         USE H5GLOBAL
358         !DEC$IF DEFINED(HDF5F90_WINDOWS)
359         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_NAME_C'::h5aget_name_c
360         !DEC$ENDIF
361         !DEC$ATTRIBUTES reference :: buf
362         INTEGER(HID_T), INTENT(IN) :: attr_id
363         INTEGER(SIZE_T), INTENT(IN) :: size
364         CHARACTER(LEN=*), INTENT(OUT) :: buf
365       END FUNCTION h5aget_name_c
366    END INTERFACE
367
368    hdferr = h5aget_name_c(attr_id, size, buf)
369  END SUBROUTINE h5aget_name_f
370
371!
372!****s* H5A/h5aget_name_by_idx_f
373!
374! NAME
375!  h5aget_name_by_idx_f
376!
377! PURPOSE
378!  Gets an attribute name, by attribute index position.
379!
380! INPUTS
381!  loc_id 	 - Location of object to which attribute is attached
382!  obj_name 	 - Name of object to which attribute is attached, relative to location
383!  idx_type 	 - Type of index; Possible values are:
384!                   H5_INDEX_UNKNOWN_F = -1  - Unknown index type
385!                   H5_INDEX_NAME_F 	     - Index on names
386!                   H5_INDEX_CRT_ORDER_F     - Index on creation order
387!                   H5_INDEX_N_F 	     - Number of indices defined
388!
389!  order 	 - Order in which to iterate over index; Possible values are:
390!                   H5_ITER_UNKNOWN_F 	 - Unknown order
391!                   H5_ITER_INC_F 	 - Increasing order
392!                   H5_ITER_DEC_F 	 - Decreasing order
393!                   H5_ITER_NATIVE_F 	 - No particular order, whatever is fastest
394!                   H5_ITER_N_F 	 - Number of iteration orders
395!  order 	 - Index traversal order
396!  n 	         - Attribute’s position in index
397!
398! OUTPUTS
399!  name 	 - Attribute name
400!  hdferr 	 - Returns 0 if successful and -1 if fails
401!
402! OPTIONAL PARAMETERS
403!  lapl_id 	 - Link access property list
404!  size 	 - Size, in bytes, of attribute name
405!
406! AUTHOR
407!  M. Scot Breitenfeld
408!  January, 2008
409!
410! SOURCE
411  SUBROUTINE h5aget_name_by_idx_f(loc_id, obj_name, idx_type, order, &
412       n, name, hdferr, size, lapl_id)
413    IMPLICIT NONE
414    INTEGER(HID_T), INTENT(IN) :: loc_id      ! Identifer for object to which attribute is attached
415    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object, relative to location,
416                                              !  from which attribute is to be removed *TEST* check NULL
417    INTEGER, INTENT(IN) :: idx_type ! Type of index; Possible values are:
418                                    !    H5_INDEX_UNKNOWN_F   - Unknown index type
419                                    !    H5_INDEX_NAME_F       - Index on names
420                                    !    H5_INDEX_CRT_ORDER_F  - Index on creation order
421                                    !    H5_INDEX_N_F 	      - Number of indices defined
422
423    INTEGER, INTENT(IN) :: order    ! Order in which to iterate over index; Possible values are:
424                                    !    H5_ITER_UNKNOWN_F   - Unknown order
425                                    !    H5_ITER_INC_F      - Increasing order
426                                    !    H5_ITER_DEC_F       - Decreasing order
427                                    !    H5_ITER_NATIVE_F    - No particular order, whatever is fastest
428                                    !    H5_ITER_N_F 	    - Number of iteration orders
429    INTEGER(HSIZE_T), INTENT(IN) :: n !  Attribute’s position in index
430    CHARACTER(LEN=*), INTENT(OUT) :: name ! Attribute name
431    INTEGER, INTENT(OUT) :: hdferr    ! Error code:
432                                      ! Returns attribute name size,
433                                      ! -1 if fail
434    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
435    INTEGER(SIZE_T), OPTIONAL, INTENT(OUT) :: size  ! Indicates the size, in the number of characters,
436                                                    ! of the attribute
437!*****
438    INTEGER(HID_T) :: lapl_id_default
439    INTEGER(SIZE_T) :: obj_namelen
440    INTEGER(SIZE_T) :: size_default
441
442    INTERFACE
443       INTEGER FUNCTION h5aget_name_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, &
444            n, name, size_default, lapl_id_default)
445         USE H5GLOBAL
446         !DEC$IF DEFINED(HDF5F90_WINDOWS)
447         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_NAME_BY_IDX_C'::h5aget_name_by_idx_c
448         !DEC$ENDIF
449         !DEC$ATTRIBUTES reference :: obj_name, name
450         INTEGER(HID_T), INTENT(IN) :: loc_id
451         CHARACTER(LEN=*), INTENT(IN) :: obj_name
452         INTEGER, INTENT(IN) :: idx_type
453         INTEGER, INTENT(IN) :: order
454         INTEGER(HSIZE_T), INTENT(IN) :: n
455
456         CHARACTER(LEN=*), INTENT(OUT) :: name
457         INTEGER(SIZE_T) :: size_default
458         INTEGER(HID_T) :: lapl_id_default
459         INTEGER(SIZE_T) :: obj_namelen
460       END FUNCTION h5aget_name_by_idx_c
461    END INTERFACE
462
463    obj_namelen = LEN(obj_name)
464    lapl_id_default = H5P_DEFAULT_F
465    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
466
467    size_default = LEN(name)
468
469    hdferr = h5aget_name_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, &
470         n, name, size_default, lapl_id_default)
471
472    IF(PRESENT(size)) size = size_default
473
474
475  END SUBROUTINE h5aget_name_by_idx_f
476!
477!****s* H5A/h5aget_num_attrs_f
478!
479! NAME
480!  h5aget_num_attrs_f
481!
482! PURPOSE
483!  Determines the number of attributes attached to an object.
484!
485! INPUTS
486!  obj_id 	 - object (group, dataset, or named datatype)
487!  identifier
488! OUTPUTS
489!  attr_num 	 - number of attributes attached to the object
490!  hdferr 	 - Returns 0 if successful and -1 if fails
491!
492! AUTHOR
493!  Elena Pourmal
494!  August 12, 1999
495!
496! HISTORY
497!  Explicit Fortran interfaces are added for
498!  called C functions (it is needed for Windows
499!  port).  February 27, 2001
500!
501! SOURCE
502  SUBROUTINE h5aget_num_attrs_f(obj_id, attr_num, hdferr)
503    IMPLICIT NONE
504    INTEGER(HID_T), INTENT(IN) :: obj_id  ! Object identifier
505    INTEGER, INTENT(OUT) :: attr_num      ! Number of attributes of the object
506    INTEGER, INTENT(OUT) :: hdferr        ! Error code
507!*****
508
509    INTERFACE
510       INTEGER FUNCTION h5aget_num_attrs_c(obj_id, attr_num)
511         USE H5GLOBAL
512         !DEC$IF DEFINED(HDF5F90_WINDOWS)
513         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_NUM_ATTRS_C'::h5aget_num_attrs_c
514         !DEC$ENDIF
515         INTEGER(HID_T), INTENT(IN) :: obj_id
516         INTEGER, INTENT(OUT) :: attr_num
517       END FUNCTION h5aget_num_attrs_c
518    END INTERFACE
519
520    hdferr = h5aget_num_attrs_c(obj_id, attr_num)
521  END SUBROUTINE h5aget_num_attrs_f
522
523!
524!****s* H5A/h5adelete_f
525!
526! NAME
527!  h5adelete_f
528!
529! PURPOSE
530!  Deletes an attribute of an object (group, dataset or
531!  named datatype)
532!
533! INPUTS
534!  obj_id 	 - object identifier
535!  name 	 - attribute name
536! OUTPUTS
537!
538!  hdferr 	 - Returns 0 if successful and -1 if fails
539! AUTHOR
540!  Elena Pourmal
541!  August 12, 1999
542!
543! HISTORY
544!  Explicit Fortran interfaces are added for
545!  called C functions (it is needed for Windows
546!  port).  February 27, 2001
547!
548! SOURCE
549  SUBROUTINE h5adelete_f(obj_id, name, hdferr)
550    IMPLICIT NONE
551    INTEGER(HID_T), INTENT(IN) :: obj_id  ! Object identifier
552    CHARACTER(LEN=*), INTENT(IN) :: name  ! Attribute name
553    INTEGER, INTENT(OUT) :: hdferr        ! Error code
554!*****
555    INTEGER(SIZE_T) :: namelen
556
557    INTERFACE
558       INTEGER FUNCTION h5adelete_c(obj_id, name, namelen)
559         USE H5GLOBAL
560         !DEC$IF DEFINED(HDF5F90_WINDOWS)
561         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ADELETE_C'::h5adelete_c
562         !DEC$ENDIF
563         !DEC$ATTRIBUTES reference :: name
564         INTEGER(HID_T), INTENT(IN) :: obj_id
565         CHARACTER(LEN=*), INTENT(IN) :: name
566         INTEGER(SIZE_T) :: namelen
567       END FUNCTION h5adelete_c
568    END INTERFACE
569
570    namelen = LEN(name)
571    hdferr = h5adelete_c(obj_id, name, namelen)
572  END SUBROUTINE h5adelete_f
573
574!
575!****s* H5A/h5aclose_f
576!
577! NAME
578!  h5aclose_f
579!
580! PURPOSE
581!  Closes the specified attribute.
582!
583! INPUTS
584!  attr_id  - attribute identifier
585! OUTPUTS
586!
587!  hdferr   - Returns 0 if successful and -1 if fails
588!
589! AUTHOR
590!  Elena Pourmal
591!  August 12, 1999
592!
593! HISTORY
594!  Explicit Fortran interfaces are added for
595!  called C functions (it is needed for Windows
596!  port).  February 27, 2001
597! SOURCE
598  SUBROUTINE h5aclose_f(attr_id, hdferr)
599    IMPLICIT NONE
600    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Attribute identifier
601    INTEGER, INTENT(OUT) :: hdferr         ! Error code
602!*****
603
604    INTERFACE
605       INTEGER FUNCTION h5aclose_c(attr_id)
606         USE H5GLOBAL
607         !DEC$IF DEFINED(HDF5F90_WINDOWS)
608         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ACLOSE_C'::h5aclose_c
609         !DEC$ENDIF
610         INTEGER(HID_T), INTENT(IN) :: attr_id
611       END FUNCTION h5aclose_c
612    END INTERFACE
613
614    hdferr = h5aclose_c(attr_id)
615  END SUBROUTINE h5aclose_f
616
617!
618!****s* H5A/h5aget_storage_size_f
619!
620! NAME
621!  h5aget_storage_size_f
622!
623! PURPOSE
624!  Returns the amount of storage required for an attribute.
625!
626! INPUTS
627!  attr_id 	 - attribute identifier
628! OUTPUTS
629!  size 	 - attribute storage size
630!  hdferr 	 - Returns 0 if successful and -1 if fails
631! AUTHOR
632!  M. Scot Breitenfeld
633!  January, 2008
634!
635! SOURCE
636  SUBROUTINE h5aget_storage_size_f(attr_id, size, hdferr)
637    IMPLICIT NONE
638    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Attribute identifier
639    INTEGER(HSIZE_T), INTENT(OUT) :: size  ! Attribute storage requirement
640    INTEGER, INTENT(OUT) :: hdferr         ! Error code
641!*****
642
643    INTERFACE
644       INTEGER FUNCTION h5aget_storage_size_c(attr_id, size)
645         USE H5GLOBAL
646         !DEC$IF DEFINED(HDF5F90_WINDOWS)
647         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_STORAGE_SIZE_C'::h5aget_storage_size_c
648         !DEC$ENDIF
649         INTEGER(HID_T), INTENT(IN) :: attr_id
650         INTEGER(HSIZE_T), INTENT(OUT) :: size
651       END FUNCTION h5aget_storage_size_c
652    END INTERFACE
653
654    hdferr = h5aget_storage_size_c(attr_id, size)
655  END SUBROUTINE h5aget_storage_size_f
656
657!
658!****s* H5A/h5aget_create_plist_f
659!
660! NAME
661!  h5aget_create_plist_f
662!
663! PURPOSE
664!  Gets an attribute creation property list identifier
665!
666! INPUTS
667!  attr_id 	    - Identifier of the attribute
668! OUTPUTS
669!  creation_prop_id - Identifier for the attribute’s creation property
670!  hdferr 	    - Returns 0 if successful and -1 if fails
671!
672! AUTHOR
673!  M. Scot Breitenfeld
674!  January, 2008
675!
676! SOURCE
677  SUBROUTINE h5aget_create_plist_f(attr_id, creation_prop_id, hdferr)
678    IMPLICIT NONE
679    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Identifier of the attribute
680    INTEGER(HID_T), INTENT(OUT) :: creation_prop_id   ! Identifier for the attribute’s creation property
681    INTEGER, INTENT(OUT) :: hdferr       ! Error code
682                                         ! 0 on success and -1 on failure
683!*****
684
685    INTERFACE
686       INTEGER FUNCTION h5aget_create_plist_c(attr_id, creation_prop_id)
687         USE H5GLOBAL
688         !DEC$IF DEFINED(HDF5F90_WINDOWS)
689         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_CREATE_PLIST_C'::h5aget_create_plist_c
690         !DEC$ENDIF
691         INTEGER(HID_T), INTENT(IN) :: attr_id
692         INTEGER(HID_T), INTENT(OUT) :: creation_prop_id
693       END FUNCTION h5aget_create_plist_c
694    END INTERFACE
695
696    hdferr = h5aget_create_plist_c(attr_id, creation_prop_id)
697  END SUBROUTINE h5aget_create_plist_f
698
699!
700!****s* H5A/h5arename_by_name_f
701!
702! NAME
703!  h5arename_by_name_f
704!
705! PURPOSE
706!  Renames an attribute
707!
708! INPUTS
709!  loc_id 	 - Location or object identifier; may be dataset or group
710!  obj_name 	 - Name of object, relative to location,
711!                  whose attribute is to be renamed
712!  old_attr_name - Prior attribute name
713!  new_attr_name - New attribute name
714!  lapl_id 	 - Link access property list identifier
715!
716! OUTPUTS
717!  hdferr 	 - Returns 0 if successful and -1 if fails
718!
719! AUTHOR
720!  M. Scot Breitenfeld
721!  January, 2008
722!
723! SOURCE
724  SUBROUTINE h5arename_by_name_f(loc_id, obj_name, old_attr_name, new_attr_name, &
725        hdferr, lapl_id)
726    IMPLICIT NONE
727    INTEGER(HID_T), INTENT(IN) :: loc_id    ! Object identifier
728    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object, relative to location,
729                                              !  whose attribute is to be renamed
730    CHARACTER(LEN=*), INTENT(IN) :: old_attr_name ! Prior attribute name
731    CHARACTER(LEN=*), INTENT(IN) :: new_attr_name ! New attribute name
732
733    INTEGER, INTENT(OUT) :: hdferr       ! Error code:
734                                         ! 0 on success and -1 on failure
735    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
736!*****
737    INTEGER(HID_T) :: lapl_id_default
738    INTEGER(SIZE_T) :: obj_namelen
739    INTEGER(SIZE_T) :: old_attr_namelen
740    INTEGER(SIZE_T) :: new_attr_namelen
741
742    INTERFACE
743       INTEGER FUNCTION h5arename_by_name_c(loc_id, obj_name, obj_namelen, &
744            old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen, &
745            lapl_id_default)
746         USE H5GLOBAL
747         !DEC$IF DEFINED(HDF5F90_WINDOWS)
748         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ARENAME_BY_NAME_C'::h5arename_by_name_c
749         !DEC$ENDIF
750         !DEC$ATTRIBUTES reference :: obj_name, old_attr_name, new_attr_name
751         INTEGER(HID_T), INTENT(IN) :: loc_id
752         CHARACTER(LEN=*), INTENT(IN) :: obj_name
753         INTEGER(SIZE_T) :: obj_namelen
754         CHARACTER(LEN=*), INTENT(IN) :: old_attr_name
755         INTEGER(SIZE_T) :: old_attr_namelen
756         CHARACTER(LEN=*), INTENT(IN) :: new_attr_name
757         INTEGER(SIZE_T) :: new_attr_namelen
758         INTEGER(HID_T) :: lapl_id_default
759
760       END FUNCTION h5arename_by_name_c
761    END INTERFACE
762
763    obj_namelen = LEN(obj_name)
764    old_attr_namelen = LEN(old_attr_name)
765    new_attr_namelen = LEN(new_attr_name)
766
767    lapl_id_default = H5P_DEFAULT_F
768    IF(PRESENT(lapl_id)) lapl_id_default=lapl_id
769
770    hdferr = h5arename_by_name_c(loc_id, obj_name, obj_namelen, &
771         old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen, &
772         lapl_id_default)
773
774  END SUBROUTINE h5arename_by_name_f
775
776!
777!****s* H5A/h5aopen_f
778!
779! NAME
780!  h5aopen_f
781!
782! PURPOSE
783!  Opens an attribute for an object specified by object
784!  identifier and attribute name
785!
786! INPUTS
787!  obj_id 	 - Identifer for object to which attribute is attached
788!  attr_name 	 - Name of attribute to open
789! OUTPUTS
790!  attr_id 	 - attribute identifier
791
792! OPTIONAL PARAMETERS
793!  aapl_id 	 - Attribute access property list
794!  hdferr 	 - Returns 0 if successful and -1 if fails
795!
796! AUTHOR
797!  M. Scot Breitenfeld
798!  January, 2008
799!
800! SOURCE
801  SUBROUTINE h5aopen_f(obj_id, attr_name, attr_id, hdferr, aapl_id)
802    IMPLICIT NONE
803    INTEGER(HID_T), INTENT(IN) :: obj_id      ! Object identifier
804    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
805    INTEGER(HID_T), INTENT(OUT) :: attr_id    ! Attribute identifier
806    INTEGER, INTENT(OUT) :: hdferr            ! Error code
807                                              !   Success:  0
808                                              !   Failure: -1
809    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id     ! Attribute access property list
810!*****
811    INTEGER(HID_T) :: aapl_id_default
812
813    INTEGER(SIZE_T) :: attr_namelen
814
815    INTERFACE
816       INTEGER FUNCTION h5aopen_c(obj_id, attr_name, attr_namelen, aapl_id_default, attr_id)
817         USE H5GLOBAL
818         !DEC$IF DEFINED(HDF5F90_WINDOWS)
819         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_C'::h5aopen_c
820         !DEC$ENDIF
821         !DEC$ATTRIBUTES reference :: attr_name
822         INTEGER(HID_T), INTENT(IN) :: obj_id
823         CHARACTER(LEN=*), INTENT(IN) :: attr_name
824         INTEGER(HID_T) :: aapl_id_default
825         INTEGER(SIZE_T) :: attr_namelen
826         INTEGER(HID_T), INTENT(OUT) :: attr_id
827       END FUNCTION h5aopen_c
828    END INTERFACE
829
830    attr_namelen = LEN(attr_name)
831
832    aapl_id_default = H5P_DEFAULT_F
833    IF(PRESENT(aapl_id)) aapl_id_default = aapl_id
834
835    hdferr = h5aopen_c(obj_id, attr_name, attr_namelen, aapl_id_default, attr_id)
836
837  END SUBROUTINE h5aopen_f
838
839!
840!****s* H5A/h5adelete_by_idx_f
841!
842! NAME
843!  h5adelete_by_idx_f
844!
845! PURPOSE
846!  Deletes an attribute from an object according to index order
847!
848! INPUTS
849!  loc_id 	 - Location or object identifier; may be dataset or group
850!  obj_name 	 - Name of object, relative to location, from which attribute is to be removed
851!  idx_type 	 - Type of index; Possible values are:
852!                   H5_INDEX_UNKNOWN_F = -1  - Unknown index type
853!                   H5_INDEX_NAME_F 	     - Index on names
854!                   H5_INDEX_CRT_ORDER_F     - Index on creation order
855!                   H5_INDEX_N_F 	     - Number of indices defined
856!
857!  order 	 - Order in which to iterate over index; Possible values are:
858!                   H5_ITER_UNKNOWN_F 	 - Unknown order
859!                   H5_ITER_INC_F 	 - Increasing order
860!                   H5_ITER_DEC_F 	 - Decreasing order
861!                   H5_ITER_NATIVE_F 	 - No particular order, whatever is fastest
862!                   H5_ITER_N_F 	 - Number of iteration orders
863!
864!  n 	         - Offset within index
865! OUTPUTS
866!  hdferr 	 - Returns 0 if successful and -1 if fails
867! OPTIONAL PARAMETERS
868!  lapl_id 	 - Link access property list
869!
870! AUTHOR
871!  M. Scot Breitenfeld
872!  January, 2008
873!
874! SOURCE
875  SUBROUTINE h5adelete_by_idx_f(loc_id, obj_name, idx_type, order, n, hdferr, lapl_id)
876    IMPLICIT NONE
877    INTEGER(HID_T), INTENT(IN) :: loc_id      ! Identifer for object to which attribute is attached
878    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object, relative to location,
879                                              !  from which attribute is to be removed
880    INTEGER, INTENT(IN) :: idx_type           ! Type of index; Possible values are:
881                                              !    H5_INDEX_UNKNOWN_F   - Unknown index type
882                                              !    H5_INDEX_NAME_F      - Index on names
883                                              !    H5_INDEX_CRT_ORDER_F - Index on creation order
884                                              !    H5_INDEX_N_F	      - Number of indices defined
885
886    INTEGER, INTENT(IN) :: order              ! Order in which to iterate over index; Possible values are:
887                                              !    H5_ITER_UNKNOWN_F  - Unknown order
888                                              !    H5_ITER_INC_F      - Increasing order
889                                              !    H5_ITER_DEC_F      - Decreasing order
890                                              !    H5_ITER_NATIVE_F   - No particular order, whatever is fastest
891                                              !    H5_ITER_N_F	    - Number of iteration orders
892    INTEGER(HSIZE_T), INTENT(IN) :: n         ! Offset within index
893    INTEGER, INTENT(OUT) :: hdferr         ! Error code:
894                                           ! 0 on success and -1 on failure
895    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
896!*****
897    INTEGER(SIZE_T) :: obj_namelen
898    INTEGER(HID_T) :: lapl_id_default
899
900    INTERFACE
901       INTEGER FUNCTION h5adelete_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, lapl_id_default)
902         USE H5GLOBAL
903         !DEC$IF DEFINED(HDF5F90_WINDOWS)
904         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ADELETE_BY_IDX_C'::h5adelete_by_idx_c
905         !DEC$ENDIF
906         !DEC$ATTRIBUTES reference :: obj_name
907         INTEGER(HID_T), INTENT(IN) :: loc_id
908         CHARACTER(LEN=*), INTENT(IN) :: obj_name
909         INTEGER, INTENT(IN) :: idx_type
910         INTEGER, INTENT(IN) :: order
911         INTEGER(HSIZE_T), INTENT(IN) :: n
912         INTEGER(HID_T) :: lapl_id_default
913         INTEGER(SIZE_T) :: obj_namelen
914       END FUNCTION h5adelete_by_idx_c
915    END INTERFACE
916
917    lapl_id_default = H5P_DEFAULT_F
918    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
919
920    obj_namelen = LEN(obj_name)
921    hdferr = h5adelete_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, lapl_id_default)
922
923  END SUBROUTINE h5adelete_by_idx_f
924
925!
926!****s* H5A/h5adelete_by_name_f
927!
928! NAME
929!  h5adelete_by_name_f
930!
931! PURPOSE
932!  Removes an attribute from a specified location
933!
934! INPUTS
935!  loc_id 	 - Identifer for object to which attribute is attached
936!  obj_name 	 - Name of attribute to open
937!  attr_name 	 - Attribute access property list
938!  lapl_id 	 - Link access property list
939! OUTPUTS
940!  hdferr 	 - Returns 0 if successful and -1 if fails
941!
942! AUTHOR
943!  M. Scot Breitenfeld
944!  January, 2008
945!
946! SOURCE
947  SUBROUTINE h5adelete_by_name_f(loc_id, obj_name, attr_name, hdferr, lapl_id)
948    IMPLICIT NONE
949    INTEGER(HID_T), INTENT(IN) :: loc_id      ! Identifer for object to which attribute is attached
950    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object, relative to location,
951                                              !  from which attribute is to be removed
952    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Name of attribute to delete
953    INTEGER, INTENT(OUT) :: hdferr            ! Error code:
954                                              ! 0 on success and -1 on failure
955    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
956!*****
957    INTEGER(SIZE_T) :: attr_namelen
958    INTEGER(SIZE_T) :: obj_namelen
959
960    INTEGER(HID_T) :: lapl_id_default
961
962    INTERFACE
963       INTEGER FUNCTION h5adelete_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default)
964         USE H5GLOBAL
965         !DEC$IF DEFINED(HDF5F90_WINDOWS)
966         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ADELETE_BY_NAME_C'::h5adelete_by_name_c
967         !DEC$ENDIF
968         !DEC$ATTRIBUTES reference :: obj_name, attr_name
969         INTEGER(HID_T), INTENT(IN) :: loc_id
970         CHARACTER(LEN=*), INTENT(IN) :: obj_name
971         CHARACTER(LEN=*), INTENT(IN) :: attr_name
972         INTEGER(HID_T) :: lapl_id_default
973         INTEGER(SIZE_T) :: attr_namelen
974         INTEGER(SIZE_T) :: obj_namelen
975       END FUNCTION h5adelete_by_name_c
976    END INTERFACE
977
978    obj_namelen = LEN(obj_name)
979    attr_namelen = LEN(attr_name)
980
981    lapl_id_default = H5P_DEFAULT_F
982    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
983
984    hdferr = h5adelete_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default)
985
986  END SUBROUTINE h5adelete_by_name_f
987
988!
989!****s* H5A/h5aopen_by_idx_f
990!
991! NAME
992!  h5aopen_by_idx_f
993!
994! PURPOSE
995!  Opens an existing attribute that is attached to an object specified by location and name
996!
997! INPUTS
998!  loc_id 	 - Location of object to which attribute is attached
999!  obj_name 	 - Name of object to which attribute is attached, relative to location
1000!  idx_type 	 - Type of index
1001!  order 	 - Index traversal order
1002!  n 	         - Attribute’s position in index
1003! OUTPUTS
1004!  hdferr 	 - Returns 0 if successful and -1 if fails
1005! OPTIONAL PARAMETERS
1006!  aapl_id 	 - Attribute access property list
1007!  lapl_id 	 - Link access property list
1008!
1009! AUTHOR
1010!  M. Scot Breitenfeld
1011!  January, 2008
1012!
1013! SOURCE
1014  SUBROUTINE h5aopen_by_idx_f(loc_id, obj_name, idx_type, order, n, attr_id, hdferr, aapl_id, lapl_id)
1015    IMPLICIT NONE
1016    INTEGER(HID_T), INTENT(IN) :: loc_id      ! Object identifier
1017    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object to which attribute is attached
1018    INTEGER, INTENT(IN) :: idx_type           ! Type of index; Possible values are:
1019                                              !    H5_INDEX_UNKNOWN_F   - Unknown index type
1020                                              !    H5_INDEX_NAME_F      - Index on names
1021                                              !    H5_INDEX_CRT_ORDER_F - Index on creation order
1022                                              !    H5_INDEX_N_F	      - Number of indices defined
1023    INTEGER, INTENT(IN) :: order              ! Order in which to iterate over index; Possible values are:
1024                                              !    H5_ITER_UNKNOWN_F  - Unknown order
1025                                              !    H5_ITER_INC_F      - Increasing order
1026                                              !    H5_ITER_DEC_F      - Decreasing order
1027                                              !    H5_ITER_NATIVE_F   - No particular order, whatever is fastest
1028
1029    INTEGER(HSIZE_T), INTENT(IN) :: n       ! Attribute’s position in index
1030
1031    INTEGER(HID_T), INTENT(OUT) :: attr_id  ! Attribute identifier
1032    INTEGER, INTENT(OUT) :: hdferr          ! Error code:
1033                                            ! 0 on success and -1 on failure
1034    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id  ! Attribute access property list
1035    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id  ! Link access property list
1036!*****
1037    INTEGER(SIZE_T) :: obj_namelen
1038    INTEGER(HID_T) :: aapl_id_default
1039    INTEGER(HID_T) :: lapl_id_default
1040
1041    INTERFACE
1042       INTEGER FUNCTION h5aopen_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, &
1043            aapl_id_default, lapl_id_default, attr_id)
1044         USE H5GLOBAL
1045         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1046         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_BY_IDX_C'::h5aopen_by_idx_c
1047         !DEC$ENDIF
1048         !DEC$ATTRIBUTES reference :: obj_name
1049         INTEGER(HID_T), INTENT(IN) :: loc_id
1050         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1051         INTEGER, INTENT(IN) :: idx_type
1052         INTEGER, INTENT(IN) :: order
1053         INTEGER(HSIZE_T), INTENT(IN) :: n
1054         INTEGER(HID_T) :: aapl_id_default
1055         INTEGER(HID_T) :: lapl_id_default
1056         INTEGER(SIZE_T) :: obj_namelen
1057         INTEGER(HID_T), INTENT(OUT) :: attr_id  ! Attribute identifier
1058       END FUNCTION h5aopen_by_idx_c
1059    END INTERFACE
1060
1061    obj_namelen = LEN(obj_name)
1062
1063    aapl_id_default = H5P_DEFAULT_F
1064    IF(PRESENT(aapl_id)) aapl_id_default = aapl_id
1065    lapl_id_default = H5P_DEFAULT_F
1066    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
1067
1068    hdferr = h5aopen_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, &
1069         aapl_id_default, lapl_id_default, attr_id)
1070
1071  END SUBROUTINE h5aopen_by_idx_f
1072
1073!
1074!****s* H5A/h5aget_info_f
1075!
1076! NAME
1077!  h5aget_info_f
1078!
1079! PURPOSE
1080!  Retrieves attribute information, by attribute identifier
1081!
1082! INPUTS
1083!  attr_id 	 - attribute identifier
1084!
1085! OUTPUTS
1086!  NOTE: In C it is defined as a structure: H5A_info_t
1087!
1088!  corder_valid  - indicates whether the creation order data is valid for this attribute
1089!  corder 	 - is a positive integer containing the creation order of the attribute
1090!  cset 	 - indicates the character set used for the attribute’s name
1091!  data_size 	 - indicates the size, in the number of characters, of the attribute
1092!  hdferr 	 - Returns 0 if successful and -1 if fails
1093! AUTHOR
1094!  M. Scot Breitenfeld
1095!  January, 2008
1096! SOURCE
1097  SUBROUTINE h5aget_info_f(attr_id, f_corder_valid, corder, cset, data_size, hdferr)
1098    IMPLICIT NONE
1099    INTEGER(HID_T), INTENT(IN) :: attr_id  ! Attribute identifier
1100
1101    LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
1102    INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
1103    INTEGER, INTENT(OUT) :: cset   ! Indicates the character set used for the attribute’s name
1104    INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
1105    INTEGER, INTENT(OUT) :: hdferr       ! Error code:
1106                                         ! 0 on success and -1 on failure
1107!*****
1108    INTEGER :: corder_valid
1109
1110    INTERFACE
1111       INTEGER FUNCTION h5aget_info_c(attr_id, corder_valid, corder, cset, data_size)
1112         USE H5GLOBAL
1113         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1114         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_INFO_C'::h5aget_info_c
1115         !DEC$ENDIF
1116         INTEGER(HID_T), INTENT(IN) :: attr_id
1117
1118         INTEGER, INTENT(OUT) :: corder_valid
1119         INTEGER, INTENT(OUT) :: corder
1120         INTEGER, INTENT(OUT) :: cset
1121         INTEGER(HSIZE_T), INTENT(OUT) :: data_size
1122       END FUNCTION h5aget_info_c
1123    END INTERFACE
1124
1125    hdferr = h5aget_info_c(attr_id, corder_valid, corder, cset, data_size)
1126
1127    f_corder_valid =.FALSE.
1128    IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
1129
1130
1131  END SUBROUTINE h5aget_info_f
1132
1133!
1134!****s* H5A/h5aget_info_by_idx_f
1135!
1136! NAME
1137!  h5aget_info_by_idx_f
1138!
1139! PURPOSE
1140!  Retrieves attribute information, by attribute index position
1141!
1142! INPUTS
1143!  loc_id 	 - Location of object to which attribute is attached
1144!  obj_name 	 - Name of object to which attribute is attached, relative to location
1145!  idx_type 	 - Type of index
1146!  order 	 - Index traversal order
1147!  n 	         - Attribute’s position in index
1148!
1149! OUTPUTS  NOTE: In C it is defined as a structure: H5A_info_t
1150!  corder_valid  - indicates whether the creation order data is valid for this attribute
1151!  corder 	 - is a positive integer containing the creation order of the attribute
1152!  cset 	 - indicates the character set used for the attribute’s name
1153!  data_size 	 - indicates the size, in the number of characters, of the attribute
1154!  hdferr 	 - Returns 0 if successful and -1 if fails
1155! OPTIONAL PARAMETERS
1156!  lapl_id 	 - Link access property list
1157!
1158! AUTHOR
1159!  M. Scot Breitenfeld
1160!  January, 2008
1161!
1162! SOURCE
1163  SUBROUTINE h5aget_info_by_idx_f(loc_id, obj_name, idx_type, order, n, &
1164       f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
1165    IMPLICIT NONE
1166    INTEGER(HID_T), INTENT(IN) :: loc_id      ! Object identifier
1167    CHARACTER(LEN=*), INTENT(IN) :: obj_name  ! Name of object to which attribute is attached
1168    INTEGER, INTENT(IN) :: idx_type           ! Type of index; Possible values are:
1169                                              !    H5_INDEX_UNKNOWN_F   - Unknown index type
1170                                              !    H5_INDEX_NAME_F      - Index on names
1171                                              !    H5_INDEX_CRT_ORDER_F - Index on creation order
1172                                              !    H5_INDEX_N_F	      - Number of indices defined
1173    INTEGER, INTENT(IN) :: order              ! Order in which to iterate over index; Possible values are:
1174                                              !    H5_ITER_UNKNOWN_F  - Unknown order
1175                                              !    H5_ITER_INC_F      - Increasing order
1176                                              !    H5_ITER_DEC_F      - Decreasing order
1177                                              !    H5_ITER_NATIVE_F   - No particular order, whatever is fastest
1178
1179    INTEGER(HSIZE_T), INTENT(IN) :: n         ! Attribute’s position in index
1180
1181
1182    LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
1183    INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
1184    INTEGER, INTENT(OUT) :: cset   ! Indicates the character set used for the attribute’s name
1185    INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
1186    INTEGER, INTENT(OUT) :: hdferr       ! Error code:
1187                                         ! 0 on success and -1 on failure
1188    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id  ! Link access property list
1189!*****
1190    INTEGER :: corder_valid
1191    INTEGER(SIZE_T)  :: obj_namelen
1192    INTEGER(HID_T) :: lapl_id_default
1193
1194    INTERFACE
1195       INTEGER FUNCTION h5aget_info_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, lapl_id_default, &
1196            corder_valid, corder, cset, data_size)
1197         USE H5GLOBAL
1198         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1199         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_INFO_BY_IDX_C'::h5aget_info_by_idx_c
1200         !DEC$ENDIF
1201         !DEC$ATTRIBUTES reference :: obj_name
1202         INTEGER(HID_T), INTENT(IN) :: loc_id
1203         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1204         INTEGER, INTENT(IN) :: idx_type
1205         INTEGER, INTENT(IN) :: order
1206         INTEGER(HSIZE_T), INTENT(IN) :: n
1207         INTEGER(HID_T) :: lapl_id_default
1208         INTEGER, INTENT(OUT) :: corder_valid
1209         INTEGER, INTENT(OUT) :: corder
1210         INTEGER, INTENT(OUT) :: cset
1211         INTEGER(HSIZE_T), INTENT(OUT) :: data_size
1212
1213         INTEGER(SIZE_T)  :: obj_namelen
1214       END FUNCTION h5aget_info_by_idx_c
1215    END INTERFACE
1216
1217    obj_namelen = LEN(obj_name)
1218
1219    lapl_id_default = H5P_DEFAULT_F
1220    IF(present(lapl_id)) lapl_id_default = lapl_id
1221
1222    hdferr = h5aget_info_by_idx_c(loc_id, obj_name, obj_namelen, idx_type, order, n, lapl_id_default, &
1223            corder_valid, corder, cset, data_size)
1224
1225    f_corder_valid =.FALSE.
1226    IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
1227
1228  END SUBROUTINE h5aget_info_by_idx_f
1229
1230!
1231!****s* H5A/h5aget_info_by_name_f
1232!
1233! NAME
1234!  h5aget_info_by_name_f
1235!
1236! PURPOSE
1237!  Retrieves attribute information, by attribute name
1238!
1239! INPUTS
1240!  loc_id 	 - Location of object to which attribute is attached
1241!  obj_name 	 - Name of object to which attribute is attached, relative to location
1242!  attr_name 	 - Attribute name
1243!
1244! OUTPUTS  NOTE: In C it is defined as a structure: H5A_info_t
1245!  corder_valid  - indicates whether the creation order data is valid for this attribute
1246!  corder 	 - is a positive integer containing the creation order of the attribute
1247!  cset 	 - indicates the character set used for the attribute’s name
1248!  data_size 	 - indicates the size, in the number of characters, of the attribute
1249!  hdferr 	 - Returns 0 if successful and -1 if fails
1250! OPTIONAL PARAMETERS
1251!  lapl_id 	 - Link access property list
1252!
1253! AUTHOR
1254!  M. Scot Breitenfeld
1255!  January, 2008
1256!
1257! SOURCE
1258  SUBROUTINE h5aget_info_by_name_f(loc_id, obj_name, attr_name, &
1259       f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
1260    IMPLICIT NONE
1261    INTEGER(HID_T), INTENT(IN) :: loc_id    ! Object identifier
1262    CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of object to which attribute is attached
1263    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
1264
1265
1266    LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
1267    INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
1268    INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
1269    INTEGER(HSIZE_T), INTENT(OUT) :: data_size   ! Indicates the size, in the number of characters, of the attribute
1270    INTEGER, INTENT(OUT) :: hdferr         ! Error code:
1271                                           ! 0 on success and -1 on failure
1272    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id  ! Link access property list
1273!*****
1274    INTEGER :: corder_valid
1275    INTEGER(SIZE_T)  :: obj_namelen
1276    INTEGER(SIZE_T)  :: attr_namelen
1277    INTEGER(HID_T) :: lapl_id_default
1278
1279    INTERFACE
1280       INTEGER FUNCTION h5aget_info_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, &
1281            corder_valid, corder, cset, data_size)
1282         USE H5GLOBAL
1283         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1284         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AGET_INFO_BY_NAME_C'::h5aget_info_by_name_c
1285         !DEC$ENDIF
1286         !DEC$ATTRIBUTES reference :: obj_name, attr_name
1287         INTEGER(HID_T), INTENT(IN) :: loc_id
1288         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1289         INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
1290         CHARACTER(LEN=*), INTENT(IN) :: attr_name
1291         INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
1292         INTEGER(HID_T) :: lapl_id_default
1293         INTEGER, INTENT(OUT) :: corder_valid
1294         INTEGER, INTENT(OUT) :: corder
1295         INTEGER, INTENT(OUT) :: cset
1296         INTEGER(HSIZE_T), INTENT(OUT) :: data_size
1297
1298       END FUNCTION h5aget_info_by_name_c
1299    END INTERFACE
1300
1301    obj_namelen = LEN(obj_name)
1302    attr_namelen = LEN(attr_name)
1303
1304    lapl_id_default = H5P_DEFAULT_F
1305    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
1306
1307    hdferr = h5aget_info_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, &
1308            corder_valid, corder, cset, data_size)
1309
1310    f_corder_valid =.FALSE.
1311    IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
1312
1313  END SUBROUTINE h5aget_info_by_name_f
1314
1315!
1316!****s* H5A/h5acreate_by_name_f
1317!
1318! NAME
1319!  h5acreate_by_name_f
1320!
1321! PURPOSE
1322!  Creates an attribute attached to a specified object
1323!
1324! INPUTS
1325!  loc_id 	 - Location or object identifier; may be dataset or group
1326!  obj_name 	 - Name, relative to loc_id, of object that attribute is to be attached to
1327!  attr_name 	 - Attribute name
1328!  type_id 	 - Attribute datatype identifier
1329!  space_id 	 - Attribute dataspace identifier
1330!
1331! OUTPUTS
1332!  attr 	 - an attribute identifier
1333!  hdferr 	 - Returns 0 if successful and -1 if fails
1334! OPTIONAL PARAMETERS
1335!  acpl_id 	 - Attribute creation property list identifier (Currently not used.)
1336!  aapl_id 	 - Attribute access property list identifier (Currently not used.)
1337!  lapl_id 	 - Link access property list
1338!
1339! AUTHOR
1340!  M. Scot Breitenfeld
1341!  February, 2008
1342! SOURCE
1343  SUBROUTINE h5acreate_by_name_f(loc_id, obj_name, attr_name, type_id, space_id, attr, hdferr, &
1344       acpl_id, aapl_id, lapl_id)
1345    IMPLICIT NONE
1346    INTEGER(HID_T),   INTENT(IN)  :: loc_id
1347    CHARACTER(LEN=*), INTENT(IN)  :: obj_name
1348    CHARACTER(LEN=*), INTENT(IN)  :: attr_name
1349    INTEGER(HID_T),   INTENT(IN)  :: type_id
1350    INTEGER(HID_T),   INTENT(IN)  :: space_id
1351    INTEGER(HID_T),   INTENT(OUT) :: attr
1352    INTEGER,          INTENT(OUT) :: hdferr
1353
1354    INTEGER(HID_T),   INTENT(IN), OPTIONAL :: acpl_id
1355    INTEGER(HID_T),   INTENT(IN), OPTIONAL :: aapl_id
1356    INTEGER(HID_T),   INTENT(IN), OPTIONAL :: lapl_id
1357!*****
1358    INTEGER(SIZE_T)  :: obj_namelen
1359    INTEGER(SIZE_T)  :: attr_namelen
1360
1361    INTEGER(HID_T) :: acpl_id_default
1362    INTEGER(HID_T) :: aapl_id_default
1363    INTEGER(HID_T) :: lapl_id_default
1364
1365    INTERFACE
1366       INTEGER FUNCTION h5acreate_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, &
1367            type_id, space_id, acpl_id_default, aapl_id_default, lapl_id_default, attr)
1368         USE H5GLOBAL
1369         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1370         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ACREATE_BY_NAME_C'::h5acreate_by_name_c
1371         !DEC$ENDIF
1372         !DEC$ATTRIBUTES reference :: obj_name, attr_name
1373         INTEGER(HID_T), INTENT(IN) :: loc_id
1374         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1375         INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
1376         CHARACTER(LEN=*), INTENT(IN) :: attr_name
1377         INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
1378         INTEGER(HID_T), INTENT(IN) :: type_id
1379         INTEGER(HID_T), INTENT(IN) :: space_id
1380         INTEGER(HID_T) :: acpl_id_default
1381         INTEGER(HID_T) :: aapl_id_default
1382         INTEGER(HID_T) :: lapl_id_default
1383         INTEGER(HID_T), INTENT(OUT) :: attr
1384
1385       END FUNCTION h5acreate_by_name_c
1386    END INTERFACE
1387
1388    obj_namelen = LEN(obj_name)
1389    attr_namelen = LEN(attr_name)
1390
1391    acpl_id_default = H5P_DEFAULT_F
1392    aapl_id_default = H5P_DEFAULT_F
1393    lapl_id_default = H5P_DEFAULT_F
1394
1395    IF(PRESENT(acpl_id)) acpl_id_default = acpl_id
1396    IF(PRESENT(aapl_id)) aapl_id_default = aapl_id
1397    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
1398
1399    hdferr = h5acreate_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, &
1400            type_id, space_id, acpl_id_default, aapl_id_default, lapl_id_default, attr)
1401  END SUBROUTINE h5acreate_by_name_f
1402
1403!
1404!****s* H5A/H5Aexists_f
1405!
1406! NAME
1407!  H5Aexists_f
1408!
1409! PURPOSE
1410!  Determines whether an attribute with a given name exists on an object
1411!
1412! INPUTS
1413!  obj_id 	 - Object identifier
1414!  attr_name 	 - Attribute name
1415!
1416! OUTPUTS
1417!  attr_exists 	 - attribute exists status
1418!  hdferr 	 - Returns 0 if successful and -1 if fails
1419!
1420! AUTHOR
1421!  M. Scot Breitenfeld
1422!  February, 2008
1423!
1424! SOURCE
1425  SUBROUTINE h5aexists_f(obj_id, attr_name, attr_exists, hdferr)
1426    IMPLICIT NONE
1427    INTEGER(HID_T), INTENT(IN) :: obj_id      ! Object identifier
1428    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
1429    LOGICAL, INTENT(OUT) :: attr_exists  ! .TRUE. if exists, .FALSE. otherwise
1430    INTEGER, INTENT(OUT) :: hdferr       ! Error code:
1431                                         ! 0 on success and -1 on failure
1432!*****
1433    INTEGER(HID_T) :: attr_exists_c
1434    INTEGER(SIZE_T) :: attr_namelen
1435
1436    INTERFACE
1437       INTEGER FUNCTION h5aexists_c(obj_id, attr_name, attr_namelen, attr_exists_c)
1438         USE H5GLOBAL
1439         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1440         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AEXISTS_C'::h5aexists_c
1441         !DEC$ENDIF
1442         !DEC$ATTRIBUTES reference :: attr_name
1443         INTEGER(HID_T), INTENT(IN) :: obj_id
1444         CHARACTER(LEN=*), INTENT(IN) :: attr_name
1445         INTEGER(SIZE_T) :: attr_namelen
1446         INTEGER(HID_T) :: attr_exists_c
1447       END FUNCTION h5aexists_c
1448    END INTERFACE
1449
1450    attr_namelen = LEN(attr_name)
1451
1452    hdferr = h5aexists_c(obj_id, attr_name, attr_namelen, attr_exists_c)
1453
1454    attr_exists = .FALSE.
1455    IF(attr_exists_c.GT.0) attr_exists = .TRUE.
1456
1457  END SUBROUTINE h5aexists_f
1458
1459!
1460!****s* H5A/H5Aexists_by_name_f
1461!
1462! NAME
1463!  H5Aexists_by_name_f
1464!
1465! PURPOSE
1466!  Determines whether an attribute with a given name exists on an object
1467!
1468! INPUTS
1469!  loc_id 	 - Location identifier
1470!  obj_name 	 - Object name either relative to loc_id, absolute from the file’s root group, or '.' (a dot)
1471!  attr_name 	 - Attribute name
1472!
1473! OUTPUTS
1474!  attr_exists 	 - attribute exists status
1475!  hdferr 	 - Returns 0 if successful and -1 if fails
1476! OPTIONAL PARAMETERS
1477!  lapl_id 	 - Link access property list identifier
1478!
1479! AUTHOR
1480!  M. Scot Breitenfeld
1481!  February, 2008
1482!
1483! SOURCE
1484  SUBROUTINE h5aexists_by_name_f(loc_id, obj_name, attr_name, attr_exists, hdferr, lapl_id)
1485    IMPLICIT NONE
1486    INTEGER(HID_T), INTENT(IN) :: loc_id     ! Location identifier
1487    CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
1488                                             ! absolute from the file’s root group, or '.'
1489    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
1490    LOGICAL, INTENT(OUT) :: attr_exists ! .TRUE. if exists, .FALSE. otherwise
1491    INTEGER, INTENT(OUT) :: hdferr      ! Error code:
1492                                        ! 0 on success and -1 on failure
1493    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
1494!*****
1495    INTEGER :: attr_exists_c
1496    INTEGER(SIZE_T)  :: obj_namelen
1497    INTEGER(SIZE_T)  :: attr_namelen
1498
1499    INTEGER(HID_T) :: lapl_id_default
1500
1501    INTERFACE
1502       INTEGER FUNCTION h5aexists_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, attr_exists_c)
1503         USE H5GLOBAL
1504         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1505         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AEXISTS_BY_NAME_C'::h5aexists_by_name_c
1506         !DEC$ENDIF
1507         !DEC$ATTRIBUTES reference :: obj_name, attr_name
1508         INTEGER(HID_T), INTENT(IN) :: loc_id
1509         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1510         INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
1511         CHARACTER(LEN=*), INTENT(IN) :: attr_name
1512         INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
1513         INTEGER(HID_T), INTENT(IN) :: lapl_id_default
1514         INTEGER, INTENT(OUT) :: attr_exists_c
1515       END FUNCTION h5aexists_by_name_c
1516    END INTERFACE
1517
1518    attr_namelen = LEN(attr_name)
1519    obj_namelen = LEN(obj_name)
1520
1521    lapl_id_default = H5P_DEFAULT_F
1522    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
1523
1524    hdferr = h5aexists_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, lapl_id_default, attr_exists_c)
1525
1526    attr_exists = .FALSE.
1527    IF(attr_exists_c.GT.0) attr_exists = .TRUE.
1528
1529  END SUBROUTINE h5aexists_by_name_f
1530!
1531!****s* H5A/H5Aopen_by_name_f
1532!
1533! NAME
1534!  H5Aopen_by_name_f
1535!
1536! PURPOSE
1537!  Opens an attribute for an object by object name and attribute name.
1538!
1539! INPUTS
1540!  loc_id 	 - Location from which to find object to which attribute is attached
1541!  obj_name 	 - Object name either relative to loc_id, absolute from the file’s root group, or '.' (a dot)
1542!  attr_name 	 - Attribute name
1543!
1544! OUTPUTS
1545!  attr_id 	 - attribute identifier
1546!  hdferr 	 - Returns 0 if successful and -1 if fails
1547! OPTIONAL PARAMETERS
1548!  aapl_id 	 - Attribute access property list (Currently unused; should be passed in as H5P_DEFAULT.)
1549!  lapl_id 	 - Link access property list identifier
1550!
1551! AUTHOR
1552!  M. Scot Breitenfeld
1553!  February, 2008
1554! SOURCE
1555  SUBROUTINE h5aopen_by_name_f(loc_id, obj_name, attr_name, attr_id, hdferr, aapl_id, lapl_id)
1556    IMPLICIT NONE
1557    INTEGER(HID_T), INTENT(IN) :: loc_id    ! Location identifier
1558    CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Object name either relative to loc_id,
1559                                             ! absolute from the file’s root group, or '.'
1560    CHARACTER(LEN=*), INTENT(IN) :: attr_name ! Attribute name
1561    INTEGER(HID_T), INTENT(OUT) :: attr_id ! Attribute identifier
1562    INTEGER, INTENT(OUT) :: hdferr         ! Error code:
1563                                           ! 0 on success and -1 on failure
1564    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: aapl_id ! Attribute access property list
1565                                                    ! (Currently unused; should be passed in as H5P_DEFAULT_F)
1566    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
1567!*****
1568    INTEGER(HID_T) :: aapl_id_default
1569    INTEGER(HID_T) :: lapl_id_default
1570
1571    INTEGER(SIZE_T) :: obj_namelen
1572    INTEGER(SIZE_T) :: attr_namelen
1573
1574    INTERFACE
1575       INTEGER FUNCTION h5aopen_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, &
1576            aapl_id_default, lapl_id_default, attr_id)
1577         USE H5GLOBAL
1578         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1579         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5AOPEN_BY_NAME_C'::h5aopen_by_name_c
1580         !DEC$ENDIF
1581         !DEC$ATTRIBUTES reference :: obj_name, attr_name
1582         INTEGER(HID_T), INTENT(IN) :: loc_id
1583         CHARACTER(LEN=*), INTENT(IN) :: obj_name
1584         INTEGER(SIZE_T), INTENT(IN) :: obj_namelen
1585         CHARACTER(LEN=*), INTENT(IN) :: attr_name
1586         INTEGER(SIZE_T), INTENT(IN) :: attr_namelen
1587         INTEGER(HID_T) :: aapl_id_default
1588         INTEGER(HID_T) :: lapl_id_default
1589         INTEGER(HID_T), INTENT(OUT) :: attr_id
1590       END FUNCTION h5aopen_by_name_c
1591    END INTERFACE
1592
1593    attr_namelen = LEN(attr_name)
1594    obj_namelen = LEN(obj_name)
1595
1596    aapl_id_default = H5P_DEFAULT_F
1597    lapl_id_default = H5P_DEFAULT_F
1598    IF(PRESENT(aapl_id)) aapl_id_default = aapl_id
1599    IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
1600
1601    hdferr = h5aopen_by_name_c(loc_id, obj_name, obj_namelen, attr_name, attr_namelen, &
1602         aapl_id_default, lapl_id_default, attr_id)
1603
1604  END SUBROUTINE h5aopen_by_name_f
1605
1606!
1607!****s* H5A/h5arename_f
1608!
1609! NAME
1610!  h5arename_f
1611!
1612! PURPOSE
1613!  Renames an attribute
1614!
1615! INPUTS
1616!  loc_id 	 - Location or object identifier; may be dataset or group
1617!  old_attr_name - Prior attribute name
1618!  new_attr_name - New attribute name
1619!
1620! OUTPUTS
1621!  hdferr 	 - Returns 0 if successful and -1 if fails
1622!
1623! AUTHOR
1624!  M. Scot Breitenfeld
1625!  January, 2008
1626!
1627! HISTORY
1628!  N/A
1629!
1630!
1631
1632! SOURCE
1633  SUBROUTINE h5arename_f(loc_id, old_attr_name, new_attr_name, hdferr)
1634    IMPLICIT NONE
1635    INTEGER(HID_T), INTENT(IN) :: loc_id    ! Object identifier
1636    CHARACTER(LEN=*), INTENT(IN) :: old_attr_name ! Prior attribute name
1637    CHARACTER(LEN=*), INTENT(IN) :: new_attr_name ! New attribute name
1638    INTEGER, INTENT(OUT) :: hdferr       ! Error code:
1639                                         ! 0 on success and -1 on failure
1640!*****
1641    INTEGER(SIZE_T) :: old_attr_namelen
1642    INTEGER(SIZE_T) :: new_attr_namelen
1643
1644    INTERFACE
1645       INTEGER FUNCTION h5arename_c(loc_id, &
1646            old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen)
1647         USE H5GLOBAL
1648         !DEC$IF DEFINED(HDF5F90_WINDOWS)
1649         !DEC$ATTRIBUTES C,reference,decorate,alias:'H5ARENAME_C'::h5arename_c
1650         !DEC$ENDIF
1651         !DEC$ATTRIBUTES reference :: old_attr_name, new_attr_name
1652         INTEGER(HID_T), INTENT(IN) :: loc_id
1653         CHARACTER(LEN=*), INTENT(IN) :: old_attr_name
1654         INTEGER(SIZE_T) :: old_attr_namelen
1655         CHARACTER(LEN=*), INTENT(IN) :: new_attr_name
1656         INTEGER(SIZE_T) :: new_attr_namelen
1657
1658       END FUNCTION h5arename_c
1659    END INTERFACE
1660
1661    old_attr_namelen = LEN(old_attr_name)
1662    new_attr_namelen = LEN(new_attr_name)
1663
1664    hdferr = h5arename_c(loc_id, &
1665         old_attr_name, old_attr_namelen, new_attr_name, new_attr_namelen)
1666
1667  END SUBROUTINE h5arename_f
1668
1669END MODULE H5A
1670
1671
1672