source: XIOS/dev/dev_olga/src/interface/fortran_attr/iinterpolate_domain_attr.F90 @ 1024

Last change on this file since 1024 was 1021, checked in by oabramkina, 8 years ago

Intermeadiate version for merging with new server functionalities.

File size: 11.8 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)  &
[1021]14    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight )
[786]15
16    IMPLICIT NONE
17      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
18      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
19      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file
[1021]20      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode
[786]21      INTEGER  , OPTIONAL, INTENT(IN) :: order
[891]22      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize
23      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]24      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename
25      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight
26      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]27
[966]28      CALL xios(get_interpolate_domain_handle) &
29      (interpolate_domain_id,interpolate_domain_hdl)
[786]30      CALL xios(set_interpolate_domain_attr_hdl_)   &
[1021]31      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]32
33  END SUBROUTINE xios(set_interpolate_domain_attr)
34
35  SUBROUTINE xios(set_interpolate_domain_attr_hdl)  &
[1021]36    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]37
38    IMPLICIT NONE
39      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
40      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file
[1021]41      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode
[786]42      INTEGER  , OPTIONAL, INTENT(IN) :: order
[891]43      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize
44      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]45      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename
46      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight
47      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]48
49      CALL xios(set_interpolate_domain_attr_hdl_)  &
[1021]50      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]51
52  END SUBROUTINE xios(set_interpolate_domain_attr_hdl)
53
54  SUBROUTINE xios(set_interpolate_domain_attr_hdl_)   &
[1021]55    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  &
56     )
[786]57
58    IMPLICIT NONE
59      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
60      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file_
[1021]61      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode_
[786]62      INTEGER  , OPTIONAL, INTENT(IN) :: order_
[891]63      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize_
64      LOGICAL (KIND=C_BOOL) :: renormalize__tmp
[1021]65      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename_
66      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight_
67      LOGICAL (KIND=C_BOOL) :: write_weight__tmp
[786]68
69      IF (PRESENT(file_)) THEN
[966]70        CALL cxios_set_interpolate_domain_file &
71      (interpolate_domain_hdl%daddr, file_, len(file_))
[786]72      ENDIF
73
[1021]74      IF (PRESENT(mode_)) THEN
75        CALL cxios_set_interpolate_domain_mode &
76      (interpolate_domain_hdl%daddr, mode_, len(mode_))
77      ENDIF
78
[786]79      IF (PRESENT(order_)) THEN
[966]80        CALL cxios_set_interpolate_domain_order &
81      (interpolate_domain_hdl%daddr, order_)
[786]82      ENDIF
83
[891]84      IF (PRESENT(renormalize_)) THEN
85        renormalize__tmp = renormalize_
[966]86        CALL cxios_set_interpolate_domain_renormalize &
87      (interpolate_domain_hdl%daddr, renormalize__tmp)
[891]88      ENDIF
89
[1021]90      IF (PRESENT(weight_filename_)) THEN
91        CALL cxios_set_interpolate_domain_weight_filename &
92      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_))
93      ENDIF
94
95      IF (PRESENT(write_weight_)) THEN
96        write_weight__tmp = write_weight_
97        CALL cxios_set_interpolate_domain_write_weight &
98      (interpolate_domain_hdl%daddr, write_weight__tmp)
99      ENDIF
100
[786]101  END SUBROUTINE xios(set_interpolate_domain_attr_hdl_)
102
103  SUBROUTINE xios(get_interpolate_domain_attr)  &
[1021]104    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight )
[786]105
106    IMPLICIT NONE
107      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
108      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
109      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file
[1021]110      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode
[786]111      INTEGER  , OPTIONAL, INTENT(OUT) :: order
[891]112      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize
113      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]114      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename
115      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight
116      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]117
[966]118      CALL xios(get_interpolate_domain_handle) &
119      (interpolate_domain_id,interpolate_domain_hdl)
[786]120      CALL xios(get_interpolate_domain_attr_hdl_)   &
[1021]121      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]122
123  END SUBROUTINE xios(get_interpolate_domain_attr)
124
125  SUBROUTINE xios(get_interpolate_domain_attr_hdl)  &
[1021]126    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]127
128    IMPLICIT NONE
129      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
130      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file
[1021]131      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode
[786]132      INTEGER  , OPTIONAL, INTENT(OUT) :: order
[891]133      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize
134      LOGICAL (KIND=C_BOOL) :: renormalize_tmp
[1021]135      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename
136      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight
137      LOGICAL (KIND=C_BOOL) :: write_weight_tmp
[786]138
139      CALL xios(get_interpolate_domain_attr_hdl_)  &
[1021]140      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]141
142  END SUBROUTINE xios(get_interpolate_domain_attr_hdl)
143
144  SUBROUTINE xios(get_interpolate_domain_attr_hdl_)   &
[1021]145    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  &
146     )
[786]147
148    IMPLICIT NONE
149      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
150      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file_
[1021]151      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode_
[786]152      INTEGER  , OPTIONAL, INTENT(OUT) :: order_
[891]153      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize_
154      LOGICAL (KIND=C_BOOL) :: renormalize__tmp
[1021]155      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename_
156      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight_
157      LOGICAL (KIND=C_BOOL) :: write_weight__tmp
[786]158
159      IF (PRESENT(file_)) THEN
[966]160        CALL cxios_get_interpolate_domain_file &
161      (interpolate_domain_hdl%daddr, file_, len(file_))
[786]162      ENDIF
163
[1021]164      IF (PRESENT(mode_)) THEN
165        CALL cxios_get_interpolate_domain_mode &
166      (interpolate_domain_hdl%daddr, mode_, len(mode_))
167      ENDIF
168
[786]169      IF (PRESENT(order_)) THEN
[966]170        CALL cxios_get_interpolate_domain_order &
171      (interpolate_domain_hdl%daddr, order_)
[786]172      ENDIF
173
[891]174      IF (PRESENT(renormalize_)) THEN
[966]175        CALL cxios_get_interpolate_domain_renormalize &
176      (interpolate_domain_hdl%daddr, renormalize__tmp)
[891]177        renormalize_ = renormalize__tmp
178      ENDIF
179
[1021]180      IF (PRESENT(weight_filename_)) THEN
181        CALL cxios_get_interpolate_domain_weight_filename &
182      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_))
183      ENDIF
184
185      IF (PRESENT(write_weight_)) THEN
186        CALL cxios_get_interpolate_domain_write_weight &
187      (interpolate_domain_hdl%daddr, write_weight__tmp)
188        write_weight_ = write_weight__tmp
189      ENDIF
190
[786]191  END SUBROUTINE xios(get_interpolate_domain_attr_hdl_)
192
193  SUBROUTINE xios(is_defined_interpolate_domain_attr)  &
[1021]194    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight )
[786]195
196    IMPLICIT NONE
197      TYPE(txios(interpolate_domain))  :: interpolate_domain_hdl
198      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id
199      LOGICAL, OPTIONAL, INTENT(OUT) :: file
200      LOGICAL(KIND=C_BOOL) :: file_tmp
[1021]201      LOGICAL, OPTIONAL, INTENT(OUT) :: mode
202      LOGICAL(KIND=C_BOOL) :: mode_tmp
[786]203      LOGICAL, OPTIONAL, INTENT(OUT) :: order
204      LOGICAL(KIND=C_BOOL) :: order_tmp
[891]205      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize
206      LOGICAL(KIND=C_BOOL) :: renormalize_tmp
[1021]207      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename
208      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp
209      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight
210      LOGICAL(KIND=C_BOOL) :: write_weight_tmp
[786]211
[966]212      CALL xios(get_interpolate_domain_handle) &
213      (interpolate_domain_id,interpolate_domain_hdl)
[786]214      CALL xios(is_defined_interpolate_domain_attr_hdl_)   &
[1021]215      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]216
217  END SUBROUTINE xios(is_defined_interpolate_domain_attr)
218
219  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)  &
[1021]220    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]221
222    IMPLICIT NONE
223      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
224      LOGICAL, OPTIONAL, INTENT(OUT) :: file
225      LOGICAL(KIND=C_BOOL) :: file_tmp
[1021]226      LOGICAL, OPTIONAL, INTENT(OUT) :: mode
227      LOGICAL(KIND=C_BOOL) :: mode_tmp
[786]228      LOGICAL, OPTIONAL, INTENT(OUT) :: order
229      LOGICAL(KIND=C_BOOL) :: order_tmp
[891]230      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize
231      LOGICAL(KIND=C_BOOL) :: renormalize_tmp
[1021]232      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename
233      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp
234      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight
235      LOGICAL(KIND=C_BOOL) :: write_weight_tmp
[786]236
237      CALL xios(is_defined_interpolate_domain_attr_hdl_)  &
[1021]238      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight )
[786]239
240  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)
241
242  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)   &
[1021]243    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  &
244     )
[786]245
246    IMPLICIT NONE
247      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl
248      LOGICAL, OPTIONAL, INTENT(OUT) :: file_
249      LOGICAL(KIND=C_BOOL) :: file__tmp
[1021]250      LOGICAL, OPTIONAL, INTENT(OUT) :: mode_
251      LOGICAL(KIND=C_BOOL) :: mode__tmp
[786]252      LOGICAL, OPTIONAL, INTENT(OUT) :: order_
253      LOGICAL(KIND=C_BOOL) :: order__tmp
[891]254      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize_
255      LOGICAL(KIND=C_BOOL) :: renormalize__tmp
[1021]256      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename_
257      LOGICAL(KIND=C_BOOL) :: weight_filename__tmp
258      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight_
259      LOGICAL(KIND=C_BOOL) :: write_weight__tmp
[786]260
261      IF (PRESENT(file_)) THEN
[966]262        file__tmp = cxios_is_defined_interpolate_domain_file &
263      (interpolate_domain_hdl%daddr)
[786]264        file_ = file__tmp
265      ENDIF
266
[1021]267      IF (PRESENT(mode_)) THEN
268        mode__tmp = cxios_is_defined_interpolate_domain_mode &
269      (interpolate_domain_hdl%daddr)
270        mode_ = mode__tmp
271      ENDIF
272
[786]273      IF (PRESENT(order_)) THEN
[966]274        order__tmp = cxios_is_defined_interpolate_domain_order &
275      (interpolate_domain_hdl%daddr)
[786]276        order_ = order__tmp
277      ENDIF
278
[891]279      IF (PRESENT(renormalize_)) THEN
[966]280        renormalize__tmp = cxios_is_defined_interpolate_domain_renormalize &
281      (interpolate_domain_hdl%daddr)
[891]282        renormalize_ = renormalize__tmp
283      ENDIF
284
[1021]285      IF (PRESENT(weight_filename_)) THEN
286        weight_filename__tmp = cxios_is_defined_interpolate_domain_weight_filename &
287      (interpolate_domain_hdl%daddr)
288        weight_filename_ = weight_filename__tmp
289      ENDIF
290
291      IF (PRESENT(write_weight_)) THEN
292        write_weight__tmp = cxios_is_defined_interpolate_domain_write_weight &
293      (interpolate_domain_hdl%daddr)
294        write_weight_ = write_weight__tmp
295      ENDIF
296
[786]297  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)
298
299END MODULE iinterpolate_domain_attr
Note: See TracBrowser for help on using the repository browser.