summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Iff.f90
blob: 690d9fdb59c76a2a9be5d95212d02b80e88041c5 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
!
! This file contains FORTRAN90 interfaces for H5I functions
!
      MODULE H5I

        USE H5GLOBAL
      
      CONTAINS

!----------------------------------------------------------------------
! Name:		h5iget_type_f 
!
! Purpose:	Retrieves the type of an object.  	
!
! Inputs: 	obj_id		- object identifier 
! Outputs:  
!		type		- type of the object, possible values:   
!				  H5I_FILE_F
!				  H5I_GROUP_F
!				  H5I_DATATYPE_F
!				  H5I_DATASPACE_F
!				  H5I_DATASET_F
!				  H5I_ATTR_F
!				  H5I_BADID_F
!		hdferr:		- error code		
!				 	Success:  0
!				 	Failure: -1   
! Optional parameters:
!				NONE
!
! Programmer:	Elena Pourmal
!		August 12, 1999	
!
! Modifications: 	Explicit Fortran interfaces were added for 
!			called C functions (it is needed for Windows
!			port).  March 5, 2001 
!
! Comment:		
!----------------------------------------------------------------------
          SUBROUTINE h5iget_type_f(obj_id, type, hdferr) 
!
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5iget_type_f
!DEC$endif
!
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: obj_id  !Object identifier 
            INTEGER, INTENT(OUT) :: type !type of an object. 
                                         !possible values are:
                                         !H5I_FILE_F
                                         !H5I_GROUP_F
                                         !H5I_DATATYPE_F
                                         !H5I_DATASPACE_F
                                         !H5I_DATASET_F
                                         !H5I_ATTR_F
                                         !H5I_BADID_F
            INTEGER, INTENT(OUT) :: hdferr  ! Error code

!            INTEGER, EXTERNAL :: h5iget_type_c
!  Interface is needed for MS FORTRAN
!
            INTERFACE
              INTEGER FUNCTION h5iget_type_c(obj_id, type)
              USE H5GLOBAL
              !DEC$ IF DEFINED(HDF5F90_WINDOWS)
              !MS$ATTRIBUTES C,reference,alias:'_H5IGET_TYPE_C':: h5iget_type_c
              !DEC$ ENDIF
              INTEGER(HID_T), INTENT(IN) :: obj_id 
              INTEGER, INTENT(OUT) :: type
              END FUNCTION h5iget_type_c
            END INTERFACE
            hdferr = h5iget_type_c(obj_id, type)
          END SUBROUTINE h5iget_type_f
!----------------------------------------------------------------------
! Name:		h5iget_name_f 
!
! Purpose: 	Gets a name of an object specified by its idetifier.  
!
! Inputs:  
!		obj_id		- attribute identifier
!		buf_size	- size of a buffer to read name in
! Outputs:  
!		buf		- buffer to read name in, name will be truncated if
!                                 buffer is not big enough
!               name_size       - name size
!		hdferr:		- error code		
!				 	Success:  0
!				 	Failure: -1   
! Optional parameters:
!				NONE			
!
! Programmer:	Elena Pourmal
!		March 12, 2003
!
! Modifications: 	
!
!----------------------------------------------------------------------


          SUBROUTINE h5iget_name_f(obj_id, buf, buf_size, name_size, hdferr) 
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5iget_name_f
!DEC$endif
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: obj_id     ! Object identifier 
            INTEGER(SIZE_T), INTENT(IN) :: buf_size  ! Buffer size 
            CHARACTER(LEN=*), INTENT(OUT) :: buf   ! Buffer to hold object name
            INTEGER(SIZE_T), INTENT(OUT) :: name_size ! Actual name size
            INTEGER, INTENT(OUT) :: hdferr         ! Error code:
                                                   ! 0 if successful,
                                                   ! -1 if fail
!            INTEGER, EXTERNAL :: h5iget_name_c
!  MS FORTRAN needs explicit interface for C functions called here.
!
            INTERFACE
              INTEGER FUNCTION h5iget_name_c(obj_id, buf, buf_size, name_size)
              USE H5GLOBAL
              !DEC$ IF DEFINED(HDF5F90_WINDOWS)
              !MS$ATTRIBUTES C,reference,alias:'_H5IGET_NAME_C'::h5iget_name_c
              !DEC$ ENDIF
              !DEC$ATTRIBUTES reference :: buf
              INTEGER(HID_T), INTENT(IN) :: obj_id
              CHARACTER(LEN=*), INTENT(OUT) :: buf
              INTEGER(SIZE_T), INTENT(IN) :: buf_size
              INTEGER(SIZE_T), INTENT(OUT) :: name_size
              END FUNCTION h5iget_name_c
            END INTERFACE

            hdferr = h5iget_name_c(obj_id, buf, buf_size, name_size)
          END SUBROUTINE h5iget_name_f


      END MODULE H5I