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
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
[2620]10  USE LOGICAL_BOOL_CONVERSION
[581]11
[549]12CONTAINS
[581]13
[549]14  SUBROUTINE xios(set_calendar_wrapper_attr)  &
[1492]15    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]16    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]17
[549]18    IMPLICIT NONE
19      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
20      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
[1492]21      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment
[550]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(:)
[549]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
[550]31      INTEGER  , OPTIONAL, INTENT(IN) :: year_length
[581]32
[966]33      CALL xios(get_calendar_wrapper_handle) &
34      (calendar_wrapper_id,calendar_wrapper_hdl)
[549]35      CALL xios(set_calendar_wrapper_attr_hdl_)   &
[1492]36      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]37      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]38
[549]39  END SUBROUTINE xios(set_calendar_wrapper_attr)
[581]40
[549]41  SUBROUTINE xios(set_calendar_wrapper_attr_hdl)  &
[1492]42    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]43    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]44
[549]45    IMPLICIT NONE
46      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]47      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment
[550]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(:)
[549]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
[550]57      INTEGER  , OPTIONAL, INTENT(IN) :: year_length
[581]58
[549]59      CALL xios(set_calendar_wrapper_attr_hdl_)  &
[1492]60      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]61      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]62
[549]63  END SUBROUTINE xios(set_calendar_wrapper_attr_hdl)
[581]64
[549]65  SUBROUTINE xios(set_calendar_wrapper_attr_hdl_)   &
[1492]66    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
[550]67    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
[581]68
[549]69    IMPLICIT NONE
70      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]71      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment_
[550]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_(:)
[549]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_
[550]81      INTEGER  , OPTIONAL, INTENT(IN) :: year_length_
[581]82
[1492]83      IF (PRESENT(comment_)) THEN
84        CALL cxios_set_calendar_wrapper_comment &
85      (calendar_wrapper_hdl%daddr, comment_, len(comment_))
86      ENDIF
87
[550]88      IF (PRESENT(day_length_)) THEN
[966]89        CALL cxios_set_calendar_wrapper_day_length &
90      (calendar_wrapper_hdl%daddr, day_length_)
[550]91      ENDIF
[581]92
[550]93      IF (PRESENT(leap_year_drift_)) THEN
[966]94        CALL cxios_set_calendar_wrapper_leap_year_drift &
95      (calendar_wrapper_hdl%daddr, leap_year_drift_)
[550]96      ENDIF
[581]97
[550]98      IF (PRESENT(leap_year_drift_offset_)) THEN
[966]99        CALL cxios_set_calendar_wrapper_leap_year_drift_offset &
100      (calendar_wrapper_hdl%daddr, leap_year_drift_offset_)
[550]101      ENDIF
[581]102
[550]103      IF (PRESENT(leap_year_month_)) THEN
[966]104        CALL cxios_set_calendar_wrapper_leap_year_month &
105      (calendar_wrapper_hdl%daddr, leap_year_month_)
[550]106      ENDIF
[581]107
[550]108      IF (PRESENT(month_lengths_)) THEN
[966]109        CALL cxios_set_calendar_wrapper_month_lengths &
110      (calendar_wrapper_hdl%daddr, month_lengths_, SHAPE(month_lengths_))
[550]111      ENDIF
[581]112
[549]113      IF (PRESENT(start_date_)) THEN
[966]114        CALL cxios_set_calendar_wrapper_start_date &
115      (calendar_wrapper_hdl%daddr, start_date_, len(start_date_))
[549]116      ENDIF
[581]117
[549]118      IF (PRESENT(time_origin_)) THEN
[966]119        CALL cxios_set_calendar_wrapper_time_origin &
120      (calendar_wrapper_hdl%daddr, time_origin_, len(time_origin_))
[549]121      ENDIF
[581]122
[549]123      IF (PRESENT(timestep_)) THEN
[966]124        CALL cxios_set_calendar_wrapper_timestep &
125      (calendar_wrapper_hdl%daddr, timestep_)
[549]126      ENDIF
[581]127
[549]128      IF (PRESENT(type_)) THEN
[966]129        CALL cxios_set_calendar_wrapper_type &
130      (calendar_wrapper_hdl%daddr, type_, len(type_))
[549]131      ENDIF
[581]132
[550]133      IF (PRESENT(year_length_)) THEN
[966]134        CALL cxios_set_calendar_wrapper_year_length &
135      (calendar_wrapper_hdl%daddr, year_length_)
[550]136      ENDIF
[581]137
[549]138  END SUBROUTINE xios(set_calendar_wrapper_attr_hdl_)
[581]139
[549]140  SUBROUTINE xios(get_calendar_wrapper_attr)  &
[1492]141    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]142    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]143
[549]144    IMPLICIT NONE
145      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
146      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
[1492]147      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment
[550]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(:)
[549]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
[550]157      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length
[581]158
[966]159      CALL xios(get_calendar_wrapper_handle) &
160      (calendar_wrapper_id,calendar_wrapper_hdl)
[549]161      CALL xios(get_calendar_wrapper_attr_hdl_)   &
[1492]162      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]163      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]164
[549]165  END SUBROUTINE xios(get_calendar_wrapper_attr)
[581]166
[549]167  SUBROUTINE xios(get_calendar_wrapper_attr_hdl)  &
[1492]168    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]169    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]170
[549]171    IMPLICIT NONE
172      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]173      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment
[550]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(:)
[549]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
[550]183      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length
[581]184
[549]185      CALL xios(get_calendar_wrapper_attr_hdl_)  &
[1492]186      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]187      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]188
[549]189  END SUBROUTINE xios(get_calendar_wrapper_attr_hdl)
[581]190
[549]191  SUBROUTINE xios(get_calendar_wrapper_attr_hdl_)   &
[1492]192    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
[550]193    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
[581]194
[549]195    IMPLICIT NONE
196      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]197      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment_
[550]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_(:)
[549]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_
[550]207      INTEGER  , OPTIONAL, INTENT(OUT) :: year_length_
[581]208
[1492]209      IF (PRESENT(comment_)) THEN
210        CALL cxios_get_calendar_wrapper_comment &
211      (calendar_wrapper_hdl%daddr, comment_, len(comment_))
212      ENDIF
213
[550]214      IF (PRESENT(day_length_)) THEN
[966]215        CALL cxios_get_calendar_wrapper_day_length &
216      (calendar_wrapper_hdl%daddr, day_length_)
[550]217      ENDIF
[581]218
[550]219      IF (PRESENT(leap_year_drift_)) THEN
[966]220        CALL cxios_get_calendar_wrapper_leap_year_drift &
221      (calendar_wrapper_hdl%daddr, leap_year_drift_)
[550]222      ENDIF
[581]223
[550]224      IF (PRESENT(leap_year_drift_offset_)) THEN
[966]225        CALL cxios_get_calendar_wrapper_leap_year_drift_offset &
226      (calendar_wrapper_hdl%daddr, leap_year_drift_offset_)
[550]227      ENDIF
[581]228
[550]229      IF (PRESENT(leap_year_month_)) THEN
[966]230        CALL cxios_get_calendar_wrapper_leap_year_month &
231      (calendar_wrapper_hdl%daddr, leap_year_month_)
[550]232      ENDIF
[581]233
[550]234      IF (PRESENT(month_lengths_)) THEN
[966]235        CALL cxios_get_calendar_wrapper_month_lengths &
236      (calendar_wrapper_hdl%daddr, month_lengths_, SHAPE(month_lengths_))
[550]237      ENDIF
[581]238
[549]239      IF (PRESENT(start_date_)) THEN
[966]240        CALL cxios_get_calendar_wrapper_start_date &
241      (calendar_wrapper_hdl%daddr, start_date_, len(start_date_))
[549]242      ENDIF
[581]243
[549]244      IF (PRESENT(time_origin_)) THEN
[966]245        CALL cxios_get_calendar_wrapper_time_origin &
246      (calendar_wrapper_hdl%daddr, time_origin_, len(time_origin_))
[549]247      ENDIF
[581]248
[549]249      IF (PRESENT(timestep_)) THEN
[966]250        CALL cxios_get_calendar_wrapper_timestep &
251      (calendar_wrapper_hdl%daddr, timestep_)
[549]252      ENDIF
[581]253
[549]254      IF (PRESENT(type_)) THEN
[966]255        CALL cxios_get_calendar_wrapper_type &
256      (calendar_wrapper_hdl%daddr, type_, len(type_))
[549]257      ENDIF
[581]258
[550]259      IF (PRESENT(year_length_)) THEN
[966]260        CALL cxios_get_calendar_wrapper_year_length &
261      (calendar_wrapper_hdl%daddr, year_length_)
[550]262      ENDIF
[581]263
[549]264  END SUBROUTINE xios(get_calendar_wrapper_attr_hdl_)
[581]265
[549]266  SUBROUTINE xios(is_defined_calendar_wrapper_attr)  &
[1492]267    ( calendar_wrapper_id, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]268    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]269
[549]270    IMPLICIT NONE
271      TYPE(txios(calendar_wrapper))  :: calendar_wrapper_hdl
272      CHARACTER(LEN=*), INTENT(IN) ::calendar_wrapper_id
[1492]273      LOGICAL, OPTIONAL, INTENT(OUT) :: comment
274      LOGICAL(KIND=C_BOOL) :: comment_tmp
[550]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
[549]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
[550]293      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length
294      LOGICAL(KIND=C_BOOL) :: year_length_tmp
[581]295
[966]296      CALL xios(get_calendar_wrapper_handle) &
297      (calendar_wrapper_id,calendar_wrapper_hdl)
[549]298      CALL xios(is_defined_calendar_wrapper_attr_hdl_)   &
[1492]299      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]300      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]301
[549]302  END SUBROUTINE xios(is_defined_calendar_wrapper_attr)
[581]303
[549]304  SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl)  &
[1492]305    ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]306    , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]307
[549]308    IMPLICIT NONE
309      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]310      LOGICAL, OPTIONAL, INTENT(OUT) :: comment
311      LOGICAL(KIND=C_BOOL) :: comment_tmp
[550]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
[549]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
[550]330      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length
331      LOGICAL(KIND=C_BOOL) :: year_length_tmp
[581]332
[549]333      CALL xios(is_defined_calendar_wrapper_attr_hdl_)  &
[1492]334      ( calendar_wrapper_hdl, comment, day_length, leap_year_drift, leap_year_drift_offset, leap_year_month  &
[550]335      , month_lengths, start_date, time_origin, timestep, type, year_length )
[581]336
[549]337  END SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl)
[581]338
[549]339  SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl_)   &
[1492]340    ( calendar_wrapper_hdl, comment_, day_length_, leap_year_drift_, leap_year_drift_offset_, leap_year_month_  &
[550]341    , month_lengths_, start_date_, time_origin_, timestep_, type_, year_length_ )
[581]342
[549]343    IMPLICIT NONE
344      TYPE(txios(calendar_wrapper)) , INTENT(IN) :: calendar_wrapper_hdl
[1492]345      LOGICAL, OPTIONAL, INTENT(OUT) :: comment_
346      LOGICAL(KIND=C_BOOL) :: comment__tmp
[550]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
[549]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
[550]365      LOGICAL, OPTIONAL, INTENT(OUT) :: year_length_
366      LOGICAL(KIND=C_BOOL) :: year_length__tmp
[581]367
[1492]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
[550]374      IF (PRESENT(day_length_)) THEN
[966]375        day_length__tmp = cxios_is_defined_calendar_wrapper_day_length &
376      (calendar_wrapper_hdl%daddr)
[581]377        day_length_ = day_length__tmp
[550]378      ENDIF
[581]379
[550]380      IF (PRESENT(leap_year_drift_)) THEN
[966]381        leap_year_drift__tmp = cxios_is_defined_calendar_wrapper_leap_year_drift &
382      (calendar_wrapper_hdl%daddr)
[581]383        leap_year_drift_ = leap_year_drift__tmp
[550]384      ENDIF
[581]385
[550]386      IF (PRESENT(leap_year_drift_offset_)) THEN
[966]387        leap_year_drift_offset__tmp = cxios_is_defined_calendar_wrapper_leap_year_drift_offset &
388      (calendar_wrapper_hdl%daddr)
[581]389        leap_year_drift_offset_ = leap_year_drift_offset__tmp
[550]390      ENDIF
[581]391
[550]392      IF (PRESENT(leap_year_month_)) THEN
[966]393        leap_year_month__tmp = cxios_is_defined_calendar_wrapper_leap_year_month &
394      (calendar_wrapper_hdl%daddr)
[581]395        leap_year_month_ = leap_year_month__tmp
[550]396      ENDIF
[581]397
[550]398      IF (PRESENT(month_lengths_)) THEN
[966]399        month_lengths__tmp = cxios_is_defined_calendar_wrapper_month_lengths &
400      (calendar_wrapper_hdl%daddr)
[581]401        month_lengths_ = month_lengths__tmp
[550]402      ENDIF
[581]403
[549]404      IF (PRESENT(start_date_)) THEN
[966]405        start_date__tmp = cxios_is_defined_calendar_wrapper_start_date &
406      (calendar_wrapper_hdl%daddr)
[581]407        start_date_ = start_date__tmp
[549]408      ENDIF
[581]409
[549]410      IF (PRESENT(time_origin_)) THEN
[966]411        time_origin__tmp = cxios_is_defined_calendar_wrapper_time_origin &
412      (calendar_wrapper_hdl%daddr)
[581]413        time_origin_ = time_origin__tmp
[549]414      ENDIF
[581]415
[549]416      IF (PRESENT(timestep_)) THEN
[966]417        timestep__tmp = cxios_is_defined_calendar_wrapper_timestep &
418      (calendar_wrapper_hdl%daddr)
[581]419        timestep_ = timestep__tmp
[549]420      ENDIF
[581]421
[549]422      IF (PRESENT(type_)) THEN
[966]423        type__tmp = cxios_is_defined_calendar_wrapper_type &
424      (calendar_wrapper_hdl%daddr)
[581]425        type_ = type__tmp
[549]426      ENDIF
[581]427
[550]428      IF (PRESENT(year_length_)) THEN
[966]429        year_length__tmp = cxios_is_defined_calendar_wrapper_year_length &
430      (calendar_wrapper_hdl%daddr)
[581]431        year_length_ = year_length__tmp
[550]432      ENDIF
[581]433
[549]434  END SUBROUTINE xios(is_defined_calendar_wrapper_attr_hdl_)
[581]435
[549]436END MODULE icalendar_wrapper_attr
Note: See TracBrowser for help on using the repository browser.