source: XIOS/trunk/src/interface/fortran_attr/ifilegroup_attr.F90 @ 551

Last change on this file since 551 was 538, checked in by rlacroix, 9 years ago

Convert more attributes to use the new duration type:

  • field: freq_op and freq_offset
  • file: output_freq, sync_freq and split_freq.

Remember that you now have to use the "xios_duration" type instead of strings to get/set those attributes through the Fortran interface.

  • Property copyright set to
    Software name : XIOS (Xml I/O Server)
    http://forge.ipsl.jussieu.fr/ioserver
    Creation date : January 2009
    Licence : CeCCIL version2
    see license file in root directory : Licence_CeCILL_V2-en.txt
    or http://www.cecill.info/licences/Licence_CeCILL_V2-en.html
    Holder : CEA/LSCE (Laboratoire des Sciences du CLimat et de l'Environnement)
    CNRS/IPSL (Institut Pierre Simon Laplace)
    Project Manager : Yann Meurdesoif
    yann.meurdesoif@cea.fr
File size: 22.4 KB
Line 
1! * ************************************************************************** *
2! *               Interface auto generated - do not modify                     *
3! * ************************************************************************** *
4#include "xios_fortran_prefix.hpp"
5
6MODULE ifilegroup_attr
7  USE, INTRINSIC :: ISO_C_BINDING
8  USE ifile
9  USE filegroup_interface_attr
10 
11CONTAINS
12 
13  SUBROUTINE xios(set_filegroup_attr)  &
14    ( filegroup_id, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
15    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
16   
17    IMPLICIT NONE
18      TYPE(txios(filegroup))  :: filegroup_hdl
19      CHARACTER(LEN=*), INTENT(IN) ::filegroup_id
20      LOGICAL  , OPTIONAL, INTENT(IN) :: append
21      LOGICAL (KIND=C_BOOL) :: append_tmp
22      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: description
23      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled
24      LOGICAL (KIND=C_BOOL) :: enabled_tmp
25      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: format
26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref
27      INTEGER  , OPTIONAL, INTENT(IN) :: min_digits
28      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name
29      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix
30      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: output_freq
31      INTEGER  , OPTIONAL, INTENT(IN) :: output_level
32      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access
33      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: split_freq
34      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format
35      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: sync_freq
36      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
37     
38      CALL xios(get_filegroup_handle)(filegroup_id,filegroup_hdl)
39      CALL xios(set_filegroup_attr_hdl_)   &
40      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
41      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
42   
43  END SUBROUTINE xios(set_filegroup_attr)
44 
45  SUBROUTINE xios(set_filegroup_attr_hdl)  &
46    ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
47    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
48   
49    IMPLICIT NONE
50      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
51      LOGICAL  , OPTIONAL, INTENT(IN) :: append
52      LOGICAL (KIND=C_BOOL) :: append_tmp
53      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: description
54      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled
55      LOGICAL (KIND=C_BOOL) :: enabled_tmp
56      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: format
57      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref
58      INTEGER  , OPTIONAL, INTENT(IN) :: min_digits
59      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name
60      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix
61      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: output_freq
62      INTEGER  , OPTIONAL, INTENT(IN) :: output_level
63      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access
64      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: split_freq
65      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format
66      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: sync_freq
67      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type
68     
69      CALL xios(set_filegroup_attr_hdl_)  &
70      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
71      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
72   
73  END SUBROUTINE xios(set_filegroup_attr_hdl)
74 
75  SUBROUTINE xios(set_filegroup_attr_hdl_)   &
76    ( filegroup_hdl, append_, description_, enabled_, format_, group_ref_, min_digits_, name_, name_suffix_  &
77    , output_freq_, output_level_, par_access_, split_freq_, split_freq_format_, sync_freq_, type_  &
78     )
79   
80    IMPLICIT NONE
81      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
82      LOGICAL  , OPTIONAL, INTENT(IN) :: append_
83      LOGICAL (KIND=C_BOOL) :: append__tmp
84      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: description_
85      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled_
86      LOGICAL (KIND=C_BOOL) :: enabled__tmp
87      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: format_
88      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref_
89      INTEGER  , OPTIONAL, INTENT(IN) :: min_digits_
90      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_
91      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix_
92      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: output_freq_
93      INTEGER  , OPTIONAL, INTENT(IN) :: output_level_
94      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access_
95      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: split_freq_
96      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format_
97      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: sync_freq_
98      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_
99     
100      IF (PRESENT(append_)) THEN
101        append__tmp=append_
102        CALL cxios_set_filegroup_append(filegroup_hdl%daddr, append__tmp)
103      ENDIF
104     
105      IF (PRESENT(description_)) THEN
106        CALL cxios_set_filegroup_description(filegroup_hdl%daddr, description_, len(description_))
107      ENDIF
108     
109      IF (PRESENT(enabled_)) THEN
110        enabled__tmp=enabled_
111        CALL cxios_set_filegroup_enabled(filegroup_hdl%daddr, enabled__tmp)
112      ENDIF
113     
114      IF (PRESENT(format_)) THEN
115        CALL cxios_set_filegroup_format(filegroup_hdl%daddr, format_, len(format_))
116      ENDIF
117     
118      IF (PRESENT(group_ref_)) THEN
119        CALL cxios_set_filegroup_group_ref(filegroup_hdl%daddr, group_ref_, len(group_ref_))
120      ENDIF
121     
122      IF (PRESENT(min_digits_)) THEN
123        CALL cxios_set_filegroup_min_digits(filegroup_hdl%daddr, min_digits_)
124      ENDIF
125     
126      IF (PRESENT(name_)) THEN
127        CALL cxios_set_filegroup_name(filegroup_hdl%daddr, name_, len(name_))
128      ENDIF
129     
130      IF (PRESENT(name_suffix_)) THEN
131        CALL cxios_set_filegroup_name_suffix(filegroup_hdl%daddr, name_suffix_, len(name_suffix_))
132      ENDIF
133     
134      IF (PRESENT(output_freq_)) THEN
135        CALL cxios_set_filegroup_output_freq(filegroup_hdl%daddr, output_freq_)
136      ENDIF
137     
138      IF (PRESENT(output_level_)) THEN
139        CALL cxios_set_filegroup_output_level(filegroup_hdl%daddr, output_level_)
140      ENDIF
141     
142      IF (PRESENT(par_access_)) THEN
143        CALL cxios_set_filegroup_par_access(filegroup_hdl%daddr, par_access_, len(par_access_))
144      ENDIF
145     
146      IF (PRESENT(split_freq_)) THEN
147        CALL cxios_set_filegroup_split_freq(filegroup_hdl%daddr, split_freq_)
148      ENDIF
149     
150      IF (PRESENT(split_freq_format_)) THEN
151        CALL cxios_set_filegroup_split_freq_format(filegroup_hdl%daddr, split_freq_format_, len(split_freq_format_))
152      ENDIF
153     
154      IF (PRESENT(sync_freq_)) THEN
155        CALL cxios_set_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_)
156      ENDIF
157     
158      IF (PRESENT(type_)) THEN
159        CALL cxios_set_filegroup_type(filegroup_hdl%daddr, type_, len(type_))
160      ENDIF
161     
162     
163   
164  END SUBROUTINE xios(set_filegroup_attr_hdl_)
165 
166  SUBROUTINE xios(get_filegroup_attr)  &
167    ( filegroup_id, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
168    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
169   
170    IMPLICIT NONE
171      TYPE(txios(filegroup))  :: filegroup_hdl
172      CHARACTER(LEN=*), INTENT(IN) ::filegroup_id
173      LOGICAL  , OPTIONAL, INTENT(OUT) :: append
174      LOGICAL (KIND=C_BOOL) :: append_tmp
175      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: description
176      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled
177      LOGICAL (KIND=C_BOOL) :: enabled_tmp
178      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: format
179      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref
180      INTEGER  , OPTIONAL, INTENT(OUT) :: min_digits
181      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name
182      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix
183      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: output_freq
184      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level
185      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access
186      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: split_freq
187      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format
188      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: sync_freq
189      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
190     
191      CALL xios(get_filegroup_handle)(filegroup_id,filegroup_hdl)
192      CALL xios(get_filegroup_attr_hdl_)   &
193      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
194      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
195   
196  END SUBROUTINE xios(get_filegroup_attr)
197 
198  SUBROUTINE xios(get_filegroup_attr_hdl)  &
199    ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
200    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
201   
202    IMPLICIT NONE
203      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
204      LOGICAL  , OPTIONAL, INTENT(OUT) :: append
205      LOGICAL (KIND=C_BOOL) :: append_tmp
206      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: description
207      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled
208      LOGICAL (KIND=C_BOOL) :: enabled_tmp
209      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: format
210      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref
211      INTEGER  , OPTIONAL, INTENT(OUT) :: min_digits
212      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name
213      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix
214      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: output_freq
215      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level
216      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access
217      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: split_freq
218      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format
219      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: sync_freq
220      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type
221     
222      CALL xios(get_filegroup_attr_hdl_)  &
223      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
224      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
225   
226  END SUBROUTINE xios(get_filegroup_attr_hdl)
227 
228  SUBROUTINE xios(get_filegroup_attr_hdl_)   &
229    ( filegroup_hdl, append_, description_, enabled_, format_, group_ref_, min_digits_, name_, name_suffix_  &
230    , output_freq_, output_level_, par_access_, split_freq_, split_freq_format_, sync_freq_, type_  &
231     )
232   
233    IMPLICIT NONE
234      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
235      LOGICAL  , OPTIONAL, INTENT(OUT) :: append_
236      LOGICAL (KIND=C_BOOL) :: append__tmp
237      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: description_
238      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled_
239      LOGICAL (KIND=C_BOOL) :: enabled__tmp
240      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: format_
241      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref_
242      INTEGER  , OPTIONAL, INTENT(OUT) :: min_digits_
243      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_
244      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix_
245      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: output_freq_
246      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level_
247      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access_
248      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: split_freq_
249      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format_
250      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: sync_freq_
251      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_
252     
253      IF (PRESENT(append_)) THEN
254        CALL cxios_get_filegroup_append(filegroup_hdl%daddr, append__tmp)
255        append_=append__tmp
256      ENDIF
257     
258      IF (PRESENT(description_)) THEN
259        CALL cxios_get_filegroup_description(filegroup_hdl%daddr, description_, len(description_))
260      ENDIF
261     
262      IF (PRESENT(enabled_)) THEN
263        CALL cxios_get_filegroup_enabled(filegroup_hdl%daddr, enabled__tmp)
264        enabled_=enabled__tmp
265      ENDIF
266     
267      IF (PRESENT(format_)) THEN
268        CALL cxios_get_filegroup_format(filegroup_hdl%daddr, format_, len(format_))
269      ENDIF
270     
271      IF (PRESENT(group_ref_)) THEN
272        CALL cxios_get_filegroup_group_ref(filegroup_hdl%daddr, group_ref_, len(group_ref_))
273      ENDIF
274     
275      IF (PRESENT(min_digits_)) THEN
276        CALL cxios_get_filegroup_min_digits(filegroup_hdl%daddr, min_digits_)
277      ENDIF
278     
279      IF (PRESENT(name_)) THEN
280        CALL cxios_get_filegroup_name(filegroup_hdl%daddr, name_, len(name_))
281      ENDIF
282     
283      IF (PRESENT(name_suffix_)) THEN
284        CALL cxios_get_filegroup_name_suffix(filegroup_hdl%daddr, name_suffix_, len(name_suffix_))
285      ENDIF
286     
287      IF (PRESENT(output_freq_)) THEN
288        CALL cxios_get_filegroup_output_freq(filegroup_hdl%daddr, output_freq_)
289      ENDIF
290     
291      IF (PRESENT(output_level_)) THEN
292        CALL cxios_get_filegroup_output_level(filegroup_hdl%daddr, output_level_)
293      ENDIF
294     
295      IF (PRESENT(par_access_)) THEN
296        CALL cxios_get_filegroup_par_access(filegroup_hdl%daddr, par_access_, len(par_access_))
297      ENDIF
298     
299      IF (PRESENT(split_freq_)) THEN
300        CALL cxios_get_filegroup_split_freq(filegroup_hdl%daddr, split_freq_)
301      ENDIF
302     
303      IF (PRESENT(split_freq_format_)) THEN
304        CALL cxios_get_filegroup_split_freq_format(filegroup_hdl%daddr, split_freq_format_, len(split_freq_format_))
305      ENDIF
306     
307      IF (PRESENT(sync_freq_)) THEN
308        CALL cxios_get_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_)
309      ENDIF
310     
311      IF (PRESENT(type_)) THEN
312        CALL cxios_get_filegroup_type(filegroup_hdl%daddr, type_, len(type_))
313      ENDIF
314     
315     
316   
317  END SUBROUTINE xios(get_filegroup_attr_hdl_)
318 
319  SUBROUTINE xios(is_defined_filegroup_attr)  &
320    ( filegroup_id, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
321    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
322   
323    IMPLICIT NONE
324      TYPE(txios(filegroup))  :: filegroup_hdl
325      CHARACTER(LEN=*), INTENT(IN) ::filegroup_id
326      LOGICAL, OPTIONAL, INTENT(OUT) :: append
327      LOGICAL(KIND=C_BOOL) :: append_tmp
328      LOGICAL, OPTIONAL, INTENT(OUT) :: description
329      LOGICAL(KIND=C_BOOL) :: description_tmp
330      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled
331      LOGICAL(KIND=C_BOOL) :: enabled_tmp
332      LOGICAL, OPTIONAL, INTENT(OUT) :: format
333      LOGICAL(KIND=C_BOOL) :: format_tmp
334      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref
335      LOGICAL(KIND=C_BOOL) :: group_ref_tmp
336      LOGICAL, OPTIONAL, INTENT(OUT) :: min_digits
337      LOGICAL(KIND=C_BOOL) :: min_digits_tmp
338      LOGICAL, OPTIONAL, INTENT(OUT) :: name
339      LOGICAL(KIND=C_BOOL) :: name_tmp
340      LOGICAL, OPTIONAL, INTENT(OUT) :: name_suffix
341      LOGICAL(KIND=C_BOOL) :: name_suffix_tmp
342      LOGICAL, OPTIONAL, INTENT(OUT) :: output_freq
343      LOGICAL(KIND=C_BOOL) :: output_freq_tmp
344      LOGICAL, OPTIONAL, INTENT(OUT) :: output_level
345      LOGICAL(KIND=C_BOOL) :: output_level_tmp
346      LOGICAL, OPTIONAL, INTENT(OUT) :: par_access
347      LOGICAL(KIND=C_BOOL) :: par_access_tmp
348      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq
349      LOGICAL(KIND=C_BOOL) :: split_freq_tmp
350      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq_format
351      LOGICAL(KIND=C_BOOL) :: split_freq_format_tmp
352      LOGICAL, OPTIONAL, INTENT(OUT) :: sync_freq
353      LOGICAL(KIND=C_BOOL) :: sync_freq_tmp
354      LOGICAL, OPTIONAL, INTENT(OUT) :: type
355      LOGICAL(KIND=C_BOOL) :: type_tmp
356     
357      CALL xios(get_filegroup_handle)(filegroup_id,filegroup_hdl)
358      CALL xios(is_defined_filegroup_attr_hdl_)   &
359      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
360      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
361   
362  END SUBROUTINE xios(is_defined_filegroup_attr)
363 
364  SUBROUTINE xios(is_defined_filegroup_attr_hdl)  &
365    ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
366    , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
367   
368    IMPLICIT NONE
369      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
370      LOGICAL, OPTIONAL, INTENT(OUT) :: append
371      LOGICAL(KIND=C_BOOL) :: append_tmp
372      LOGICAL, OPTIONAL, INTENT(OUT) :: description
373      LOGICAL(KIND=C_BOOL) :: description_tmp
374      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled
375      LOGICAL(KIND=C_BOOL) :: enabled_tmp
376      LOGICAL, OPTIONAL, INTENT(OUT) :: format
377      LOGICAL(KIND=C_BOOL) :: format_tmp
378      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref
379      LOGICAL(KIND=C_BOOL) :: group_ref_tmp
380      LOGICAL, OPTIONAL, INTENT(OUT) :: min_digits
381      LOGICAL(KIND=C_BOOL) :: min_digits_tmp
382      LOGICAL, OPTIONAL, INTENT(OUT) :: name
383      LOGICAL(KIND=C_BOOL) :: name_tmp
384      LOGICAL, OPTIONAL, INTENT(OUT) :: name_suffix
385      LOGICAL(KIND=C_BOOL) :: name_suffix_tmp
386      LOGICAL, OPTIONAL, INTENT(OUT) :: output_freq
387      LOGICAL(KIND=C_BOOL) :: output_freq_tmp
388      LOGICAL, OPTIONAL, INTENT(OUT) :: output_level
389      LOGICAL(KIND=C_BOOL) :: output_level_tmp
390      LOGICAL, OPTIONAL, INTENT(OUT) :: par_access
391      LOGICAL(KIND=C_BOOL) :: par_access_tmp
392      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq
393      LOGICAL(KIND=C_BOOL) :: split_freq_tmp
394      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq_format
395      LOGICAL(KIND=C_BOOL) :: split_freq_format_tmp
396      LOGICAL, OPTIONAL, INTENT(OUT) :: sync_freq
397      LOGICAL(KIND=C_BOOL) :: sync_freq_tmp
398      LOGICAL, OPTIONAL, INTENT(OUT) :: type
399      LOGICAL(KIND=C_BOOL) :: type_tmp
400     
401      CALL xios(is_defined_filegroup_attr_hdl_)  &
402      ( filegroup_hdl, append, description, enabled, format, group_ref, min_digits, name, name_suffix  &
403      , output_freq, output_level, par_access, split_freq, split_freq_format, sync_freq, type )
404   
405  END SUBROUTINE xios(is_defined_filegroup_attr_hdl)
406 
407  SUBROUTINE xios(is_defined_filegroup_attr_hdl_)   &
408    ( filegroup_hdl, append_, description_, enabled_, format_, group_ref_, min_digits_, name_, name_suffix_  &
409    , output_freq_, output_level_, par_access_, split_freq_, split_freq_format_, sync_freq_, type_  &
410     )
411   
412    IMPLICIT NONE
413      TYPE(txios(filegroup)) , INTENT(IN) :: filegroup_hdl
414      LOGICAL, OPTIONAL, INTENT(OUT) :: append_
415      LOGICAL(KIND=C_BOOL) :: append__tmp
416      LOGICAL, OPTIONAL, INTENT(OUT) :: description_
417      LOGICAL(KIND=C_BOOL) :: description__tmp
418      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled_
419      LOGICAL(KIND=C_BOOL) :: enabled__tmp
420      LOGICAL, OPTIONAL, INTENT(OUT) :: format_
421      LOGICAL(KIND=C_BOOL) :: format__tmp
422      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref_
423      LOGICAL(KIND=C_BOOL) :: group_ref__tmp
424      LOGICAL, OPTIONAL, INTENT(OUT) :: min_digits_
425      LOGICAL(KIND=C_BOOL) :: min_digits__tmp
426      LOGICAL, OPTIONAL, INTENT(OUT) :: name_
427      LOGICAL(KIND=C_BOOL) :: name__tmp
428      LOGICAL, OPTIONAL, INTENT(OUT) :: name_suffix_
429      LOGICAL(KIND=C_BOOL) :: name_suffix__tmp
430      LOGICAL, OPTIONAL, INTENT(OUT) :: output_freq_
431      LOGICAL(KIND=C_BOOL) :: output_freq__tmp
432      LOGICAL, OPTIONAL, INTENT(OUT) :: output_level_
433      LOGICAL(KIND=C_BOOL) :: output_level__tmp
434      LOGICAL, OPTIONAL, INTENT(OUT) :: par_access_
435      LOGICAL(KIND=C_BOOL) :: par_access__tmp
436      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq_
437      LOGICAL(KIND=C_BOOL) :: split_freq__tmp
438      LOGICAL, OPTIONAL, INTENT(OUT) :: split_freq_format_
439      LOGICAL(KIND=C_BOOL) :: split_freq_format__tmp
440      LOGICAL, OPTIONAL, INTENT(OUT) :: sync_freq_
441      LOGICAL(KIND=C_BOOL) :: sync_freq__tmp
442      LOGICAL, OPTIONAL, INTENT(OUT) :: type_
443      LOGICAL(KIND=C_BOOL) :: type__tmp
444     
445      IF (PRESENT(append_)) THEN
446        append__tmp=cxios_is_defined_filegroup_append(filegroup_hdl%daddr)
447        append_=append__tmp
448      ENDIF
449     
450      IF (PRESENT(description_)) THEN
451        description__tmp=cxios_is_defined_filegroup_description(filegroup_hdl%daddr)
452        description_=description__tmp
453      ENDIF
454     
455      IF (PRESENT(enabled_)) THEN
456        enabled__tmp=cxios_is_defined_filegroup_enabled(filegroup_hdl%daddr)
457        enabled_=enabled__tmp
458      ENDIF
459     
460      IF (PRESENT(format_)) THEN
461        format__tmp=cxios_is_defined_filegroup_format(filegroup_hdl%daddr)
462        format_=format__tmp
463      ENDIF
464     
465      IF (PRESENT(group_ref_)) THEN
466        group_ref__tmp=cxios_is_defined_filegroup_group_ref(filegroup_hdl%daddr)
467        group_ref_=group_ref__tmp
468      ENDIF
469     
470      IF (PRESENT(min_digits_)) THEN
471        min_digits__tmp=cxios_is_defined_filegroup_min_digits(filegroup_hdl%daddr)
472        min_digits_=min_digits__tmp
473      ENDIF
474     
475      IF (PRESENT(name_)) THEN
476        name__tmp=cxios_is_defined_filegroup_name(filegroup_hdl%daddr)
477        name_=name__tmp
478      ENDIF
479     
480      IF (PRESENT(name_suffix_)) THEN
481        name_suffix__tmp=cxios_is_defined_filegroup_name_suffix(filegroup_hdl%daddr)
482        name_suffix_=name_suffix__tmp
483      ENDIF
484     
485      IF (PRESENT(output_freq_)) THEN
486        output_freq__tmp=cxios_is_defined_filegroup_output_freq(filegroup_hdl%daddr)
487        output_freq_=output_freq__tmp
488      ENDIF
489     
490      IF (PRESENT(output_level_)) THEN
491        output_level__tmp=cxios_is_defined_filegroup_output_level(filegroup_hdl%daddr)
492        output_level_=output_level__tmp
493      ENDIF
494     
495      IF (PRESENT(par_access_)) THEN
496        par_access__tmp=cxios_is_defined_filegroup_par_access(filegroup_hdl%daddr)
497        par_access_=par_access__tmp
498      ENDIF
499     
500      IF (PRESENT(split_freq_)) THEN
501        split_freq__tmp=cxios_is_defined_filegroup_split_freq(filegroup_hdl%daddr)
502        split_freq_=split_freq__tmp
503      ENDIF
504     
505      IF (PRESENT(split_freq_format_)) THEN
506        split_freq_format__tmp=cxios_is_defined_filegroup_split_freq_format(filegroup_hdl%daddr)
507        split_freq_format_=split_freq_format__tmp
508      ENDIF
509     
510      IF (PRESENT(sync_freq_)) THEN
511        sync_freq__tmp=cxios_is_defined_filegroup_sync_freq(filegroup_hdl%daddr)
512        sync_freq_=sync_freq__tmp
513      ENDIF
514     
515      IF (PRESENT(type_)) THEN
516        type__tmp=cxios_is_defined_filegroup_type(filegroup_hdl%daddr)
517        type_=type__tmp
518      ENDIF
519     
520     
521   
522  END SUBROUTINE xios(is_defined_filegroup_attr_hdl_)
523 
524END MODULE ifilegroup_attr
Note: See TracBrowser for help on using the repository browser.