source: XIOS/trunk/src/interface/fortran_attr/iinterpolate_axis_attr.F90 @ 891

Last change on this file since 891 was 891, checked in by mhnguyen, 8 years ago

Adding Fortran interface for reduce_axis_to_scalar

Test
+) On Curie
+) Only compilation

File size: 6.8 KB
RevLine 
[786]1! * ************************************************************************** *
2! *               Interface auto generated - do not modify                     *
3! * ************************************************************************** *
4#include "xios_fortran_prefix.hpp"
5
6MODULE iinterpolate_axis_attr
7  USE, INTRINSIC :: ISO_C_BINDING
8  USE iinterpolate_axis
9  USE interpolate_axis_interface_attr
10
11CONTAINS
12
13  SUBROUTINE xios(set_interpolate_axis_attr)  &
[891]14    ( interpolate_axis_id, coordinate, order, type )
[786]15
16    IMPLICIT NONE
17      TYPE(txios(interpolate_axis))  :: interpolate_axis_hdl
18      CHARACTER(LEN=*), INTENT(IN) ::interpolate_axis_id
[891]19      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: coordinate
[786]20      INTEGER  , OPTIONAL, INTENT(IN) :: order
21      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
22
23      CALL xios(get_interpolate_axis_handle)(interpolate_axis_id,interpolate_axis_hdl)
24      CALL xios(set_interpolate_axis_attr_hdl_)   &
[891]25      ( interpolate_axis_hdl, coordinate, order, type )
[786]26
27  END SUBROUTINE xios(set_interpolate_axis_attr)
28
29  SUBROUTINE xios(set_interpolate_axis_attr_hdl)  &
[891]30    ( interpolate_axis_hdl, coordinate, order, type )
[786]31
32    IMPLICIT NONE
33      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]34      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: coordinate
[786]35      INTEGER  , OPTIONAL, INTENT(IN) :: order
36      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
37
38      CALL xios(set_interpolate_axis_attr_hdl_)  &
[891]39      ( interpolate_axis_hdl, coordinate, order, type )
[786]40
41  END SUBROUTINE xios(set_interpolate_axis_attr_hdl)
42
43  SUBROUTINE xios(set_interpolate_axis_attr_hdl_)   &
[891]44    ( interpolate_axis_hdl, coordinate_, order_, type_ )
[786]45
46    IMPLICIT NONE
47      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]48      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: coordinate_
[786]49      INTEGER  , OPTIONAL, INTENT(IN) :: order_
50      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_
51
[891]52      IF (PRESENT(coordinate_)) THEN
53        CALL cxios_set_interpolate_axis_coordinate(interpolate_axis_hdl%daddr, coordinate_, len(coordinate_))
54      ENDIF
55
[786]56      IF (PRESENT(order_)) THEN
57        CALL cxios_set_interpolate_axis_order(interpolate_axis_hdl%daddr, order_)
58      ENDIF
59
60      IF (PRESENT(type_)) THEN
61        CALL cxios_set_interpolate_axis_type(interpolate_axis_hdl%daddr, type_, len(type_))
62      ENDIF
63
64  END SUBROUTINE xios(set_interpolate_axis_attr_hdl_)
65
66  SUBROUTINE xios(get_interpolate_axis_attr)  &
[891]67    ( interpolate_axis_id, coordinate, order, type )
[786]68
69    IMPLICIT NONE
70      TYPE(txios(interpolate_axis))  :: interpolate_axis_hdl
71      CHARACTER(LEN=*), INTENT(IN) ::interpolate_axis_id
[891]72      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: coordinate
[786]73      INTEGER  , OPTIONAL, INTENT(OUT) :: order
74      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
75
76      CALL xios(get_interpolate_axis_handle)(interpolate_axis_id,interpolate_axis_hdl)
77      CALL xios(get_interpolate_axis_attr_hdl_)   &
[891]78      ( interpolate_axis_hdl, coordinate, order, type )
[786]79
80  END SUBROUTINE xios(get_interpolate_axis_attr)
81
82  SUBROUTINE xios(get_interpolate_axis_attr_hdl)  &
[891]83    ( interpolate_axis_hdl, coordinate, order, type )
[786]84
85    IMPLICIT NONE
86      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]87      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: coordinate
[786]88      INTEGER  , OPTIONAL, INTENT(OUT) :: order
89      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
90
91      CALL xios(get_interpolate_axis_attr_hdl_)  &
[891]92      ( interpolate_axis_hdl, coordinate, order, type )
[786]93
94  END SUBROUTINE xios(get_interpolate_axis_attr_hdl)
95
96  SUBROUTINE xios(get_interpolate_axis_attr_hdl_)   &
[891]97    ( interpolate_axis_hdl, coordinate_, order_, type_ )
[786]98
99    IMPLICIT NONE
100      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]101      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: coordinate_
[786]102      INTEGER  , OPTIONAL, INTENT(OUT) :: order_
103      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_
104
[891]105      IF (PRESENT(coordinate_)) THEN
106        CALL cxios_get_interpolate_axis_coordinate(interpolate_axis_hdl%daddr, coordinate_, len(coordinate_))
107      ENDIF
108
[786]109      IF (PRESENT(order_)) THEN
110        CALL cxios_get_interpolate_axis_order(interpolate_axis_hdl%daddr, order_)
111      ENDIF
112
113      IF (PRESENT(type_)) THEN
114        CALL cxios_get_interpolate_axis_type(interpolate_axis_hdl%daddr, type_, len(type_))
115      ENDIF
116
117  END SUBROUTINE xios(get_interpolate_axis_attr_hdl_)
118
119  SUBROUTINE xios(is_defined_interpolate_axis_attr)  &
[891]120    ( interpolate_axis_id, coordinate, order, type )
[786]121
122    IMPLICIT NONE
123      TYPE(txios(interpolate_axis))  :: interpolate_axis_hdl
124      CHARACTER(LEN=*), INTENT(IN) ::interpolate_axis_id
[891]125      LOGICAL, OPTIONAL, INTENT(OUT) :: coordinate
126      LOGICAL(KIND=C_BOOL) :: coordinate_tmp
[786]127      LOGICAL, OPTIONAL, INTENT(OUT) :: order
128      LOGICAL(KIND=C_BOOL) :: order_tmp
129      LOGICAL, OPTIONAL, INTENT(OUT) :: type
130      LOGICAL(KIND=C_BOOL) :: type_tmp
131
132      CALL xios(get_interpolate_axis_handle)(interpolate_axis_id,interpolate_axis_hdl)
133      CALL xios(is_defined_interpolate_axis_attr_hdl_)   &
[891]134      ( interpolate_axis_hdl, coordinate, order, type )
[786]135
136  END SUBROUTINE xios(is_defined_interpolate_axis_attr)
137
138  SUBROUTINE xios(is_defined_interpolate_axis_attr_hdl)  &
[891]139    ( interpolate_axis_hdl, coordinate, order, type )
[786]140
141    IMPLICIT NONE
142      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]143      LOGICAL, OPTIONAL, INTENT(OUT) :: coordinate
144      LOGICAL(KIND=C_BOOL) :: coordinate_tmp
[786]145      LOGICAL, OPTIONAL, INTENT(OUT) :: order
146      LOGICAL(KIND=C_BOOL) :: order_tmp
147      LOGICAL, OPTIONAL, INTENT(OUT) :: type
148      LOGICAL(KIND=C_BOOL) :: type_tmp
149
150      CALL xios(is_defined_interpolate_axis_attr_hdl_)  &
[891]151      ( interpolate_axis_hdl, coordinate, order, type )
[786]152
153  END SUBROUTINE xios(is_defined_interpolate_axis_attr_hdl)
154
155  SUBROUTINE xios(is_defined_interpolate_axis_attr_hdl_)   &
[891]156    ( interpolate_axis_hdl, coordinate_, order_, type_ )
[786]157
158    IMPLICIT NONE
159      TYPE(txios(interpolate_axis)) , INTENT(IN) :: interpolate_axis_hdl
[891]160      LOGICAL, OPTIONAL, INTENT(OUT) :: coordinate_
161      LOGICAL(KIND=C_BOOL) :: coordinate__tmp
[786]162      LOGICAL, OPTIONAL, INTENT(OUT) :: order_
163      LOGICAL(KIND=C_BOOL) :: order__tmp
164      LOGICAL, OPTIONAL, INTENT(OUT) :: type_
165      LOGICAL(KIND=C_BOOL) :: type__tmp
166
[891]167      IF (PRESENT(coordinate_)) THEN
168        coordinate__tmp = cxios_is_defined_interpolate_axis_coordinate(interpolate_axis_hdl%daddr)
169        coordinate_ = coordinate__tmp
170      ENDIF
171
[786]172      IF (PRESENT(order_)) THEN
173        order__tmp = cxios_is_defined_interpolate_axis_order(interpolate_axis_hdl%daddr)
174        order_ = order__tmp
175      ENDIF
176
177      IF (PRESENT(type_)) THEN
178        type__tmp = cxios_is_defined_interpolate_axis_type(interpolate_axis_hdl%daddr)
179        type_ = type__tmp
180      ENDIF
181
182  END SUBROUTINE xios(is_defined_interpolate_axis_attr_hdl_)
183
184END MODULE iinterpolate_axis_attr
Note: See TracBrowser for help on using the repository browser.