source: XIOS/dev/XIOS_DEV_CMIP6/src/interface/fortran_attr/iinterpolate_domain_attr.F90 @ 1567

Last change on this file since 1567 was 1492, checked in by oabramkina, 6 years ago

Updating fortran interface for attributes that have been recently introduced and the following filters:

duplicate_scalar_to_axis
reduce_axis_to_axis
reduce_scalar_to_scalar
reorder_domain
temporal_splitting.

File size: 16.2 KB
RevLine 
[786]1! * ************************************************************************** *
2! *               Interface auto generated - do not modify                     *
3! * ************************************************************************** *
4#include "xios_fortran_prefix.hpp"
5
6MODULE iinterpolate_domain_attr
7  USE, INTRINSIC :: ISO_C_BINDING
8  USE iinterpolate_domain
9  USE interpolate_domain_interface_attr
10
11CONTAINS
12
13  SUBROUTINE xios(set_interpolate_domain_attr)  &
[1492]14    ( interpolate_domain_id, detect_missing_value, mode, order, quantity, read_write_convention  &
15    , renormalize, weight_filename, write_weight )
[786]16
17    IMPLICIT NONE
18      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
19      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
[1492]20      LOGICAL  , OPTIONAL, INTENT(IN) :: detect_missing_value
21      LOGICAL (KIND=C_BOOL) :: detect_missing_value_tmp
[1021]22      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode
[786]23      INTEGER  , OPTIONAL, INTENT(IN) :: order
[1201]24      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity
25      LOGICAL (KIND=C_BOOL) :: quantity_tmp
[1492]26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: read_write_convention
[891]27      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize
28      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]29      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename
30      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight
31      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]32
[966]33      CALL xios(get_interpolate_domain_handle) &
34      (interpolate_domain_id,interpolate_domain_hdl)
[786]35      CALL xios(set_interpolate_domain_attr_hdl_)   &
[1492]36      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
37      , renormalize, weight_filename, write_weight )
[786]38
39  END SUBROUTINE xios(set_interpolate_domain_attr)
40
41  SUBROUTINE xios(set_interpolate_domain_attr_hdl)  &
[1492]42    ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
43    , renormalize, weight_filename, write_weight )
[786]44
45    IMPLICIT NONE
46      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]47      LOGICAL  , OPTIONAL, INTENT(IN) :: detect_missing_value
48      LOGICAL (KIND=C_BOOL) :: detect_missing_value_tmp
[1021]49      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode
[786]50      INTEGER  , OPTIONAL, INTENT(IN) :: order
[1201]51      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity
52      LOGICAL (KIND=C_BOOL) :: quantity_tmp
[1492]53      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: read_write_convention
[891]54      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize
55      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]56      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename
57      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight
58      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]59
60      CALL xios(set_interpolate_domain_attr_hdl_)  &
[1492]61      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
62      , renormalize, weight_filename, write_weight )
[786]63
64  END SUBROUTINE xios(set_interpolate_domain_attr_hdl)
65
66  SUBROUTINE xios(set_interpolate_domain_attr_hdl_)   &
[1492]67    ( interpolate_domain_hdl, detect_missing_value_, mode_, order_, quantity_, read_write_convention_  &
68    , renormalize_, weight_filename_, write_weight_ )
[786]69
70    IMPLICIT NONE
71      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]72      LOGICAL  , OPTIONAL, INTENT(IN) :: detect_missing_value_
73      LOGICAL (KIND=C_BOOL) :: detect_missing_value__tmp
[1021]74      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode_
[786]75      INTEGER  , OPTIONAL, INTENT(IN) :: order_
[1201]76      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity_
77      LOGICAL (KIND=C_BOOL) :: quantity__tmp
[1492]78      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: read_write_convention_
[891]79      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize_
80      LOGICAL (KIND=C_BOOL) :: renormalize__tmp
[1021]81      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename_
82      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight_
83      LOGICAL (KIND=C_BOOL) :: write_weight__tmp
[786]84
[1492]85      IF (PRESENT(detect_missing_value_)) THEN
86        detect_missing_value__tmp = detect_missing_value_
87        CALL cxios_set_interpolate_domain_detect_missing_value &
88      (interpolate_domain_hdl%daddr, detect_missing_value__tmp)
89      ENDIF
90
[1021]91      IF (PRESENT(mode_)) THEN
92        CALL cxios_set_interpolate_domain_mode &
93      (interpolate_domain_hdl%daddr, mode_, len(mode_))
94      ENDIF
95
[786]96      IF (PRESENT(order_)) THEN
[966]97        CALL cxios_set_interpolate_domain_order &
98      (interpolate_domain_hdl%daddr, order_)
[786]99      ENDIF
100
[1201]101      IF (PRESENT(quantity_)) THEN
102        quantity__tmp = quantity_
103        CALL cxios_set_interpolate_domain_quantity &
104      (interpolate_domain_hdl%daddr, quantity__tmp)
105      ENDIF
106
[1492]107      IF (PRESENT(read_write_convention_)) THEN
108        CALL cxios_set_interpolate_domain_read_write_convention &
109      (interpolate_domain_hdl%daddr, read_write_convention_, len(read_write_convention_))
110      ENDIF
111
[891]112      IF (PRESENT(renormalize_)) THEN
113        renormalize__tmp = renormalize_
[966]114        CALL cxios_set_interpolate_domain_renormalize &
115      (interpolate_domain_hdl%daddr, renormalize__tmp)
[891]116      ENDIF
117
[1021]118      IF (PRESENT(weight_filename_)) THEN
119        CALL cxios_set_interpolate_domain_weight_filename &
120      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_))
121      ENDIF
122
123      IF (PRESENT(write_weight_)) THEN
124        write_weight__tmp = write_weight_
125        CALL cxios_set_interpolate_domain_write_weight &
126      (interpolate_domain_hdl%daddr, write_weight__tmp)
127      ENDIF
128
[786]129  END SUBROUTINE xios(set_interpolate_domain_attr_hdl_)
130
131  SUBROUTINE xios(get_interpolate_domain_attr)  &
[1492]132    ( interpolate_domain_id, detect_missing_value, mode, order, quantity, read_write_convention  &
133    , renormalize, weight_filename, write_weight )
[786]134
135    IMPLICIT NONE
136      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
137      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
[1492]138      LOGICAL  , OPTIONAL, INTENT(OUT) :: detect_missing_value
139      LOGICAL (KIND=C_BOOL) :: detect_missing_value_tmp
[1021]140      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode
[786]141      INTEGER  , OPTIONAL, INTENT(OUT) :: order
[1201]142      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity
143      LOGICAL (KIND=C_BOOL) :: quantity_tmp
[1492]144      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: read_write_convention
[891]145      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize
146      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]147      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename
148      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight
149      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]150
[966]151      CALL xios(get_interpolate_domain_handle) &
152      (interpolate_domain_id,interpolate_domain_hdl)
[786]153      CALL xios(get_interpolate_domain_attr_hdl_)   &
[1492]154      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
155      , renormalize, weight_filename, write_weight )
[786]156
157  END SUBROUTINE xios(get_interpolate_domain_attr)
158
159  SUBROUTINE xios(get_interpolate_domain_attr_hdl)  &
[1492]160    ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
161    , renormalize, weight_filename, write_weight )
[786]162
163    IMPLICIT NONE
164      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]165      LOGICAL  , OPTIONAL, INTENT(OUT) :: detect_missing_value
166      LOGICAL (KIND=C_BOOL) :: detect_missing_value_tmp
[1021]167      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode
[786]168      INTEGER  , OPTIONAL, INTENT(OUT) :: order
[1201]169      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity
170      LOGICAL (KIND=C_BOOL) :: quantity_tmp
[1492]171      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: read_write_convention
[891]172      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize
173      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]174      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename
175      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight
176      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]177
178      CALL xios(get_interpolate_domain_attr_hdl_)  &
[1492]179      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
180      , renormalize, weight_filename, write_weight )
[786]181
182  END SUBROUTINE xios(get_interpolate_domain_attr_hdl)
183
184  SUBROUTINE xios(get_interpolate_domain_attr_hdl_)   &
[1492]185    ( interpolate_domain_hdl, detect_missing_value_, mode_, order_, quantity_, read_write_convention_  &
186    , renormalize_, weight_filename_, write_weight_ )
[786]187
188    IMPLICIT NONE
189      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]190      LOGICAL  , OPTIONAL, INTENT(OUT) :: detect_missing_value_
191      LOGICAL (KIND=C_BOOL) :: detect_missing_value__tmp
[1021]192      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode_
[786]193      INTEGER  , OPTIONAL, INTENT(OUT) :: order_
[1201]194      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity_
195      LOGICAL (KIND=C_BOOL) :: quantity__tmp
[1492]196      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: read_write_convention_
[891]197      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize_
198      LOGICAL (KIND=C_BOOL) :: renormalize__tmp
[1021]199      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename_
200      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight_
201      LOGICAL (KIND=C_BOOL) :: write_weight__tmp
[786]202
[1492]203      IF (PRESENT(detect_missing_value_)) THEN
204        CALL cxios_get_interpolate_domain_detect_missing_value &
205      (interpolate_domain_hdl%daddr, detect_missing_value__tmp)
206        detect_missing_value_ = detect_missing_value__tmp
207      ENDIF
208
[1021]209      IF (PRESENT(mode_)) THEN
210        CALL cxios_get_interpolate_domain_mode &
211      (interpolate_domain_hdl%daddr, mode_, len(mode_))
212      ENDIF
213
[786]214      IF (PRESENT(order_)) THEN
[966]215        CALL cxios_get_interpolate_domain_order &
216      (interpolate_domain_hdl%daddr, order_)
[786]217      ENDIF
218
[1201]219      IF (PRESENT(quantity_)) THEN
220        CALL cxios_get_interpolate_domain_quantity &
221      (interpolate_domain_hdl%daddr, quantity__tmp)
222        quantity_ = quantity__tmp
223      ENDIF
224
[1492]225      IF (PRESENT(read_write_convention_)) THEN
226        CALL cxios_get_interpolate_domain_read_write_convention &
227      (interpolate_domain_hdl%daddr, read_write_convention_, len(read_write_convention_))
228      ENDIF
229
[891]230      IF (PRESENT(renormalize_)) THEN
[966]231        CALL cxios_get_interpolate_domain_renormalize &
232      (interpolate_domain_hdl%daddr, renormalize__tmp)
[891]233        renormalize_ = renormalize__tmp
234      ENDIF
235
[1021]236      IF (PRESENT(weight_filename_)) THEN
237        CALL cxios_get_interpolate_domain_weight_filename &
238      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_))
239      ENDIF
240
241      IF (PRESENT(write_weight_)) THEN
242        CALL cxios_get_interpolate_domain_write_weight &
243      (interpolate_domain_hdl%daddr, write_weight__tmp)
244        write_weight_ = write_weight__tmp
245      ENDIF
246
[786]247  END SUBROUTINE xios(get_interpolate_domain_attr_hdl_)
248
249  SUBROUTINE xios(is_defined_interpolate_domain_attr)  &
[1492]250    ( interpolate_domain_id, detect_missing_value, mode, order, quantity, read_write_convention  &
251    , renormalize, weight_filename, write_weight )
[786]252
253    IMPLICIT NONE
254      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
255      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
[1492]256      LOGICAL, OPTIONAL, INTENT(OUT) :: detect_missing_value
257      LOGICAL(KIND=C_BOOL) :: detect_missing_value_tmp
[1021]258      LOGICAL, OPTIONAL, INTENT(OUT) :: mode
259      LOGICAL(KIND=C_BOOL) :: mode_tmp
[786]260      LOGICAL, OPTIONAL, INTENT(OUT) :: order
261      LOGICAL(KIND=C_BOOL) :: order_tmp
[1201]262      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity
263      LOGICAL(KIND=C_BOOL) :: quantity_tmp
[1492]264      LOGICAL, OPTIONAL, INTENT(OUT) :: read_write_convention
265      LOGICAL(KIND=C_BOOL) :: read_write_convention_tmp
[891]266      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize
267      LOGICAL(KIND=C_BOOL) :: renormalize_tmp
[1021]268      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename
269      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp
270      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight
271      LOGICAL(KIND=C_BOOL) :: write_weight_tmp
[786]272
[966]273      CALL xios(get_interpolate_domain_handle) &
274      (interpolate_domain_id,interpolate_domain_hdl)
[786]275      CALL xios(is_defined_interpolate_domain_attr_hdl_)   &
[1492]276      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
277      , renormalize, weight_filename, write_weight )
[786]278
279  END SUBROUTINE xios(is_defined_interpolate_domain_attr)
280
281  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)  &
[1492]282    ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
283    , renormalize, weight_filename, write_weight )
[786]284
285    IMPLICIT NONE
286      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]287      LOGICAL, OPTIONAL, INTENT(OUT) :: detect_missing_value
288      LOGICAL(KIND=C_BOOL) :: detect_missing_value_tmp
[1021]289      LOGICAL, OPTIONAL, INTENT(OUT) :: mode
290      LOGICAL(KIND=C_BOOL) :: mode_tmp
[786]291      LOGICAL, OPTIONAL, INTENT(OUT) :: order
292      LOGICAL(KIND=C_BOOL) :: order_tmp
[1201]293      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity
294      LOGICAL(KIND=C_BOOL) :: quantity_tmp
[1492]295      LOGICAL, OPTIONAL, INTENT(OUT) :: read_write_convention
296      LOGICAL(KIND=C_BOOL) :: read_write_convention_tmp
[891]297      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize
298      LOGICAL(KIND=C_BOOL) :: renormalize_tmp
[1021]299      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename
300      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp
301      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight
302      LOGICAL(KIND=C_BOOL) :: write_weight_tmp
[786]303
304      CALL xios(is_defined_interpolate_domain_attr_hdl_)  &
[1492]305      ( interpolate_domain_hdl, detect_missing_value, mode, order, quantity, read_write_convention  &
306      , renormalize, weight_filename, write_weight )
[786]307
308  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)
309
310  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)   &
[1492]311    ( interpolate_domain_hdl, detect_missing_value_, mode_, order_, quantity_, read_write_convention_  &
312    , renormalize_, weight_filename_, write_weight_ )
[786]313
314    IMPLICIT NONE
315      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
[1492]316      LOGICAL, OPTIONAL, INTENT(OUT) :: detect_missing_value_
317      LOGICAL(KIND=C_BOOL) :: detect_missing_value__tmp
[1021]318      LOGICAL, OPTIONAL, INTENT(OUT) :: mode_
319      LOGICAL(KIND=C_BOOL) :: mode__tmp
[786]320      LOGICAL, OPTIONAL, INTENT(OUT) :: order_
321      LOGICAL(KIND=C_BOOL) :: order__tmp
[1201]322      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity_
323      LOGICAL(KIND=C_BOOL) :: quantity__tmp
[1492]324      LOGICAL, OPTIONAL, INTENT(OUT) :: read_write_convention_
325      LOGICAL(KIND=C_BOOL) :: read_write_convention__tmp
[891]326      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize_
327      LOGICAL(KIND=C_BOOL) :: renormalize__tmp
[1021]328      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename_
329      LOGICAL(KIND=C_BOOL) :: weight_filename__tmp
330      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight_
331      LOGICAL(KIND=C_BOOL) :: write_weight__tmp
[786]332
[1492]333      IF (PRESENT(detect_missing_value_)) THEN
334        detect_missing_value__tmp = cxios_is_defined_interpolate_domain_detect_missing_value &
335      (interpolate_domain_hdl%daddr)
336        detect_missing_value_ = detect_missing_value__tmp
337      ENDIF
338
[1021]339      IF (PRESENT(mode_)) THEN
340        mode__tmp = cxios_is_defined_interpolate_domain_mode &
341      (interpolate_domain_hdl%daddr)
342        mode_ = mode__tmp
343      ENDIF
344
[786]345      IF (PRESENT(order_)) THEN
[966]346        order__tmp = cxios_is_defined_interpolate_domain_order &
347      (interpolate_domain_hdl%daddr)
[786]348        order_ = order__tmp
349      ENDIF
350
[1201]351      IF (PRESENT(quantity_)) THEN
352        quantity__tmp = cxios_is_defined_interpolate_domain_quantity &
353      (interpolate_domain_hdl%daddr)
354        quantity_ = quantity__tmp
355      ENDIF
356
[1492]357      IF (PRESENT(read_write_convention_)) THEN
358        read_write_convention__tmp = cxios_is_defined_interpolate_domain_read_write_convention &
359      (interpolate_domain_hdl%daddr)
360        read_write_convention_ = read_write_convention__tmp
361      ENDIF
362
[891]363      IF (PRESENT(renormalize_)) THEN
[966]364        renormalize__tmp = cxios_is_defined_interpolate_domain_renormalize &
365      (interpolate_domain_hdl%daddr)
[891]366        renormalize_ = renormalize__tmp
367      ENDIF
368
[1021]369      IF (PRESENT(weight_filename_)) THEN
370        weight_filename__tmp = cxios_is_defined_interpolate_domain_weight_filename &
371      (interpolate_domain_hdl%daddr)
372        weight_filename_ = weight_filename__tmp
373      ENDIF
374
375      IF (PRESENT(write_weight_)) THEN
376        write_weight__tmp = cxios_is_defined_interpolate_domain_write_weight &
377      (interpolate_domain_hdl%daddr)
378        write_weight_ = write_weight__tmp
379      ENDIF
380
[786]381  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)
382
383END MODULE iinterpolate_domain_attr
Note: See TracBrowser for help on using the repository browser.