summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Rff.f90
blob: 3fd914234a8e070860ae39a1633f3d6f49b2cac2 (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
!
! This file contains Fortran90 interfaces for H5R functions.
! 
      MODULE H5R
        USE H5FORTRAN_TYPES 
        USE H5FORTRAN_FLAGS

        TYPE hobj_ref_t_f
             !INTEGER(KIND=4) ref(2)   could cause trouble on Crays
             CHARACTER ref(8)
        END TYPE 

        TYPE hdset_reg_ref_t_f
             !INTEGER(KIND=4) reg_ref(3)  could cause troubles on Crays
             CHARACTER ref(12)
        END TYPE 

          INTERFACE h5rcreate_f

            MODULE PROCEDURE h5rcreate_object_f
            MODULE PROCEDURE h5rcreate_region_f 

          END INTERFACE 
          
          INTERFACE h5rdereference_f

            MODULE PROCEDURE h5rdereference_object_f
            MODULE PROCEDURE h5rdereference_region_f 

          END INTERFACE 
          
          INTERFACE h5rget_region_f

            MODULE PROCEDURE h5rget_region_region_f 

          END INTERFACE 
          
          INTERFACE h5rget_object_type_f

            MODULE PROCEDURE h5rget_object_type_obj_f

          END INTERFACE 
          

        CONTAINS
          
  
          SUBROUTINE h5rcreate_object_f(loc_id, name, ref, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: loc_id   ! Location identifier 
            CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the object at location specified
                                                   ! by loc_id identifier 
            TYPE(hobj_ref_t_f), INTENT(OUT) :: ref   ! Object reference 
            INTEGER, INTENT(OUT) :: hdferr         ! Error code 

            INTEGER :: namelen                     ! Name length
            INTEGER, EXTERNAL :: h5rcreate_object_c
            namelen = LEN(name)
            hdferr = h5rcreate_object_c(ref, loc_id, name, namelen )

          END SUBROUTINE h5rcreate_object_f
          
          SUBROUTINE h5rcreate_region_f(loc_id, name, space_id, ref, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: loc_id   ! Location identifier 
            CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the dataset at location specified
                                                   ! by loc_id identifier 
            INTEGER(HID_T), INTENT(IN) :: space_id ! Dataset's dataspace identifier 
            TYPE(hdset_reg_ref_t_f), INTENT(OUT) :: ref ! Dataset region reference 
            INTEGER, INTENT(OUT) :: hdferr         ! Error code 

            INTEGER :: namelen                     ! Name length
            INTEGER, EXTERNAL :: h5rcreate_region_c
            namelen = LEN(name)
            hdferr = h5rcreate_region_c(ref, loc_id, name, namelen, space_id )

          END SUBROUTINE h5rcreate_region_f
          
          SUBROUTINE h5rdereference_object_f(dset_id, ref, obj_id, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier 
            TYPE(hobj_ref_t_f), INTENT(IN) :: ref   ! Object reference 
            INTEGER(HID_T), INTENT(OUT) :: obj_id   ! Object identifier 
            INTEGER, INTENT(OUT) :: hdferr         ! Error code 

            INTEGER :: ref_type     ! Reference type 
            INTEGER, EXTERNAL :: h5rdereference_object_c
            ref_type = H5R_OBJECT_F
            hdferr = h5rdereference_object_c(dset_id, ref, obj_id )

          END SUBROUTINE h5rdereference_object_f
          
          SUBROUTINE h5rdereference_region_f(dset_id, ref, obj_id, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier 
            TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref   ! Object reference 
            INTEGER(HID_T), INTENT(OUT) :: obj_id   ! Object identifier 
            INTEGER, INTENT(OUT) :: hdferr          ! Error code 

            INTEGER :: ref_type      ! Reference type 
            INTEGER, EXTERNAL :: h5rdereference_region_c
            ref_type = H5R_DATASET_REGION_F
            hdferr = h5rdereference_region_c(dset_id, ref, obj_id )

          END SUBROUTINE h5rdereference_region_f
          
          
          SUBROUTINE h5rget_region_region_f(dset_id, ref, space_id, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier 
            TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref   ! Dataset region reference 
            INTEGER(HID_T), INTENT(OUT) :: space_id   ! Space identifier 
            INTEGER, INTENT(OUT) :: hdferr          ! Error code 

            INTEGER, EXTERNAL :: h5rget_region_region_c
            hdferr = h5rget_region_region_c(dset_id, ref, space_id )

          END SUBROUTINE h5rget_region_region_f

          SUBROUTINE h5rget_object_type_obj_f(dset_id, ref, obj_type, hdferr) 
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier 
            TYPE(hobj_ref_t_f), INTENT(IN) :: ref   ! Object reference 
            INTEGER, INTENT(OUT) :: obj_type   ! Object type  
                                               !  H5G_UNKNOWN_F     (-1)
                                               !  H5G_LINK_F         0
                                               !  H5G_GROUP_F        1
                                               !  H5G_DATASET_F      2
                                               !  H5G_TYPE_F         3

            INTEGER, INTENT(OUT) :: hdferr          ! Error code 

            INTEGER, EXTERNAL :: h5rget_object_type_obj_c
            hdferr = h5rget_object_type_obj_c(dset_id, ref, obj_type )

          END SUBROUTINE h5rget_object_type_obj_f

      END MODULE H5R