source: XIOS3/trunk/src/interface/fortran_attr/icalendar_wrapper_attr.F90 @ 2622

Last change on this file since 2622 was 2620, checked in by jderouillat, 4 months ago

Modify fortran-C interfaces to manage logical-bool conversion, the optimizations of OneAPI could produce bugs regarding the logical-bool encodings.

File size: 18.5 KB
Line 
1! * ************************************************************************** *
2! *               Interface auto generated - do not modify                     *
3! * ************************************************************************** *
4#include "xios_fortran_prefix.hpp"
5
6MODULE icalendar_wrapper_attr
7  USE, INTRINSIC :: ISO_C_BINDING
8  USE icalendar_wrapper
9  USE calendar_wrapper_interface_attr
10  USE LOGICAL_BOOL_CONVERSION
11
12CONTAINS
13
14  SUBROUTINE xios(set_calendar_wrapper_attr)  &
15    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
16    , month_lengths, start_date, time_origin, timestep, type, year_length )
17
18    IMPLICIT NONE
19      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
20      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
21      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment
22      INTEGER  , OPTIONAL, INTENT(IN) :: day_length
23      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift
24      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift_offset
25      INTEGER  , OPTIONAL, INTENT(IN) :: leap_year_month
26      INTEGER  , OPTIONAL, INTENT(IN) :: month_lengths(:)
27      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: start_date
28      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: time_origin
29      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: timestep
30      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
31      INTEGER  , OPTIONAL, INTENT(IN) :: year_length
32
33      CALL xios(get_calendar_wrapper_handle) &
34      (calendar_wrapper_id,calendar_wrapper_hdl)
35      CALL xios(set_calendar_wrapper_attr_hdl_)   &
36      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
37      , month_lengths, start_date, time_origin, timestep, type, year_length )
38
39  END SUBROUTINE xios(set_calendar_wrapper_attr)
40
41  SUBROUTINE xios(set_calendar_wrapper_attr_hdl)  &
42    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
43    , month_lengths, start_date, time_origin, timestep, type, year_length )
44
45    IMPLICIT NONE
46      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
47      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment
48      INTEGER  , OPTIONAL, INTENT(IN) :: day_length
49      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift
50      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift_offset
51      INTEGER  , OPTIONAL, INTENT(IN) :: leap_year_month
52      INTEGER  , OPTIONAL, INTENT(IN) :: month_lengths(:)
53      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: start_date
54      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: time_origin
55      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: timestep
56      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
57      INTEGER  , OPTIONAL, INTENT(IN) :: year_length
58
59      CALL xios(set_calendar_wrapper_attr_hdl_)  &
60      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
61      , month_lengths, start_date, time_origin, timestep, type, year_length )
62
63  END SUBROUTINE xios(set_calendar_wrapper_attr_hdl)
64
65  SUBROUTINE xios(set_calendar_wrapper_attr_hdl_)   &
66    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
67    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
68
69    IMPLICIT NONE
70      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
71      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment_
72      INTEGER  , OPTIONAL, INTENT(IN) :: day_length_
73      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift_
74      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: leap_year_drift_offset_
75      INTEGER  , OPTIONAL, INTENT(IN) :: leap_year_month_
76      INTEGER  , OPTIONAL, INTENT(IN) :: month_lengths_(:)
77      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: start_date_
78      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: time_origin_
79      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: timestep_
80      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_
81      INTEGER  , OPTIONAL, INTENT(IN) :: year_length_
82
83      IF (PRESENT(comment_)) THEN
84        CALL cxios_set_calendar_wrapper_comment &
85      (calendar_wrapper_hdl%daddr, comment_, len(comment_))
86      ENDIF
87
88      IF (PRESENT(day_length_)) THEN
89        CALL cxios_set_calendar_wrapper_day_length &
90      (calendar_wrapper_hdl%daddr, day_length_)
91      ENDIF
92
93      IF (PRESENT(leap_year_drift_)) THEN
94        CALL cxios_set_calendar_wrapper_leap_year_drift &
95      (calendar_wrapper_hdl%daddr, leap_year_drift_)
96      ENDIF
97
98      IF (PRESENT(leap_year_drift_offset_)) THEN
99        CALL cxios_set_calendar_wrapper_leap_year_drift_offset &
100      (calendar_wrapper_hdl%daddr, leap_year_drift_offset_)
101      ENDIF
102
103      IF (PRESENT(leap_year_month_)) THEN
104        CALL cxios_set_calendar_wrapper_leap_year_month &
105      (calendar_wrapper_hdl%daddr, leap_year_month_)
106      ENDIF
107
108      IF (PRESENT(month_lengths_)) THEN
109        CALL cxios_set_calendar_wrapper_month_lengths &
110      (calendar_wrapper_hdl%daddr, month_lengths_, SHAPE(month_lengths_))
111      ENDIF
112
113      IF (PRESENT(start_date_)) THEN
114        CALL cxios_set_calendar_wrapper_start_date &
115      (calendar_wrapper_hdl%daddr, start_date_, len(start_date_))
116      ENDIF
117
118      IF (PRESENT(time_origin_)) THEN
119        CALL cxios_set_calendar_wrapper_time_origin &
120      (calendar_wrapper_hdl%daddr, time_origin_, len(time_origin_))
121      ENDIF
122
123      IF (PRESENT(timestep_)) THEN
124        CALL cxios_set_calendar_wrapper_timestep &
125      (calendar_wrapper_hdl%daddr, timestep_)
126      ENDIF
127
128      IF (PRESENT(type_)) THEN
129        CALL cxios_set_calendar_wrapper_type &
130      (calendar_wrapper_hdl%daddr, type_, len(type_))
131      ENDIF
132
133      IF (PRESENT(year_length_)) THEN
134        CALL cxios_set_calendar_wrapper_year_length &
135      (calendar_wrapper_hdl%daddr, year_length_)
136      ENDIF
137
138  END SUBROUTINE xios(set_calendar_wrapper_attr_hdl_)
139
140  SUBROUTINE xios(get_calendar_wrapper_attr)  &
141    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
142    , month_lengths, start_date, time_origin, timestep, type, year_length )
143
144    IMPLICIT NONE
145      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
146      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
147      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment
148      INTEGER  , OPTIONAL, INTENT(OUT) :: day_length
149      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift
150      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift_offset
151      INTEGER  , OPTIONAL, INTENT(OUT) :: leap_year_month
152      INTEGER  , OPTIONAL, INTENT(OUT) :: month_lengths(:)
153      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: start_date
154      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: time_origin
155      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: timestep
156      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
157      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length
158
159      CALL xios(get_calendar_wrapper_handle) &
160      (calendar_wrapper_id,calendar_wrapper_hdl)
161      CALL xios(get_calendar_wrapper_attr_hdl_)   &
162      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
163      , month_lengths, start_date, time_origin, timestep, type, year_length )
164
165  END SUBROUTINE xios(get_calendar_wrapper_attr)
166
167  SUBROUTINE xios(get_calendar_wrapper_attr_hdl)  &
168    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
169    , month_lengths, start_date, time_origin, timestep, type, year_length )
170
171    IMPLICIT NONE
172      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
173      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment
174      INTEGER  , OPTIONAL, INTENT(OUT) :: day_length
175      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift
176      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift_offset
177      INTEGER  , OPTIONAL, INTENT(OUT) :: leap_year_month
178      INTEGER  , OPTIONAL, INTENT(OUT) :: month_lengths(:)
179      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: start_date
180      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: time_origin
181      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: timestep
182      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
183      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length
184
185      CALL xios(get_calendar_wrapper_attr_hdl_)  &
186      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
187      , month_lengths, start_date, time_origin, timestep, type, year_length )
188
189  END SUBROUTINE xios(get_calendar_wrapper_attr_hdl)
190
191  SUBROUTINE xios(get_calendar_wrapper_attr_hdl_)   &
192    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
193    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
194
195    IMPLICIT NONE
196      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
197      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment_
198      INTEGER  , OPTIONAL, INTENT(OUT) :: day_length_
199      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift_
200      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: leap_year_drift_offset_
201      INTEGER  , OPTIONAL, INTENT(OUT) :: leap_year_month_
202      INTEGER  , OPTIONAL, INTENT(OUT) :: month_lengths_(:)
203      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: start_date_
204      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: time_origin_
205      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: timestep_
206      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_
207      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length_
208
209      IF (PRESENT(comment_)) THEN
210        CALL cxios_get_calendar_wrapper_comment &
211      (calendar_wrapper_hdl%daddr, comment_, len(comment_))
212      ENDIF
213
214      IF (PRESENT(day_length_)) THEN
215        CALL cxios_get_calendar_wrapper_day_length &
216      (calendar_wrapper_hdl%daddr, day_length_)
217      ENDIF
218
219      IF (PRESENT(leap_year_drift_)) THEN
220        CALL cxios_get_calendar_wrapper_leap_year_drift &
221      (calendar_wrapper_hdl%daddr, leap_year_drift_)
222      ENDIF
223
224      IF (PRESENT(leap_year_drift_offset_)) THEN
225        CALL cxios_get_calendar_wrapper_leap_year_drift_offset &
226      (calendar_wrapper_hdl%daddr, leap_year_drift_offset_)
227      ENDIF
228
229      IF (PRESENT(leap_year_month_)) THEN
230        CALL cxios_get_calendar_wrapper_leap_year_month &
231      (calendar_wrapper_hdl%daddr, leap_year_month_)
232      ENDIF
233
234      IF (PRESENT(month_lengths_)) THEN
235        CALL cxios_get_calendar_wrapper_month_lengths &
236      (calendar_wrapper_hdl%daddr, month_lengths_, SHAPE(month_lengths_))
237      ENDIF
238
239      IF (PRESENT(start_date_)) THEN
240        CALL cxios_get_calendar_wrapper_start_date &
241      (calendar_wrapper_hdl%daddr, start_date_, len(start_date_))
242      ENDIF
243
244      IF (PRESENT(time_origin_)) THEN
245        CALL cxios_get_calendar_wrapper_time_origin &
246      (calendar_wrapper_hdl%daddr, time_origin_, len(time_origin_))
247      ENDIF
248
249      IF (PRESENT(timestep_)) THEN
250        CALL cxios_get_calendar_wrapper_timestep &
251      (calendar_wrapper_hdl%daddr, timestep_)
252      ENDIF
253
254      IF (PRESENT(type_)) THEN
255        CALL cxios_get_calendar_wrapper_type &
256      (calendar_wrapper_hdl%daddr, type_, len(type_))
257      ENDIF
258
259      IF (PRESENT(year_length_)) THEN
260        CALL cxios_get_calendar_wrapper_year_length &
261      (calendar_wrapper_hdl%daddr, year_length_)
262      ENDIF
263
264  END SUBROUTINE xios(get_calendar_wrapper_attr_hdl_)
265
266  SUBROUTINE xios(is_defined_calendar_wrapper_attr)  &
267    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
268    , month_lengths, start_date, time_origin, timestep, type, year_length )
269
270    IMPLICIT NONE
271      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
272      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
273      LOGICAL, OPTIONAL, INTENT(OUT) :: comment
274      LOGICAL(KIND=C_BOOL) :: comment_tmp
275      LOGICAL, OPTIONAL, INTENT(OUT) :: day_length
276      LOGICAL(KIND=C_BOOL) :: day_length_tmp
277      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift
278      LOGICAL(KIND=C_BOOL) :: leap_year_drift_tmp
279      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift_offset
280      LOGICAL(KIND=C_BOOL) :: leap_year_drift_offset_tmp
281      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_month
282      LOGICAL(KIND=C_BOOL) :: leap_year_month_tmp
283      LOGICAL, OPTIONAL, INTENT(OUT) :: month_lengths
284      LOGICAL(KIND=C_BOOL) :: month_lengths_tmp
285      LOGICAL, OPTIONAL, INTENT(OUT) :: start_date
286      LOGICAL(KIND=C_BOOL) :: start_date_tmp
287      LOGICAL, OPTIONAL, INTENT(OUT) :: time_origin
288      LOGICAL(KIND=C_BOOL) :: time_origin_tmp
289      LOGICAL, OPTIONAL, INTENT(OUT) :: timestep
290      LOGICAL(KIND=C_BOOL) :: timestep_tmp
291      LOGICAL, OPTIONAL, INTENT(OUT) :: type
292      LOGICAL(KIND=C_BOOL) :: type_tmp
293      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length
294      LOGICAL(KIND=C_BOOL) :: year_length_tmp
295
296      CALL xios(get_calendar_wrapper_handle) &
297      (calendar_wrapper_id,calendar_wrapper_hdl)
298      CALL xios(is_defined_calendar_wrapper_attr_hdl_)   &
299      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
300      , month_lengths, start_date, time_origin, timestep, type, year_length )
301
302  END SUBROUTINE xios(is_defined_calendar_wrapper_attr)
303
304  SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl)  &
305    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
306    , month_lengths, start_date, time_origin, timestep, type, year_length )
307
308    IMPLICIT NONE
309      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
310      LOGICAL, OPTIONAL, INTENT(OUT) :: comment
311      LOGICAL(KIND=C_BOOL) :: comment_tmp
312      LOGICAL, OPTIONAL, INTENT(OUT) :: day_length
313      LOGICAL(KIND=C_BOOL) :: day_length_tmp
314      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift
315      LOGICAL(KIND=C_BOOL) :: leap_year_drift_tmp
316      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift_offset
317      LOGICAL(KIND=C_BOOL) :: leap_year_drift_offset_tmp
318      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_month
319      LOGICAL(KIND=C_BOOL) :: leap_year_month_tmp
320      LOGICAL, OPTIONAL, INTENT(OUT) :: month_lengths
321      LOGICAL(KIND=C_BOOL) :: month_lengths_tmp
322      LOGICAL, OPTIONAL, INTENT(OUT) :: start_date
323      LOGICAL(KIND=C_BOOL) :: start_date_tmp
324      LOGICAL, OPTIONAL, INTENT(OUT) :: time_origin
325      LOGICAL(KIND=C_BOOL) :: time_origin_tmp
326      LOGICAL, OPTIONAL, INTENT(OUT) :: timestep
327      LOGICAL(KIND=C_BOOL) :: timestep_tmp
328      LOGICAL, OPTIONAL, INTENT(OUT) :: type
329      LOGICAL(KIND=C_BOOL) :: type_tmp
330      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length
331      LOGICAL(KIND=C_BOOL) :: year_length_tmp
332
333      CALL xios(is_defined_calendar_wrapper_attr_hdl_)  &
334      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
335      , month_lengths, start_date, time_origin, timestep, type, year_length )
336
337  END SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl)
338
339  SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl_)   &
340    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
341    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
342
343    IMPLICIT NONE
344      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
345      LOGICAL, OPTIONAL, INTENT(OUT) :: comment_
346      LOGICAL(KIND=C_BOOL) :: comment__tmp
347      LOGICAL, OPTIONAL, INTENT(OUT) :: day_length_
348      LOGICAL(KIND=C_BOOL) :: day_length__tmp
349      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift_
350      LOGICAL(KIND=C_BOOL) :: leap_year_drift__tmp
351      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_drift_offset_
352      LOGICAL(KIND=C_BOOL) :: leap_year_drift_offset__tmp
353      LOGICAL, OPTIONAL, INTENT(OUT) :: leap_year_month_
354      LOGICAL(KIND=C_BOOL) :: leap_year_month__tmp
355      LOGICAL, OPTIONAL, INTENT(OUT) :: month_lengths_
356      LOGICAL(KIND=C_BOOL) :: month_lengths__tmp
357      LOGICAL, OPTIONAL, INTENT(OUT) :: start_date_
358      LOGICAL(KIND=C_BOOL) :: start_date__tmp
359      LOGICAL, OPTIONAL, INTENT(OUT) :: time_origin_
360      LOGICAL(KIND=C_BOOL) :: time_origin__tmp
361      LOGICAL, OPTIONAL, INTENT(OUT) :: timestep_
362      LOGICAL(KIND=C_BOOL) :: timestep__tmp
363      LOGICAL, OPTIONAL, INTENT(OUT) :: type_
364      LOGICAL(KIND=C_BOOL) :: type__tmp
365      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length_
366      LOGICAL(KIND=C_BOOL) :: year_length__tmp
367
368      IF (PRESENT(comment_)) THEN
369        comment__tmp = cxios_is_defined_calendar_wrapper_comment &
370      (calendar_wrapper_hdl%daddr)
371        comment_ = comment__tmp
372      ENDIF
373
374      IF (PRESENT(day_length_)) THEN
375        day_length__tmp = cxios_is_defined_calendar_wrapper_day_length &
376      (calendar_wrapper_hdl%daddr)
377        day_length_ = day_length__tmp
378      ENDIF
379
380      IF (PRESENT(leap_year_drift_)) THEN
381        leap_year_drift__tmp = cxios_is_defined_calendar_wrapper_leap_year_drift &
382      (calendar_wrapper_hdl%daddr)
383        leap_year_drift_ = leap_year_drift__tmp
384      ENDIF
385
386      IF (PRESENT(leap_year_drift_offset_)) THEN
387        leap_year_drift_offset__tmp = cxios_is_defined_calendar_wrapper_leap_year_drift_offset &
388      (calendar_wrapper_hdl%daddr)
389        leap_year_drift_offset_ = leap_year_drift_offset__tmp
390      ENDIF
391
392      IF (PRESENT(leap_year_month_)) THEN
393        leap_year_month__tmp = cxios_is_defined_calendar_wrapper_leap_year_month &
394      (calendar_wrapper_hdl%daddr)
395        leap_year_month_ = leap_year_month__tmp
396      ENDIF
397
398      IF (PRESENT(month_lengths_)) THEN
399        month_lengths__tmp = cxios_is_defined_calendar_wrapper_month_lengths &
400      (calendar_wrapper_hdl%daddr)
401        month_lengths_ = month_lengths__tmp
402      ENDIF
403
404      IF (PRESENT(start_date_)) THEN
405        start_date__tmp = cxios_is_defined_calendar_wrapper_start_date &
406      (calendar_wrapper_hdl%daddr)
407        start_date_ = start_date__tmp
408      ENDIF
409
410      IF (PRESENT(time_origin_)) THEN
411        time_origin__tmp = cxios_is_defined_calendar_wrapper_time_origin &
412      (calendar_wrapper_hdl%daddr)
413        time_origin_ = time_origin__tmp
414      ENDIF
415
416      IF (PRESENT(timestep_)) THEN
417        timestep__tmp = cxios_is_defined_calendar_wrapper_timestep &
418      (calendar_wrapper_hdl%daddr)
419        timestep_ = timestep__tmp
420      ENDIF
421
422      IF (PRESENT(type_)) THEN
423        type__tmp = cxios_is_defined_calendar_wrapper_type &
424      (calendar_wrapper_hdl%daddr)
425        type_ = type__tmp
426      ENDIF
427
428      IF (PRESENT(year_length_)) THEN
429        year_length__tmp = cxios_is_defined_calendar_wrapper_year_length &
430      (calendar_wrapper_hdl%daddr)
431        year_length_ = year_length__tmp
432      ENDIF
433
434  END SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl_)
435
436END MODULE icalendar_wrapper_attr
Note: See TracBrowser for help on using the repository browser.