Ignore:
Timestamp:
04/24/18 18:03:18 (6 years ago)
Author:
oabramkina
Message:

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:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/dev/XIOS_DEV_CMIP6/src/interface/fortran_attr/iaxisgroup_attr.F90

    r1158 r1492  
    1212 
    1313  SUBROUTINE xios(set_axisgroup_attr)  & 
    14     ( axisgroup_id, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    15     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    16     , value ) 
     14    ( axisgroup_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     15    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     16    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     17    , unit, value ) 
    1718 
    1819    IMPLICIT NONE 
     
    2021      CHARACTER(LEN=*), INTENT(IN) ::axisgroup_id 
    2122      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     23      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_type 
    2224      INTEGER  , OPTIONAL, INTENT(IN) :: begin 
    2325      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds(:,:) 
     26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name 
     27      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment 
    2428      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin 
    2529      INTEGER  , OPTIONAL, INTENT(IN) :: data_index(:) 
    2630      INTEGER  , OPTIONAL, INTENT(IN) :: data_n 
     31      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: dim_name 
     32      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula 
     33      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_bounds 
     34      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term 
     35      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term_bounds 
    2736      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref 
    2837      INTEGER  , OPTIONAL, INTENT(IN) :: index(:) 
     
    4453      (axisgroup_id,axisgroup_hdl) 
    4554      CALL xios(set_axisgroup_attr_hdl_)   & 
    46       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    47       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    48       , value ) 
     55      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     56      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     57      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     58      , unit, value ) 
    4959 
    5060  END SUBROUTINE xios(set_axisgroup_attr) 
    5161 
    5262  SUBROUTINE xios(set_axisgroup_attr_hdl)  & 
    53     ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    54     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    55     , value ) 
     63    ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     64    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     65    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     66    , unit, value ) 
    5667 
    5768    IMPLICIT NONE 
    5869      TYPE(txios(axisgroup)) , INTENT(IN) :: axisgroup_hdl 
    5970      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     71      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_type 
    6072      INTEGER  , OPTIONAL, INTENT(IN) :: begin 
    6173      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds(:,:) 
     74      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name 
     75      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment 
    6276      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin 
    6377      INTEGER  , OPTIONAL, INTENT(IN) :: data_index(:) 
    6478      INTEGER  , OPTIONAL, INTENT(IN) :: data_n 
     79      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: dim_name 
     80      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula 
     81      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_bounds 
     82      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term 
     83      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term_bounds 
    6584      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref 
    6685      INTEGER  , OPTIONAL, INTENT(IN) :: index(:) 
     
    8099 
    81100      CALL xios(set_axisgroup_attr_hdl_)  & 
    82       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    83       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    84       , value ) 
     101      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     102      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     103      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     104      , unit, value ) 
    85105 
    86106  END SUBROUTINE xios(set_axisgroup_attr_hdl) 
    87107 
    88108  SUBROUTINE xios(set_axisgroup_attr_hdl_)   & 
    89     ( axisgroup_hdl, axis_ref_, begin_, bounds_, data_begin_, data_index_, data_n_, group_ref_, index_  & 
    90     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    91     , unit_, value_ ) 
     109    ( axisgroup_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_  & 
     110    , data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     111    , group_ref_, index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_  & 
     112    , positive_, prec_, standard_name_, unit_, value_ ) 
    92113 
    93114    IMPLICIT NONE 
    94115      TYPE(txios(axisgroup)) , INTENT(IN) :: axisgroup_hdl 
    95116      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref_ 
     117      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_type_ 
    96118      INTEGER  , OPTIONAL, INTENT(IN) :: begin_ 
    97119      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds_(:,:) 
     120      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name_ 
     121      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment_ 
    98122      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin_ 
    99123      INTEGER  , OPTIONAL, INTENT(IN) :: data_index_(:) 
    100124      INTEGER  , OPTIONAL, INTENT(IN) :: data_n_ 
     125      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: dim_name_ 
     126      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_ 
     127      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_bounds_ 
     128      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term_ 
     129      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: formula_term_bounds_ 
    101130      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref_ 
    102131      INTEGER  , OPTIONAL, INTENT(IN) :: index_(:) 
     
    120149      ENDIF 
    121150 
     151      IF (PRESENT(axis_type_)) THEN 
     152        CALL cxios_set_axisgroup_axis_type & 
     153      (axisgroup_hdl%daddr, axis_type_, len(axis_type_)) 
     154      ENDIF 
     155 
    122156      IF (PRESENT(begin_)) THEN 
    123157        CALL cxios_set_axisgroup_begin & 
     
    130164      ENDIF 
    131165 
     166      IF (PRESENT(bounds_name_)) THEN 
     167        CALL cxios_set_axisgroup_bounds_name & 
     168      (axisgroup_hdl%daddr, bounds_name_, len(bounds_name_)) 
     169      ENDIF 
     170 
     171      IF (PRESENT(comment_)) THEN 
     172        CALL cxios_set_axisgroup_comment & 
     173      (axisgroup_hdl%daddr, comment_, len(comment_)) 
     174      ENDIF 
     175 
    132176      IF (PRESENT(data_begin_)) THEN 
    133177        CALL cxios_set_axisgroup_data_begin & 
     
    143187        CALL cxios_set_axisgroup_data_n & 
    144188      (axisgroup_hdl%daddr, data_n_) 
     189      ENDIF 
     190 
     191      IF (PRESENT(dim_name_)) THEN 
     192        CALL cxios_set_axisgroup_dim_name & 
     193      (axisgroup_hdl%daddr, dim_name_, len(dim_name_)) 
     194      ENDIF 
     195 
     196      IF (PRESENT(formula_)) THEN 
     197        CALL cxios_set_axisgroup_formula & 
     198      (axisgroup_hdl%daddr, formula_, len(formula_)) 
     199      ENDIF 
     200 
     201      IF (PRESENT(formula_bounds_)) THEN 
     202        CALL cxios_set_axisgroup_formula_bounds & 
     203      (axisgroup_hdl%daddr, formula_bounds_, len(formula_bounds_)) 
     204      ENDIF 
     205 
     206      IF (PRESENT(formula_term_)) THEN 
     207        CALL cxios_set_axisgroup_formula_term & 
     208      (axisgroup_hdl%daddr, formula_term_, len(formula_term_)) 
     209      ENDIF 
     210 
     211      IF (PRESENT(formula_term_bounds_)) THEN 
     212        CALL cxios_set_axisgroup_formula_term_bounds & 
     213      (axisgroup_hdl%daddr, formula_term_bounds_, len(formula_term_bounds_)) 
    145214      ENDIF 
    146215 
     
    220289 
    221290  SUBROUTINE xios(get_axisgroup_attr)  & 
    222     ( axisgroup_id, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    223     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    224     , value ) 
     291    ( axisgroup_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     292    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     293    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     294    , unit, value ) 
    225295 
    226296    IMPLICIT NONE 
     
    228298      CHARACTER(LEN=*), INTENT(IN) ::axisgroup_id 
    229299      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     300      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_type 
    230301      INTEGER  , OPTIONAL, INTENT(OUT) :: begin 
    231302      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds(:,:) 
     303      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name 
     304      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment 
    232305      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin 
    233306      INTEGER  , OPTIONAL, INTENT(OUT) :: data_index(:) 
    234307      INTEGER  , OPTIONAL, INTENT(OUT) :: data_n 
     308      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: dim_name 
     309      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula 
     310      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_bounds 
     311      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term 
     312      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term_bounds 
    235313      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref 
    236314      INTEGER  , OPTIONAL, INTENT(OUT) :: index(:) 
     
    252330      (axisgroup_id,axisgroup_hdl) 
    253331      CALL xios(get_axisgroup_attr_hdl_)   & 
    254       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    255       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    256       , value ) 
     332      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     333      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     334      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     335      , unit, value ) 
    257336 
    258337  END SUBROUTINE xios(get_axisgroup_attr) 
    259338 
    260339  SUBROUTINE xios(get_axisgroup_attr_hdl)  & 
    261     ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    262     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    263     , value ) 
     340    ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     341    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     342    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     343    , unit, value ) 
    264344 
    265345    IMPLICIT NONE 
    266346      TYPE(txios(axisgroup)) , INTENT(IN) :: axisgroup_hdl 
    267347      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     348      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_type 
    268349      INTEGER  , OPTIONAL, INTENT(OUT) :: begin 
    269350      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds(:,:) 
     351      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name 
     352      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment 
    270353      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin 
    271354      INTEGER  , OPTIONAL, INTENT(OUT) :: data_index(:) 
    272355      INTEGER  , OPTIONAL, INTENT(OUT) :: data_n 
     356      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: dim_name 
     357      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula 
     358      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_bounds 
     359      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term 
     360      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term_bounds 
    273361      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref 
    274362      INTEGER  , OPTIONAL, INTENT(OUT) :: index(:) 
     
    288376 
    289377      CALL xios(get_axisgroup_attr_hdl_)  & 
    290       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    291       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    292       , value ) 
     378      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     379      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     380      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     381      , unit, value ) 
    293382 
    294383  END SUBROUTINE xios(get_axisgroup_attr_hdl) 
    295384 
    296385  SUBROUTINE xios(get_axisgroup_attr_hdl_)   & 
    297     ( axisgroup_hdl, axis_ref_, begin_, bounds_, data_begin_, data_index_, data_n_, group_ref_, index_  & 
    298     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    299     , unit_, value_ ) 
     386    ( axisgroup_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_  & 
     387    , data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     388    , group_ref_, index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_  & 
     389    , positive_, prec_, standard_name_, unit_, value_ ) 
    300390 
    301391    IMPLICIT NONE 
    302392      TYPE(txios(axisgroup)) , INTENT(IN) :: axisgroup_hdl 
    303393      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref_ 
     394      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_type_ 
    304395      INTEGER  , OPTIONAL, INTENT(OUT) :: begin_ 
    305396      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds_(:,:) 
     397      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name_ 
     398      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment_ 
    306399      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin_ 
    307400      INTEGER  , OPTIONAL, INTENT(OUT) :: data_index_(:) 
    308401      INTEGER  , OPTIONAL, INTENT(OUT) :: data_n_ 
     402      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: dim_name_ 
     403      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_ 
     404      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_bounds_ 
     405      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term_ 
     406      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: formula_term_bounds_ 
    309407      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref_ 
    310408      INTEGER  , OPTIONAL, INTENT(OUT) :: index_(:) 
     
    328426      ENDIF 
    329427 
     428      IF (PRESENT(axis_type_)) THEN 
     429        CALL cxios_get_axisgroup_axis_type & 
     430      (axisgroup_hdl%daddr, axis_type_, len(axis_type_)) 
     431      ENDIF 
     432 
    330433      IF (PRESENT(begin_)) THEN 
    331434        CALL cxios_get_axisgroup_begin & 
     
    338441      ENDIF 
    339442 
     443      IF (PRESENT(bounds_name_)) THEN 
     444        CALL cxios_get_axisgroup_bounds_name & 
     445      (axisgroup_hdl%daddr, bounds_name_, len(bounds_name_)) 
     446      ENDIF 
     447 
     448      IF (PRESENT(comment_)) THEN 
     449        CALL cxios_get_axisgroup_comment & 
     450      (axisgroup_hdl%daddr, comment_, len(comment_)) 
     451      ENDIF 
     452 
    340453      IF (PRESENT(data_begin_)) THEN 
    341454        CALL cxios_get_axisgroup_data_begin & 
     
    351464        CALL cxios_get_axisgroup_data_n & 
    352465      (axisgroup_hdl%daddr, data_n_) 
     466      ENDIF 
     467 
     468      IF (PRESENT(dim_name_)) THEN 
     469        CALL cxios_get_axisgroup_dim_name & 
     470      (axisgroup_hdl%daddr, dim_name_, len(dim_name_)) 
     471      ENDIF 
     472 
     473      IF (PRESENT(formula_)) THEN 
     474        CALL cxios_get_axisgroup_formula & 
     475      (axisgroup_hdl%daddr, formula_, len(formula_)) 
     476      ENDIF 
     477 
     478      IF (PRESENT(formula_bounds_)) THEN 
     479        CALL cxios_get_axisgroup_formula_bounds & 
     480      (axisgroup_hdl%daddr, formula_bounds_, len(formula_bounds_)) 
     481      ENDIF 
     482 
     483      IF (PRESENT(formula_term_)) THEN 
     484        CALL cxios_get_axisgroup_formula_term & 
     485      (axisgroup_hdl%daddr, formula_term_, len(formula_term_)) 
     486      ENDIF 
     487 
     488      IF (PRESENT(formula_term_bounds_)) THEN 
     489        CALL cxios_get_axisgroup_formula_term_bounds & 
     490      (axisgroup_hdl%daddr, formula_term_bounds_, len(formula_term_bounds_)) 
    353491      ENDIF 
    354492 
     
    428566 
    429567  SUBROUTINE xios(is_defined_axisgroup_attr)  & 
    430     ( axisgroup_id, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    431     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    432     , value ) 
     568    ( axisgroup_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     569    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     570    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     571    , unit, value ) 
    433572 
    434573    IMPLICIT NONE 
     
    437576      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    438577      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     578      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_type 
     579      LOGICAL(KIND=C_BOOL) :: axis_type_tmp 
    439580      LOGICAL, OPTIONAL, INTENT(OUT) :: begin 
    440581      LOGICAL(KIND=C_BOOL) :: begin_tmp 
    441582      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds 
    442583      LOGICAL(KIND=C_BOOL) :: bounds_tmp 
     584      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name 
     585      LOGICAL(KIND=C_BOOL) :: bounds_name_tmp 
     586      LOGICAL, OPTIONAL, INTENT(OUT) :: comment 
     587      LOGICAL(KIND=C_BOOL) :: comment_tmp 
    443588      LOGICAL, OPTIONAL, INTENT(OUT) :: data_begin 
    444589      LOGICAL(KIND=C_BOOL) :: data_begin_tmp 
     
    447592      LOGICAL, OPTIONAL, INTENT(OUT) :: data_n 
    448593      LOGICAL(KIND=C_BOOL) :: data_n_tmp 
     594      LOGICAL, OPTIONAL, INTENT(OUT) :: dim_name 
     595      LOGICAL(KIND=C_BOOL) :: dim_name_tmp 
     596      LOGICAL, OPTIONAL, INTENT(OUT) :: formula 
     597      LOGICAL(KIND=C_BOOL) :: formula_tmp 
     598      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_bounds 
     599      LOGICAL(KIND=C_BOOL) :: formula_bounds_tmp 
     600      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term 
     601      LOGICAL(KIND=C_BOOL) :: formula_term_tmp 
     602      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term_bounds 
     603      LOGICAL(KIND=C_BOOL) :: formula_term_bounds_tmp 
    449604      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref 
    450605      LOGICAL(KIND=C_BOOL) :: group_ref_tmp 
     
    479634      (axisgroup_id,axisgroup_hdl) 
    480635      CALL xios(is_defined_axisgroup_attr_hdl_)   & 
    481       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    482       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    483       , value ) 
     636      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     637      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     638      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     639      , unit, value ) 
    484640 
    485641  END SUBROUTINE xios(is_defined_axisgroup_attr) 
    486642 
    487643  SUBROUTINE xios(is_defined_axisgroup_attr_hdl)  & 
    488     ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    489     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    490     , value ) 
     644    ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     645    , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     646    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     647    , unit, value ) 
    491648 
    492649    IMPLICIT NONE 
     
    494651      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    495652      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     653      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_type 
     654      LOGICAL(KIND=C_BOOL) :: axis_type_tmp 
    496655      LOGICAL, OPTIONAL, INTENT(OUT) :: begin 
    497656      LOGICAL(KIND=C_BOOL) :: begin_tmp 
    498657      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds 
    499658      LOGICAL(KIND=C_BOOL) :: bounds_tmp 
     659      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name 
     660      LOGICAL(KIND=C_BOOL) :: bounds_name_tmp 
     661      LOGICAL, OPTIONAL, INTENT(OUT) :: comment 
     662      LOGICAL(KIND=C_BOOL) :: comment_tmp 
    500663      LOGICAL, OPTIONAL, INTENT(OUT) :: data_begin 
    501664      LOGICAL(KIND=C_BOOL) :: data_begin_tmp 
     
    504667      LOGICAL, OPTIONAL, INTENT(OUT) :: data_n 
    505668      LOGICAL(KIND=C_BOOL) :: data_n_tmp 
     669      LOGICAL, OPTIONAL, INTENT(OUT) :: dim_name 
     670      LOGICAL(KIND=C_BOOL) :: dim_name_tmp 
     671      LOGICAL, OPTIONAL, INTENT(OUT) :: formula 
     672      LOGICAL(KIND=C_BOOL) :: formula_tmp 
     673      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_bounds 
     674      LOGICAL(KIND=C_BOOL) :: formula_bounds_tmp 
     675      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term 
     676      LOGICAL(KIND=C_BOOL) :: formula_term_tmp 
     677      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term_bounds 
     678      LOGICAL(KIND=C_BOOL) :: formula_term_bounds_tmp 
    506679      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref 
    507680      LOGICAL(KIND=C_BOOL) :: group_ref_tmp 
     
    534707 
    535708      CALL xios(is_defined_axisgroup_attr_hdl_)  & 
    536       ( axisgroup_hdl, axis_ref, begin, bounds, data_begin, data_index, data_n, group_ref, index, label  & 
    537       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    538       , value ) 
     709      ( axisgroup_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
     710      , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, group_ref, index  & 
     711      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     712      , unit, value ) 
    539713 
    540714  END SUBROUTINE xios(is_defined_axisgroup_attr_hdl) 
    541715 
    542716  SUBROUTINE xios(is_defined_axisgroup_attr_hdl_)   & 
    543     ( axisgroup_hdl, axis_ref_, begin_, bounds_, data_begin_, data_index_, data_n_, group_ref_, index_  & 
    544     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    545     , unit_, value_ ) 
     717    ( axisgroup_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_  & 
     718    , data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     719    , group_ref_, index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_  & 
     720    , positive_, prec_, standard_name_, unit_, value_ ) 
    546721 
    547722    IMPLICIT NONE 
     
    549724      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref_ 
    550725      LOGICAL(KIND=C_BOOL) :: axis_ref__tmp 
     726      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_type_ 
     727      LOGICAL(KIND=C_BOOL) :: axis_type__tmp 
    551728      LOGICAL, OPTIONAL, INTENT(OUT) :: begin_ 
    552729      LOGICAL(KIND=C_BOOL) :: begin__tmp 
    553730      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_ 
    554731      LOGICAL(KIND=C_BOOL) :: bounds__tmp 
     732      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name_ 
     733      LOGICAL(KIND=C_BOOL) :: bounds_name__tmp 
     734      LOGICAL, OPTIONAL, INTENT(OUT) :: comment_ 
     735      LOGICAL(KIND=C_BOOL) :: comment__tmp 
    555736      LOGICAL, OPTIONAL, INTENT(OUT) :: data_begin_ 
    556737      LOGICAL(KIND=C_BOOL) :: data_begin__tmp 
     
    559740      LOGICAL, OPTIONAL, INTENT(OUT) :: data_n_ 
    560741      LOGICAL(KIND=C_BOOL) :: data_n__tmp 
     742      LOGICAL, OPTIONAL, INTENT(OUT) :: dim_name_ 
     743      LOGICAL(KIND=C_BOOL) :: dim_name__tmp 
     744      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_ 
     745      LOGICAL(KIND=C_BOOL) :: formula__tmp 
     746      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_bounds_ 
     747      LOGICAL(KIND=C_BOOL) :: formula_bounds__tmp 
     748      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term_ 
     749      LOGICAL(KIND=C_BOOL) :: formula_term__tmp 
     750      LOGICAL, OPTIONAL, INTENT(OUT) :: formula_term_bounds_ 
     751      LOGICAL(KIND=C_BOOL) :: formula_term_bounds__tmp 
    561752      LOGICAL, OPTIONAL, INTENT(OUT) :: group_ref_ 
    562753      LOGICAL(KIND=C_BOOL) :: group_ref__tmp 
     
    594785      ENDIF 
    595786 
     787      IF (PRESENT(axis_type_)) THEN 
     788        axis_type__tmp = cxios_is_defined_axisgroup_axis_type & 
     789      (axisgroup_hdl%daddr) 
     790        axis_type_ = axis_type__tmp 
     791      ENDIF 
     792 
    596793      IF (PRESENT(begin_)) THEN 
    597794        begin__tmp = cxios_is_defined_axisgroup_begin & 
     
    606803      ENDIF 
    607804 
     805      IF (PRESENT(bounds_name_)) THEN 
     806        bounds_name__tmp = cxios_is_defined_axisgroup_bounds_name & 
     807      (axisgroup_hdl%daddr) 
     808        bounds_name_ = bounds_name__tmp 
     809      ENDIF 
     810 
     811      IF (PRESENT(comment_)) THEN 
     812        comment__tmp = cxios_is_defined_axisgroup_comment & 
     813      (axisgroup_hdl%daddr) 
     814        comment_ = comment__tmp 
     815      ENDIF 
     816 
    608817      IF (PRESENT(data_begin_)) THEN 
    609818        data_begin__tmp = cxios_is_defined_axisgroup_data_begin & 
     
    624833      ENDIF 
    625834 
     835      IF (PRESENT(dim_name_)) THEN 
     836        dim_name__tmp = cxios_is_defined_axisgroup_dim_name & 
     837      (axisgroup_hdl%daddr) 
     838        dim_name_ = dim_name__tmp 
     839      ENDIF 
     840 
     841      IF (PRESENT(formula_)) THEN 
     842        formula__tmp = cxios_is_defined_axisgroup_formula & 
     843      (axisgroup_hdl%daddr) 
     844        formula_ = formula__tmp 
     845      ENDIF 
     846 
     847      IF (PRESENT(formula_bounds_)) THEN 
     848        formula_bounds__tmp = cxios_is_defined_axisgroup_formula_bounds & 
     849      (axisgroup_hdl%daddr) 
     850        formula_bounds_ = formula_bounds__tmp 
     851      ENDIF 
     852 
     853      IF (PRESENT(formula_term_)) THEN 
     854        formula_term__tmp = cxios_is_defined_axisgroup_formula_term & 
     855      (axisgroup_hdl%daddr) 
     856        formula_term_ = formula_term__tmp 
     857      ENDIF 
     858 
     859      IF (PRESENT(formula_term_bounds_)) THEN 
     860        formula_term_bounds__tmp = cxios_is_defined_axisgroup_formula_term_bounds & 
     861      (axisgroup_hdl%daddr) 
     862        formula_term_bounds_ = formula_term_bounds__tmp 
     863      ENDIF 
     864 
    626865      IF (PRESENT(group_ref_)) THEN 
    627866        group_ref__tmp = cxios_is_defined_axisgroup_group_ref & 
Note: See TracChangeset for help on using the changeset viewer.