Ignore:
Timestamp:
01/10/17 14:36:29 (8 years ago)
Author:
oabramkina
Message:

Intermeadiate version for merging with new server functionalities.

Location:
XIOS/dev/dev_olga/src/interface/fortran_attr
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • XIOS/dev/dev_olga/src/interface/fortran_attr/field_interface_attr.F90

    r891 r1021  
    5050 
    5151 
     52    SUBROUTINE cxios_set_field_cell_methods(field_hdl, cell_methods, cell_methods_size) BIND(C) 
     53      USE ISO_C_BINDING 
     54      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     55      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods 
     56      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_size 
     57    END SUBROUTINE cxios_set_field_cell_methods 
     58 
     59    SUBROUTINE cxios_get_field_cell_methods(field_hdl, cell_methods, cell_methods_size) BIND(C) 
     60      USE ISO_C_BINDING 
     61      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     62      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods 
     63      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_size 
     64    END SUBROUTINE cxios_get_field_cell_methods 
     65 
     66    FUNCTION cxios_is_defined_field_cell_methods(field_hdl) BIND(C) 
     67      USE ISO_C_BINDING 
     68      LOGICAL(kind=C_BOOL) :: cxios_is_defined_field_cell_methods 
     69      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     70    END FUNCTION cxios_is_defined_field_cell_methods 
     71 
     72 
     73    SUBROUTINE cxios_set_field_cell_methods_mode(field_hdl, cell_methods_mode, cell_methods_mode_size) BIND(C) 
     74      USE ISO_C_BINDING 
     75      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     76      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods_mode 
     77      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_mode_size 
     78    END SUBROUTINE cxios_set_field_cell_methods_mode 
     79 
     80    SUBROUTINE cxios_get_field_cell_methods_mode(field_hdl, cell_methods_mode, cell_methods_mode_size) BIND(C) 
     81      USE ISO_C_BINDING 
     82      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     83      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods_mode 
     84      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_mode_size 
     85    END SUBROUTINE cxios_get_field_cell_methods_mode 
     86 
     87    FUNCTION cxios_is_defined_field_cell_methods_mode(field_hdl) BIND(C) 
     88      USE ISO_C_BINDING 
     89      LOGICAL(kind=C_BOOL) :: cxios_is_defined_field_cell_methods_mode 
     90      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     91    END FUNCTION cxios_is_defined_field_cell_methods_mode 
     92 
     93 
    5294    SUBROUTINE cxios_set_field_compression_level(field_hdl, compression_level) BIND(C) 
    5395      USE ISO_C_BINDING 
     
    147189 
    148190 
     191    SUBROUTINE cxios_set_field_expr(field_hdl, expr, expr_size) BIND(C) 
     192      USE ISO_C_BINDING 
     193      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     194      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: expr 
     195      INTEGER  (kind = C_INT)     , VALUE        :: expr_size 
     196    END SUBROUTINE cxios_set_field_expr 
     197 
     198    SUBROUTINE cxios_get_field_expr(field_hdl, expr, expr_size) BIND(C) 
     199      USE ISO_C_BINDING 
     200      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     201      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: expr 
     202      INTEGER  (kind = C_INT)     , VALUE        :: expr_size 
     203    END SUBROUTINE cxios_get_field_expr 
     204 
     205    FUNCTION cxios_is_defined_field_expr(field_hdl) BIND(C) 
     206      USE ISO_C_BINDING 
     207      LOGICAL(kind=C_BOOL) :: cxios_is_defined_field_expr 
     208      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     209    END FUNCTION cxios_is_defined_field_expr 
     210 
     211 
    149212    SUBROUTINE cxios_set_field_field_ref(field_hdl, field_ref, field_ref_size) BIND(C) 
    150213      USE ISO_C_BINDING 
  • XIOS/dev/dev_olga/src/interface/fortran_attr/fieldgroup_interface_attr.F90

    r891 r1021  
    5050 
    5151 
     52    SUBROUTINE cxios_set_fieldgroup_cell_methods(fieldgroup_hdl, cell_methods, cell_methods_size) BIND(C) 
     53      USE ISO_C_BINDING 
     54      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     55      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods 
     56      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_size 
     57    END SUBROUTINE cxios_set_fieldgroup_cell_methods 
     58 
     59    SUBROUTINE cxios_get_fieldgroup_cell_methods(fieldgroup_hdl, cell_methods, cell_methods_size) BIND(C) 
     60      USE ISO_C_BINDING 
     61      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     62      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods 
     63      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_size 
     64    END SUBROUTINE cxios_get_fieldgroup_cell_methods 
     65 
     66    FUNCTION cxios_is_defined_fieldgroup_cell_methods(fieldgroup_hdl) BIND(C) 
     67      USE ISO_C_BINDING 
     68      LOGICAL(kind=C_BOOL) :: cxios_is_defined_fieldgroup_cell_methods 
     69      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     70    END FUNCTION cxios_is_defined_fieldgroup_cell_methods 
     71 
     72 
     73    SUBROUTINE cxios_set_fieldgroup_cell_methods_mode(fieldgroup_hdl, cell_methods_mode, cell_methods_mode_size) BIND(C) 
     74      USE ISO_C_BINDING 
     75      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     76      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods_mode 
     77      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_mode_size 
     78    END SUBROUTINE cxios_set_fieldgroup_cell_methods_mode 
     79 
     80    SUBROUTINE cxios_get_fieldgroup_cell_methods_mode(fieldgroup_hdl, cell_methods_mode, cell_methods_mode_size) BIND(C) 
     81      USE ISO_C_BINDING 
     82      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     83      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: cell_methods_mode 
     84      INTEGER  (kind = C_INT)     , VALUE        :: cell_methods_mode_size 
     85    END SUBROUTINE cxios_get_fieldgroup_cell_methods_mode 
     86 
     87    FUNCTION cxios_is_defined_fieldgroup_cell_methods_mode(fieldgroup_hdl) BIND(C) 
     88      USE ISO_C_BINDING 
     89      LOGICAL(kind=C_BOOL) :: cxios_is_defined_fieldgroup_cell_methods_mode 
     90      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     91    END FUNCTION cxios_is_defined_fieldgroup_cell_methods_mode 
     92 
     93 
    5294    SUBROUTINE cxios_set_fieldgroup_compression_level(fieldgroup_hdl, compression_level) BIND(C) 
    5395      USE ISO_C_BINDING 
     
    147189 
    148190 
     191    SUBROUTINE cxios_set_fieldgroup_expr(fieldgroup_hdl, expr, expr_size) BIND(C) 
     192      USE ISO_C_BINDING 
     193      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     194      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: expr 
     195      INTEGER  (kind = C_INT)     , VALUE        :: expr_size 
     196    END SUBROUTINE cxios_set_fieldgroup_expr 
     197 
     198    SUBROUTINE cxios_get_fieldgroup_expr(fieldgroup_hdl, expr, expr_size) BIND(C) 
     199      USE ISO_C_BINDING 
     200      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     201      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: expr 
     202      INTEGER  (kind = C_INT)     , VALUE        :: expr_size 
     203    END SUBROUTINE cxios_get_fieldgroup_expr 
     204 
     205    FUNCTION cxios_is_defined_fieldgroup_expr(fieldgroup_hdl) BIND(C) 
     206      USE ISO_C_BINDING 
     207      LOGICAL(kind=C_BOOL) :: cxios_is_defined_fieldgroup_expr 
     208      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     209    END FUNCTION cxios_is_defined_fieldgroup_expr 
     210 
     211 
    149212    SUBROUTINE cxios_set_fieldgroup_field_ref(fieldgroup_hdl, field_ref, field_ref_size) BIND(C) 
    150213      USE ISO_C_BINDING 
  • XIOS/dev/dev_olga/src/interface/fortran_attr/ifield_attr.F90

    r966 r1021  
    1212 
    1313  SUBROUTINE xios(set_field_attr)  & 
    14     ( field_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    15     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    16     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    17     , unit, valid_max, valid_min ) 
     14    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     15    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     16    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     17    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    1818 
    1919    IMPLICIT NONE 
     
    2222      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset 
    2323      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     24      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
     25      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
    2426      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2527      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    2931      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled 
    3032      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     33      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr 
    3134      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    3235      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset 
     
    5659      (field_id,field_hdl) 
    5760      CALL xios(set_field_attr_hdl_)   & 
    58       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    59       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    60       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    61       , unit, valid_max, valid_min ) 
     61      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     62      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     63      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     64      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    6265 
    6366  END SUBROUTINE xios(set_field_attr) 
    6467 
    6568  SUBROUTINE xios(set_field_attr_hdl)  & 
    66     ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    67     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    68     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    69     , unit, valid_max, valid_min ) 
     69    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     70    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     71    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     72    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    7073 
    7174    IMPLICIT NONE 
     
    7376      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset 
    7477      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     78      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
     79      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
    7580      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    7681      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    8085      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled 
    8186      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     87      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr 
    8288      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    8389      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset 
     
    105111 
    106112      CALL xios(set_field_attr_hdl_)  & 
    107       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    108       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    109       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    110       , unit, valid_max, valid_min ) 
     113      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     114      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     115      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     116      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    111117 
    112118  END SUBROUTINE xios(set_field_attr_hdl) 
    113119 
    114120  SUBROUTINE xios(set_field_attr_hdl_)   & 
    115     ( field_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    116     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, indexed_output_  & 
    117     , level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_  & 
    118     , ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     121    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_, default_value_  & 
     122    , detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_, freq_op_, grid_path_  & 
     123    , grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_  & 
     124    , scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_  & 
     125     ) 
    119126 
    120127    IMPLICIT NONE 
     
    122129      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset_ 
    123130      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref_ 
     131      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_ 
     132      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode_ 
    124133      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    125134      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value_ 
     
    129138      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled_ 
    130139      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
     140      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr_ 
    131141      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref_ 
    132142      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset_ 
     
    163173      ENDIF 
    164174 
     175      IF (PRESENT(cell_methods_)) THEN 
     176        CALL cxios_set_field_cell_methods & 
     177      (field_hdl%daddr, cell_methods_, len(cell_methods_)) 
     178      ENDIF 
     179 
     180      IF (PRESENT(cell_methods_mode_)) THEN 
     181        CALL cxios_set_field_cell_methods_mode & 
     182      (field_hdl%daddr, cell_methods_mode_, len(cell_methods_mode_)) 
     183      ENDIF 
     184 
    165185      IF (PRESENT(compression_level_)) THEN 
    166186        CALL cxios_set_field_compression_level & 
     
    190210      ENDIF 
    191211 
     212      IF (PRESENT(expr_)) THEN 
     213        CALL cxios_set_field_expr & 
     214      (field_hdl%daddr, expr_, len(expr_)) 
     215      ENDIF 
     216 
    192217      IF (PRESENT(field_ref_)) THEN 
    193218        CALL cxios_set_field_field_ref & 
     
    296321 
    297322  SUBROUTINE xios(get_field_attr)  & 
    298     ( field_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    299     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    300     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    301     , unit, valid_max, valid_min ) 
     323    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     324    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     325    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     326    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    302327 
    303328    IMPLICIT NONE 
     
    306331      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset 
    307332      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     333      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
     334      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    308335      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    309336      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    313340      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled 
    314341      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     342      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr 
    315343      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    316344      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset 
     
    340368      (field_id,field_hdl) 
    341369      CALL xios(get_field_attr_hdl_)   & 
    342       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    343       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    344       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    345       , unit, valid_max, valid_min ) 
     370      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     371      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     372      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     373      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    346374 
    347375  END SUBROUTINE xios(get_field_attr) 
    348376 
    349377  SUBROUTINE xios(get_field_attr_hdl)  & 
    350     ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    351     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    352     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    353     , unit, valid_max, valid_min ) 
     378    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     379    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     380    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     381    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    354382 
    355383    IMPLICIT NONE 
     
    357385      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset 
    358386      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     387      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
     388      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    359389      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    360390      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    364394      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled 
    365395      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     396      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr 
    366397      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    367398      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset 
     
    389420 
    390421      CALL xios(get_field_attr_hdl_)  & 
    391       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    392       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    393       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    394       , unit, valid_max, valid_min ) 
     422      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     423      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     424      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     425      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    395426 
    396427  END SUBROUTINE xios(get_field_attr_hdl) 
    397428 
    398429  SUBROUTINE xios(get_field_attr_hdl_)   & 
    399     ( field_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    400     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, indexed_output_  & 
    401     , level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_  & 
    402     , ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     430    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_, default_value_  & 
     431    , detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_, freq_op_, grid_path_  & 
     432    , grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_  & 
     433    , scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_  & 
     434     ) 
    403435 
    404436    IMPLICIT NONE 
     
    406438      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset_ 
    407439      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref_ 
     440      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_ 
     441      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
    408442      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    409443      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value_ 
     
    413447      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled_ 
    414448      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
     449      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr_ 
    415450      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref_ 
    416451      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset_ 
     
    447482      ENDIF 
    448483 
     484      IF (PRESENT(cell_methods_)) THEN 
     485        CALL cxios_get_field_cell_methods & 
     486      (field_hdl%daddr, cell_methods_, len(cell_methods_)) 
     487      ENDIF 
     488 
     489      IF (PRESENT(cell_methods_mode_)) THEN 
     490        CALL cxios_get_field_cell_methods_mode & 
     491      (field_hdl%daddr, cell_methods_mode_, len(cell_methods_mode_)) 
     492      ENDIF 
     493 
    449494      IF (PRESENT(compression_level_)) THEN 
    450495        CALL cxios_get_field_compression_level & 
     
    474519      ENDIF 
    475520 
     521      IF (PRESENT(expr_)) THEN 
     522        CALL cxios_get_field_expr & 
     523      (field_hdl%daddr, expr_, len(expr_)) 
     524      ENDIF 
     525 
    476526      IF (PRESENT(field_ref_)) THEN 
    477527        CALL cxios_get_field_field_ref & 
     
    580630 
    581631  SUBROUTINE xios(is_defined_field_attr)  & 
    582     ( field_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    583     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    584     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    585     , unit, valid_max, valid_min ) 
     632    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     633    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     634    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     635    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    586636 
    587637    IMPLICIT NONE 
     
    592642      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    593643      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     644      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods 
     645      LOGICAL(KIND=C_BOOL) :: cell_methods_tmp 
     646      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     647      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
    594648      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    595649      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    602656      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled 
    603657      LOGICAL(KIND=C_BOOL) :: enabled_tmp 
     658      LOGICAL, OPTIONAL, INTENT(OUT) :: expr 
     659      LOGICAL(KIND=C_BOOL) :: expr_tmp 
    604660      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref 
    605661      LOGICAL(KIND=C_BOOL) :: field_ref_tmp 
     
    646702      (field_id,field_hdl) 
    647703      CALL xios(is_defined_field_attr_hdl_)   & 
    648       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    649       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    650       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    651       , unit, valid_max, valid_min ) 
     704      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     705      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     706      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     707      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    652708 
    653709  END SUBROUTINE xios(is_defined_field_attr) 
    654710 
    655711  SUBROUTINE xios(is_defined_field_attr_hdl)  & 
    656     ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    657     , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    658     , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    659     , unit, valid_max, valid_min ) 
     712    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     713    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     714    , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     715    , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    660716 
    661717    IMPLICIT NONE 
     
    665721      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    666722      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     723      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods 
     724      LOGICAL(KIND=C_BOOL) :: cell_methods_tmp 
     725      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     726      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
    667727      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    668728      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    675735      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled 
    676736      LOGICAL(KIND=C_BOOL) :: enabled_tmp 
     737      LOGICAL, OPTIONAL, INTENT(OUT) :: expr 
     738      LOGICAL(KIND=C_BOOL) :: expr_tmp 
    677739      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref 
    678740      LOGICAL(KIND=C_BOOL) :: field_ref_tmp 
     
    717779 
    718780      CALL xios(is_defined_field_attr_hdl_)  & 
    719       ( field_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value, domain_ref  & 
    720       , enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, indexed_output, level, long_name  & 
    721       , name, operation, prec, read_access, scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq  & 
    722       , unit, valid_max, valid_min ) 
     781      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     782      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     783      , grid_ref, indexed_output, level, long_name, name, operation, prec, read_access, scalar_ref  & 
     784      , scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
    723785 
    724786  END SUBROUTINE xios(is_defined_field_attr_hdl) 
    725787 
    726788  SUBROUTINE xios(is_defined_field_attr_hdl_)   & 
    727     ( field_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    728     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, indexed_output_  & 
    729     , level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_  & 
    730     , ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     789    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_, default_value_  & 
     790    , detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_, freq_op_, grid_path_  & 
     791    , grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_  & 
     792    , scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_  & 
     793     ) 
    731794 
    732795    IMPLICIT NONE 
     
    736799      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref_ 
    737800      LOGICAL(KIND=C_BOOL) :: axis_ref__tmp 
     801      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_ 
     802      LOGICAL(KIND=C_BOOL) :: cell_methods__tmp 
     803      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
     804      LOGICAL(KIND=C_BOOL) :: cell_methods_mode__tmp 
    738805      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level_ 
    739806      LOGICAL(KIND=C_BOOL) :: compression_level__tmp 
     
    746813      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled_ 
    747814      LOGICAL(KIND=C_BOOL) :: enabled__tmp 
     815      LOGICAL, OPTIONAL, INTENT(OUT) :: expr_ 
     816      LOGICAL(KIND=C_BOOL) :: expr__tmp 
    748817      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref_ 
    749818      LOGICAL(KIND=C_BOOL) :: field_ref__tmp 
     
    799868      ENDIF 
    800869 
     870      IF (PRESENT(cell_methods_)) THEN 
     871        cell_methods__tmp = cxios_is_defined_field_cell_methods & 
     872      (field_hdl%daddr) 
     873        cell_methods_ = cell_methods__tmp 
     874      ENDIF 
     875 
     876      IF (PRESENT(cell_methods_mode_)) THEN 
     877        cell_methods_mode__tmp = cxios_is_defined_field_cell_methods_mode & 
     878      (field_hdl%daddr) 
     879        cell_methods_mode_ = cell_methods_mode__tmp 
     880      ENDIF 
     881 
    801882      IF (PRESENT(compression_level_)) THEN 
    802883        compression_level__tmp = cxios_is_defined_field_compression_level & 
     
    829910      ENDIF 
    830911 
     912      IF (PRESENT(expr_)) THEN 
     913        expr__tmp = cxios_is_defined_field_expr & 
     914      (field_hdl%daddr) 
     915        expr_ = expr__tmp 
     916      ENDIF 
     917 
    831918      IF (PRESENT(field_ref_)) THEN 
    832919        field_ref__tmp = cxios_is_defined_field_field_ref & 
  • XIOS/dev/dev_olga/src/interface/fortran_attr/ifieldgroup_attr.F90

    r966 r1021  
    1212 
    1313  SUBROUTINE xios(set_fieldgroup_attr)  & 
    14     ( fieldgroup_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    15     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    16     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    17     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     14    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     15    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     16    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     17    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     18     ) 
    1819 
    1920    IMPLICIT NONE 
     
    2223      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset 
    2324      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     25      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
     26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
    2427      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2528      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    2932      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled 
    3033      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     34      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr 
    3135      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    3236      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset 
     
    5761      (fieldgroup_id,fieldgroup_hdl) 
    5862      CALL xios(set_fieldgroup_attr_hdl_)   & 
    59       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    60       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    61       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    62       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     63      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     64      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     65      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     66      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     67       ) 
    6368 
    6469  END SUBROUTINE xios(set_fieldgroup_attr) 
    6570 
    6671  SUBROUTINE xios(set_fieldgroup_attr_hdl)  & 
    67     ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    68     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    69     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    70     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     72    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     73    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     74    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     75    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     76     ) 
    7177 
    7278    IMPLICIT NONE 
     
    7480      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset 
    7581      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref 
     82      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
     83      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
    7684      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    7785      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    8189      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled 
    8290      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     91      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr 
    8392      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    8493      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset 
     
    107116 
    108117      CALL xios(set_fieldgroup_attr_hdl_)  & 
    109       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    110       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    111       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    112       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     118      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     119      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     120      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     121      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     122       ) 
    113123 
    114124  END SUBROUTINE xios(set_fieldgroup_attr_hdl) 
    115125 
    116126  SUBROUTINE xios(set_fieldgroup_attr_hdl_)   & 
    117     ( fieldgroup_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    118     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_  & 
    119     , indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_  & 
    120     , standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     127    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_  & 
     128    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     129    , freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_, name_, operation_  & 
     130    , prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_  & 
     131    , unit_, valid_max_, valid_min_ ) 
    121132 
    122133    IMPLICIT NONE 
     
    124135      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: add_offset_ 
    125136      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: axis_ref_ 
     137      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_ 
     138      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode_ 
    126139      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    127140      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value_ 
     
    131144      LOGICAL  , OPTIONAL, INTENT(IN) :: enabled_ 
    132145      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
     146      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: expr_ 
    133147      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref_ 
    134148      TYPE(txios(duration))  , OPTIONAL, INTENT(IN) :: freq_offset_ 
     
    166180      ENDIF 
    167181 
     182      IF (PRESENT(cell_methods_)) THEN 
     183        CALL cxios_set_fieldgroup_cell_methods & 
     184      (fieldgroup_hdl%daddr, cell_methods_, len(cell_methods_)) 
     185      ENDIF 
     186 
     187      IF (PRESENT(cell_methods_mode_)) THEN 
     188        CALL cxios_set_fieldgroup_cell_methods_mode & 
     189      (fieldgroup_hdl%daddr, cell_methods_mode_, len(cell_methods_mode_)) 
     190      ENDIF 
     191 
    168192      IF (PRESENT(compression_level_)) THEN 
    169193        CALL cxios_set_fieldgroup_compression_level & 
     
    193217      ENDIF 
    194218 
     219      IF (PRESENT(expr_)) THEN 
     220        CALL cxios_set_fieldgroup_expr & 
     221      (fieldgroup_hdl%daddr, expr_, len(expr_)) 
     222      ENDIF 
     223 
    195224      IF (PRESENT(field_ref_)) THEN 
    196225        CALL cxios_set_fieldgroup_field_ref & 
     
    304333 
    305334  SUBROUTINE xios(get_fieldgroup_attr)  & 
    306     ( fieldgroup_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    307     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    308     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    309     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     335    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     336    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     337    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     338    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     339     ) 
    310340 
    311341    IMPLICIT NONE 
     
    314344      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset 
    315345      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     346      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
     347      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    316348      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    317349      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    321353      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled 
    322354      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     355      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr 
    323356      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    324357      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset 
     
    349382      (fieldgroup_id,fieldgroup_hdl) 
    350383      CALL xios(get_fieldgroup_attr_hdl_)   & 
    351       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    352       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    353       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    354       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     384      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     385      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     386      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     387      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     388       ) 
    355389 
    356390  END SUBROUTINE xios(get_fieldgroup_attr) 
    357391 
    358392  SUBROUTINE xios(get_fieldgroup_attr_hdl)  & 
    359     ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    360     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    361     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    362     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     393    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     394    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     395    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     396    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     397     ) 
    363398 
    364399    IMPLICIT NONE 
     
    366401      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset 
    367402      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref 
     403      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
     404      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    368405      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    369406      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    373410      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled 
    374411      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
     412      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr 
    375413      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    376414      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset 
     
    399437 
    400438      CALL xios(get_fieldgroup_attr_hdl_)  & 
    401       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    402       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    403       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    404       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     439      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     440      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     441      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     442      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     443       ) 
    405444 
    406445  END SUBROUTINE xios(get_fieldgroup_attr_hdl) 
    407446 
    408447  SUBROUTINE xios(get_fieldgroup_attr_hdl_)   & 
    409     ( fieldgroup_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    410     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_  & 
    411     , indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_  & 
    412     , standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     448    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_  & 
     449    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     450    , freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_, name_, operation_  & 
     451    , prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_  & 
     452    , unit_, valid_max_, valid_min_ ) 
    413453 
    414454    IMPLICIT NONE 
     
    416456      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: add_offset_ 
    417457      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: axis_ref_ 
     458      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_ 
     459      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
    418460      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    419461      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value_ 
     
    423465      LOGICAL  , OPTIONAL, INTENT(OUT) :: enabled_ 
    424466      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
     467      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: expr_ 
    425468      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref_ 
    426469      TYPE(txios(duration))  , OPTIONAL, INTENT(OUT) :: freq_offset_ 
     
    458501      ENDIF 
    459502 
     503      IF (PRESENT(cell_methods_)) THEN 
     504        CALL cxios_get_fieldgroup_cell_methods & 
     505      (fieldgroup_hdl%daddr, cell_methods_, len(cell_methods_)) 
     506      ENDIF 
     507 
     508      IF (PRESENT(cell_methods_mode_)) THEN 
     509        CALL cxios_get_fieldgroup_cell_methods_mode & 
     510      (fieldgroup_hdl%daddr, cell_methods_mode_, len(cell_methods_mode_)) 
     511      ENDIF 
     512 
    460513      IF (PRESENT(compression_level_)) THEN 
    461514        CALL cxios_get_fieldgroup_compression_level & 
     
    485538      ENDIF 
    486539 
     540      IF (PRESENT(expr_)) THEN 
     541        CALL cxios_get_fieldgroup_expr & 
     542      (fieldgroup_hdl%daddr, expr_, len(expr_)) 
     543      ENDIF 
     544 
    487545      IF (PRESENT(field_ref_)) THEN 
    488546        CALL cxios_get_fieldgroup_field_ref & 
     
    596654 
    597655  SUBROUTINE xios(is_defined_fieldgroup_attr)  & 
    598     ( fieldgroup_id, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    599     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    600     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    601     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     656    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     657    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     658    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     659    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     660     ) 
    602661 
    603662    IMPLICIT NONE 
     
    608667      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    609668      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     669      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods 
     670      LOGICAL(KIND=C_BOOL) :: cell_methods_tmp 
     671      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     672      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
    610673      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    611674      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    618681      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled 
    619682      LOGICAL(KIND=C_BOOL) :: enabled_tmp 
     683      LOGICAL, OPTIONAL, INTENT(OUT) :: expr 
     684      LOGICAL(KIND=C_BOOL) :: expr_tmp 
    620685      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref 
    621686      LOGICAL(KIND=C_BOOL) :: field_ref_tmp 
     
    664729      (fieldgroup_id,fieldgroup_hdl) 
    665730      CALL xios(is_defined_fieldgroup_attr_hdl_)   & 
    666       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    667       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    668       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    669       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     731      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     732      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     733      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     734      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     735       ) 
    670736 
    671737  END SUBROUTINE xios(is_defined_fieldgroup_attr) 
    672738 
    673739  SUBROUTINE xios(is_defined_fieldgroup_attr_hdl)  & 
    674     ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    675     , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    676     , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    677     , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     740    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     741    , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     742    , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     743    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     744     ) 
    678745 
    679746    IMPLICIT NONE 
     
    683750      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref 
    684751      LOGICAL(KIND=C_BOOL) :: axis_ref_tmp 
     752      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods 
     753      LOGICAL(KIND=C_BOOL) :: cell_methods_tmp 
     754      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     755      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
    685756      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    686757      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    693764      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled 
    694765      LOGICAL(KIND=C_BOOL) :: enabled_tmp 
     766      LOGICAL, OPTIONAL, INTENT(OUT) :: expr 
     767      LOGICAL(KIND=C_BOOL) :: expr_tmp 
    695768      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref 
    696769      LOGICAL(KIND=C_BOOL) :: field_ref_tmp 
     
    737810 
    738811      CALL xios(is_defined_fieldgroup_attr_hdl_)  & 
    739       ( fieldgroup_hdl, add_offset, axis_ref, compression_level, default_value, detect_missing_value  & 
    740       , domain_ref, enabled, field_ref, freq_offset, freq_op, grid_path, grid_ref, group_ref, indexed_output  & 
    741       , level, long_name, name, operation, prec, read_access, scalar_ref, scale_factor, standard_name  & 
    742       , ts_enabled, ts_split_freq, unit, valid_max, valid_min ) 
     812      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, compression_level, default_value  & 
     813      , detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op, grid_path  & 
     814      , grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     815      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     816       ) 
    743817 
    744818  END SUBROUTINE xios(is_defined_fieldgroup_attr_hdl) 
    745819 
    746820  SUBROUTINE xios(is_defined_fieldgroup_attr_hdl_)   & 
    747     ( fieldgroup_hdl, add_offset_, axis_ref_, compression_level_, default_value_, detect_missing_value_  & 
    748     , domain_ref_, enabled_, field_ref_, freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_  & 
    749     , indexed_output_, level_, long_name_, name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_  & 
    750     , standard_name_, ts_enabled_, ts_split_freq_, unit_, valid_max_, valid_min_ ) 
     821    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, compression_level_  & 
     822    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     823    , freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_, name_, operation_  & 
     824    , prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_  & 
     825    , unit_, valid_max_, valid_min_ ) 
    751826 
    752827    IMPLICIT NONE 
     
    756831      LOGICAL, OPTIONAL, INTENT(OUT) :: axis_ref_ 
    757832      LOGICAL(KIND=C_BOOL) :: axis_ref__tmp 
     833      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_ 
     834      LOGICAL(KIND=C_BOOL) :: cell_methods__tmp 
     835      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
     836      LOGICAL(KIND=C_BOOL) :: cell_methods_mode__tmp 
    758837      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level_ 
    759838      LOGICAL(KIND=C_BOOL) :: compression_level__tmp 
     
    766845      LOGICAL, OPTIONAL, INTENT(OUT) :: enabled_ 
    767846      LOGICAL(KIND=C_BOOL) :: enabled__tmp 
     847      LOGICAL, OPTIONAL, INTENT(OUT) :: expr_ 
     848      LOGICAL(KIND=C_BOOL) :: expr__tmp 
    768849      LOGICAL, OPTIONAL, INTENT(OUT) :: field_ref_ 
    769850      LOGICAL(KIND=C_BOOL) :: field_ref__tmp 
     
    821902      ENDIF 
    822903 
     904      IF (PRESENT(cell_methods_)) THEN 
     905        cell_methods__tmp = cxios_is_defined_fieldgroup_cell_methods & 
     906      (fieldgroup_hdl%daddr) 
     907        cell_methods_ = cell_methods__tmp 
     908      ENDIF 
     909 
     910      IF (PRESENT(cell_methods_mode_)) THEN 
     911        cell_methods_mode__tmp = cxios_is_defined_fieldgroup_cell_methods_mode & 
     912      (fieldgroup_hdl%daddr) 
     913        cell_methods_mode_ = cell_methods_mode__tmp 
     914      ENDIF 
     915 
    823916      IF (PRESENT(compression_level_)) THEN 
    824917        compression_level__tmp = cxios_is_defined_fieldgroup_compression_level & 
     
    851944      ENDIF 
    852945 
     946      IF (PRESENT(expr_)) THEN 
     947        expr__tmp = cxios_is_defined_fieldgroup_expr & 
     948      (fieldgroup_hdl%daddr) 
     949        expr_ = expr__tmp 
     950      ENDIF 
     951 
    853952      IF (PRESENT(field_ref_)) THEN 
    854953        field_ref__tmp = cxios_is_defined_fieldgroup_field_ref & 
  • XIOS/dev/dev_olga/src/interface/fortran_attr/iinterpolate_domain_attr.F90

    r966 r1021  
    1212 
    1313  SUBROUTINE xios(set_interpolate_domain_attr)  & 
    14     ( interpolate_domain_id, file, order, renormalize ) 
     14    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight ) 
    1515 
    1616    IMPLICIT NONE 
     
    1818      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id 
    1919      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file 
     20      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode 
    2021      INTEGER  , OPTIONAL, INTENT(IN) :: order 
    2122      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize 
    2223      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     24      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename 
     25      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight 
     26      LOGICAL (KIND=C_BOOL) :: write_weight_tmp 
    2327 
    2428      CALL xios(get_interpolate_domain_handle) & 
    2529      (interpolate_domain_id,interpolate_domain_hdl) 
    2630      CALL xios(set_interpolate_domain_attr_hdl_)   & 
    27       ( interpolate_domain_hdl, file, order, renormalize ) 
     31      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    2832 
    2933  END SUBROUTINE xios(set_interpolate_domain_attr) 
    3034 
    3135  SUBROUTINE xios(set_interpolate_domain_attr_hdl)  & 
    32     ( interpolate_domain_hdl, file, order, renormalize ) 
     36    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    3337 
    3438    IMPLICIT NONE 
    3539      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl 
    3640      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file 
     41      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode 
    3742      INTEGER  , OPTIONAL, INTENT(IN) :: order 
    3843      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize 
    3944      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     45      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename 
     46      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight 
     47      LOGICAL (KIND=C_BOOL) :: write_weight_tmp 
    4048 
    4149      CALL xios(set_interpolate_domain_attr_hdl_)  & 
    42       ( interpolate_domain_hdl, file, order, renormalize ) 
     50      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    4351 
    4452  END SUBROUTINE xios(set_interpolate_domain_attr_hdl) 
    4553 
    4654  SUBROUTINE xios(set_interpolate_domain_attr_hdl_)   & 
    47     ( interpolate_domain_hdl, file_, order_, renormalize_ ) 
     55    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  & 
     56     ) 
    4857 
    4958    IMPLICIT NONE 
    5059      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl 
    5160      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: file_ 
     61      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode_ 
    5262      INTEGER  , OPTIONAL, INTENT(IN) :: order_ 
    5363      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize_ 
    5464      LOGICAL (KIND=C_BOOL) :: renormalize__tmp 
     65      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: weight_filename_ 
     66      LOGICAL  , OPTIONAL, INTENT(IN) :: write_weight_ 
     67      LOGICAL (KIND=C_BOOL) :: write_weight__tmp 
    5568 
    5669      IF (PRESENT(file_)) THEN 
    5770        CALL cxios_set_interpolate_domain_file & 
    5871      (interpolate_domain_hdl%daddr, file_, len(file_)) 
     72      ENDIF 
     73 
     74      IF (PRESENT(mode_)) THEN 
     75        CALL cxios_set_interpolate_domain_mode & 
     76      (interpolate_domain_hdl%daddr, mode_, len(mode_)) 
    5977      ENDIF 
    6078 
     
    7088      ENDIF 
    7189 
     90      IF (PRESENT(weight_filename_)) THEN 
     91        CALL cxios_set_interpolate_domain_weight_filename & 
     92      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_)) 
     93      ENDIF 
     94 
     95      IF (PRESENT(write_weight_)) THEN 
     96        write_weight__tmp = write_weight_ 
     97        CALL cxios_set_interpolate_domain_write_weight & 
     98      (interpolate_domain_hdl%daddr, write_weight__tmp) 
     99      ENDIF 
     100 
    72101  END SUBROUTINE xios(set_interpolate_domain_attr_hdl_) 
    73102 
    74103  SUBROUTINE xios(get_interpolate_domain_attr)  & 
    75     ( interpolate_domain_id, file, order, renormalize ) 
     104    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight ) 
    76105 
    77106    IMPLICIT NONE 
     
    79108      CHARACTER(LEN=*), INTENT(IN) ::interpolate_domain_id 
    80109      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file 
     110      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode 
    81111      INTEGER  , OPTIONAL, INTENT(OUT) :: order 
    82112      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize 
    83113      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     114      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename 
     115      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight 
     116      LOGICAL (KIND=C_BOOL) :: write_weight_tmp 
    84117 
    85118      CALL xios(get_interpolate_domain_handle) & 
    86119      (interpolate_domain_id,interpolate_domain_hdl) 
    87120      CALL xios(get_interpolate_domain_attr_hdl_)   & 
    88       ( interpolate_domain_hdl, file, order, renormalize ) 
     121      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    89122 
    90123  END SUBROUTINE xios(get_interpolate_domain_attr) 
    91124 
    92125  SUBROUTINE xios(get_interpolate_domain_attr_hdl)  & 
    93     ( interpolate_domain_hdl, file, order, renormalize ) 
     126    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    94127 
    95128    IMPLICIT NONE 
    96129      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl 
    97130      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file 
     131      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode 
    98132      INTEGER  , OPTIONAL, INTENT(OUT) :: order 
    99133      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize 
    100134      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     135      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename 
     136      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight 
     137      LOGICAL (KIND=C_BOOL) :: write_weight_tmp 
    101138 
    102139      CALL xios(get_interpolate_domain_attr_hdl_)  & 
    103       ( interpolate_domain_hdl, file, order, renormalize ) 
     140      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    104141 
    105142  END SUBROUTINE xios(get_interpolate_domain_attr_hdl) 
    106143 
    107144  SUBROUTINE xios(get_interpolate_domain_attr_hdl_)   & 
    108     ( interpolate_domain_hdl, file_, order_, renormalize_ ) 
     145    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  & 
     146     ) 
    109147 
    110148    IMPLICIT NONE 
    111149      TYPE(txios(interpolate_domain)) , INTENT(IN) :: interpolate_domain_hdl 
    112150      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: file_ 
     151      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode_ 
    113152      INTEGER  , OPTIONAL, INTENT(OUT) :: order_ 
    114153      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize_ 
    115154      LOGICAL (KIND=C_BOOL) :: renormalize__tmp 
     155      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: weight_filename_ 
     156      LOGICAL  , OPTIONAL, INTENT(OUT) :: write_weight_ 
     157      LOGICAL (KIND=C_BOOL) :: write_weight__tmp 
    116158 
    117159      IF (PRESENT(file_)) THEN 
    118160        CALL cxios_get_interpolate_domain_file & 
    119161      (interpolate_domain_hdl%daddr, file_, len(file_)) 
     162      ENDIF 
     163 
     164      IF (PRESENT(mode_)) THEN 
     165        CALL cxios_get_interpolate_domain_mode & 
     166      (interpolate_domain_hdl%daddr, mode_, len(mode_)) 
    120167      ENDIF 
    121168 
     
    131178      ENDIF 
    132179 
     180      IF (PRESENT(weight_filename_)) THEN 
     181        CALL cxios_get_interpolate_domain_weight_filename & 
     182      (interpolate_domain_hdl%daddr, weight_filename_, len(weight_filename_)) 
     183      ENDIF 
     184 
     185      IF (PRESENT(write_weight_)) THEN 
     186        CALL cxios_get_interpolate_domain_write_weight & 
     187      (interpolate_domain_hdl%daddr, write_weight__tmp) 
     188        write_weight_ = write_weight__tmp 
     189      ENDIF 
     190 
    133191  END SUBROUTINE xios(get_interpolate_domain_attr_hdl_) 
    134192 
    135193  SUBROUTINE xios(is_defined_interpolate_domain_attr)  & 
    136     ( interpolate_domain_id, file, order, renormalize ) 
     194    ( interpolate_domain_id, file, mode, order, renormalize, weight_filename, write_weight ) 
    137195 
    138196    IMPLICIT NONE 
     
    141199      LOGICAL, OPTIONAL, INTENT(OUT) :: file 
    142200      LOGICAL(KIND=C_BOOL) :: file_tmp 
     201      LOGICAL, OPTIONAL, INTENT(OUT) :: mode 
     202      LOGICAL(KIND=C_BOOL) :: mode_tmp 
    143203      LOGICAL, OPTIONAL, INTENT(OUT) :: order 
    144204      LOGICAL(KIND=C_BOOL) :: order_tmp 
    145205      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize 
    146206      LOGICAL(KIND=C_BOOL) :: renormalize_tmp 
     207      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename 
     208      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp 
     209      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight 
     210      LOGICAL(KIND=C_BOOL) :: write_weight_tmp 
    147211 
    148212      CALL xios(get_interpolate_domain_handle) & 
    149213      (interpolate_domain_id,interpolate_domain_hdl) 
    150214      CALL xios(is_defined_interpolate_domain_attr_hdl_)   & 
    151       ( interpolate_domain_hdl, file, order, renormalize ) 
     215      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    152216 
    153217  END SUBROUTINE xios(is_defined_interpolate_domain_attr) 
    154218 
    155219  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)  & 
    156     ( interpolate_domain_hdl, file, order, renormalize ) 
     220    ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    157221 
    158222    IMPLICIT NONE 
     
    160224      LOGICAL, OPTIONAL, INTENT(OUT) :: file 
    161225      LOGICAL(KIND=C_BOOL) :: file_tmp 
     226      LOGICAL, OPTIONAL, INTENT(OUT) :: mode 
     227      LOGICAL(KIND=C_BOOL) :: mode_tmp 
    162228      LOGICAL, OPTIONAL, INTENT(OUT) :: order 
    163229      LOGICAL(KIND=C_BOOL) :: order_tmp 
    164230      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize 
    165231      LOGICAL(KIND=C_BOOL) :: renormalize_tmp 
     232      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename 
     233      LOGICAL(KIND=C_BOOL) :: weight_filename_tmp 
     234      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight 
     235      LOGICAL(KIND=C_BOOL) :: write_weight_tmp 
    166236 
    167237      CALL xios(is_defined_interpolate_domain_attr_hdl_)  & 
    168       ( interpolate_domain_hdl, file, order, renormalize ) 
     238      ( interpolate_domain_hdl, file, mode, order, renormalize, weight_filename, write_weight ) 
    169239 
    170240  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl) 
    171241 
    172242  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)   & 
    173     ( interpolate_domain_hdl, file_, order_, renormalize_ ) 
     243    ( interpolate_domain_hdl, file_, mode_, order_, renormalize_, weight_filename_, write_weight_  & 
     244     ) 
    174245 
    175246    IMPLICIT NONE 
     
    177248      LOGICAL, OPTIONAL, INTENT(OUT) :: file_ 
    178249      LOGICAL(KIND=C_BOOL) :: file__tmp 
     250      LOGICAL, OPTIONAL, INTENT(OUT) :: mode_ 
     251      LOGICAL(KIND=C_BOOL) :: mode__tmp 
    179252      LOGICAL, OPTIONAL, INTENT(OUT) :: order_ 
    180253      LOGICAL(KIND=C_BOOL) :: order__tmp 
    181254      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize_ 
    182255      LOGICAL(KIND=C_BOOL) :: renormalize__tmp 
     256      LOGICAL, OPTIONAL, INTENT(OUT) :: weight_filename_ 
     257      LOGICAL(KIND=C_BOOL) :: weight_filename__tmp 
     258      LOGICAL, OPTIONAL, INTENT(OUT) :: write_weight_ 
     259      LOGICAL(KIND=C_BOOL) :: write_weight__tmp 
    183260 
    184261      IF (PRESENT(file_)) THEN 
     
    188265      ENDIF 
    189266 
     267      IF (PRESENT(mode_)) THEN 
     268        mode__tmp = cxios_is_defined_interpolate_domain_mode & 
     269      (interpolate_domain_hdl%daddr) 
     270        mode_ = mode__tmp 
     271      ENDIF 
     272 
    190273      IF (PRESENT(order_)) THEN 
    191274        order__tmp = cxios_is_defined_interpolate_domain_order & 
     
    200283      ENDIF 
    201284 
     285      IF (PRESENT(weight_filename_)) THEN 
     286        weight_filename__tmp = cxios_is_defined_interpolate_domain_weight_filename & 
     287      (interpolate_domain_hdl%daddr) 
     288        weight_filename_ = weight_filename__tmp 
     289      ENDIF 
     290 
     291      IF (PRESENT(write_weight_)) THEN 
     292        write_weight__tmp = cxios_is_defined_interpolate_domain_write_weight & 
     293      (interpolate_domain_hdl%daddr) 
     294        write_weight_ = write_weight__tmp 
     295      ENDIF 
     296 
    202297  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_) 
    203298 
  • XIOS/dev/dev_olga/src/interface/fortran_attr/interpolate_domain_interface_attr.F90

    r891 r1021  
    2929      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
    3030    END FUNCTION cxios_is_defined_interpolate_domain_file 
     31 
     32 
     33    SUBROUTINE cxios_set_interpolate_domain_mode(interpolate_domain_hdl, mode, mode_size) BIND(C) 
     34      USE ISO_C_BINDING 
     35      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     36      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: mode 
     37      INTEGER  (kind = C_INT)     , VALUE        :: mode_size 
     38    END SUBROUTINE cxios_set_interpolate_domain_mode 
     39 
     40    SUBROUTINE cxios_get_interpolate_domain_mode(interpolate_domain_hdl, mode, mode_size) BIND(C) 
     41      USE ISO_C_BINDING 
     42      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     43      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: mode 
     44      INTEGER  (kind = C_INT)     , VALUE        :: mode_size 
     45    END SUBROUTINE cxios_get_interpolate_domain_mode 
     46 
     47    FUNCTION cxios_is_defined_interpolate_domain_mode(interpolate_domain_hdl) BIND(C) 
     48      USE ISO_C_BINDING 
     49      LOGICAL(kind=C_BOOL) :: cxios_is_defined_interpolate_domain_mode 
     50      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     51    END FUNCTION cxios_is_defined_interpolate_domain_mode 
    3152 
    3253 
     
    6889    END FUNCTION cxios_is_defined_interpolate_domain_renormalize 
    6990 
     91 
     92    SUBROUTINE cxios_set_interpolate_domain_weight_filename(interpolate_domain_hdl, weight_filename, weight_filename_size) BIND(C) 
     93      USE ISO_C_BINDING 
     94      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     95      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: weight_filename 
     96      INTEGER  (kind = C_INT)     , VALUE        :: weight_filename_size 
     97    END SUBROUTINE cxios_set_interpolate_domain_weight_filename 
     98 
     99    SUBROUTINE cxios_get_interpolate_domain_weight_filename(interpolate_domain_hdl, weight_filename, weight_filename_size) BIND(C) 
     100      USE ISO_C_BINDING 
     101      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     102      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: weight_filename 
     103      INTEGER  (kind = C_INT)     , VALUE        :: weight_filename_size 
     104    END SUBROUTINE cxios_get_interpolate_domain_weight_filename 
     105 
     106    FUNCTION cxios_is_defined_interpolate_domain_weight_filename(interpolate_domain_hdl) BIND(C) 
     107      USE ISO_C_BINDING 
     108      LOGICAL(kind=C_BOOL) :: cxios_is_defined_interpolate_domain_weight_filename 
     109      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     110    END FUNCTION cxios_is_defined_interpolate_domain_weight_filename 
     111 
     112 
     113    SUBROUTINE cxios_set_interpolate_domain_write_weight(interpolate_domain_hdl, write_weight) BIND(C) 
     114      USE ISO_C_BINDING 
     115      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     116      LOGICAL (KIND=C_BOOL)      , VALUE :: write_weight 
     117    END SUBROUTINE cxios_set_interpolate_domain_write_weight 
     118 
     119    SUBROUTINE cxios_get_interpolate_domain_write_weight(interpolate_domain_hdl, write_weight) BIND(C) 
     120      USE ISO_C_BINDING 
     121      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     122      LOGICAL (KIND=C_BOOL)             :: write_weight 
     123    END SUBROUTINE cxios_get_interpolate_domain_write_weight 
     124 
     125    FUNCTION cxios_is_defined_interpolate_domain_write_weight(interpolate_domain_hdl) BIND(C) 
     126      USE ISO_C_BINDING 
     127      LOGICAL(kind=C_BOOL) :: cxios_is_defined_interpolate_domain_write_weight 
     128      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     129    END FUNCTION cxios_is_defined_interpolate_domain_write_weight 
     130 
    70131  END INTERFACE 
    71132 
Note: See TracChangeset for help on using the changeset viewer.