source: XIOS/dev/XIOS_DEV_CMIP6/src/interface/fortran_attr/icalendar_wrapper_attr.F90 @ 2338

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