Ignore:
Timestamp:
07/10/17 18:17:04 (7 years ago)
Author:
yushan
Message:

branch merged with trunk @1200

Location:
XIOS/dev/branch_yushan_merged/src/interface/fortran_attr
Files:
12 edited

Legend:

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

    r1005 r1205  
    9292 
    9393 
     94    SUBROUTINE cxios_set_field_check_if_active(field_hdl, check_if_active) BIND(C) 
     95      USE ISO_C_BINDING 
     96      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     97      LOGICAL (KIND=C_BOOL)      , VALUE :: check_if_active 
     98    END SUBROUTINE cxios_set_field_check_if_active 
     99 
     100    SUBROUTINE cxios_get_field_check_if_active(field_hdl, check_if_active) BIND(C) 
     101      USE ISO_C_BINDING 
     102      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     103      LOGICAL (KIND=C_BOOL)             :: check_if_active 
     104    END SUBROUTINE cxios_get_field_check_if_active 
     105 
     106    FUNCTION cxios_is_defined_field_check_if_active(field_hdl) BIND(C) 
     107      USE ISO_C_BINDING 
     108      LOGICAL(kind=C_BOOL) :: cxios_is_defined_field_check_if_active 
     109      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     110    END FUNCTION cxios_is_defined_field_check_if_active 
     111 
     112 
    94113    SUBROUTINE cxios_set_field_compression_level(field_hdl, compression_level) BIND(C) 
    95114      USE ISO_C_BINDING 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/fieldgroup_interface_attr.F90

    r1005 r1205  
    9292 
    9393 
     94    SUBROUTINE cxios_set_fieldgroup_check_if_active(fieldgroup_hdl, check_if_active) BIND(C) 
     95      USE ISO_C_BINDING 
     96      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     97      LOGICAL (KIND=C_BOOL)      , VALUE :: check_if_active 
     98    END SUBROUTINE cxios_set_fieldgroup_check_if_active 
     99 
     100    SUBROUTINE cxios_get_fieldgroup_check_if_active(fieldgroup_hdl, check_if_active) BIND(C) 
     101      USE ISO_C_BINDING 
     102      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     103      LOGICAL (KIND=C_BOOL)             :: check_if_active 
     104    END SUBROUTINE cxios_get_fieldgroup_check_if_active 
     105 
     106    FUNCTION cxios_is_defined_fieldgroup_check_if_active(fieldgroup_hdl) BIND(C) 
     107      USE ISO_C_BINDING 
     108      LOGICAL(kind=C_BOOL) :: cxios_is_defined_fieldgroup_check_if_active 
     109      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     110    END FUNCTION cxios_is_defined_fieldgroup_check_if_active 
     111 
     112 
    94113    SUBROUTINE cxios_set_fieldgroup_compression_level(fieldgroup_hdl, compression_level) BIND(C) 
    95114      USE ISO_C_BINDING 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/file_interface_attr.F90

    r1052 r1205  
    6969 
    7070 
     71    SUBROUTINE cxios_set_file_convention_str(file_hdl, convention_str, convention_str_size) BIND(C) 
     72      USE ISO_C_BINDING 
     73      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     74      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: convention_str 
     75      INTEGER  (kind = C_INT)     , VALUE        :: convention_str_size 
     76    END SUBROUTINE cxios_set_file_convention_str 
     77 
     78    SUBROUTINE cxios_get_file_convention_str(file_hdl, convention_str, convention_str_size) BIND(C) 
     79      USE ISO_C_BINDING 
     80      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     81      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: convention_str 
     82      INTEGER  (kind = C_INT)     , VALUE        :: convention_str_size 
     83    END SUBROUTINE cxios_get_file_convention_str 
     84 
     85    FUNCTION cxios_is_defined_file_convention_str(file_hdl) BIND(C) 
     86      USE ISO_C_BINDING 
     87      LOGICAL(kind=C_BOOL) :: cxios_is_defined_file_convention_str 
     88      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     89    END FUNCTION cxios_is_defined_file_convention_str 
     90 
     91 
    7192    SUBROUTINE cxios_set_file_cyclic(file_hdl, cyclic) BIND(C) 
    7293      USE ISO_C_BINDING 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/filegroup_interface_attr.F90

    r1052 r1205  
    6969 
    7070 
     71    SUBROUTINE cxios_set_filegroup_convention_str(filegroup_hdl, convention_str, convention_str_size) BIND(C) 
     72      USE ISO_C_BINDING 
     73      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     74      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: convention_str 
     75      INTEGER  (kind = C_INT)     , VALUE        :: convention_str_size 
     76    END SUBROUTINE cxios_set_filegroup_convention_str 
     77 
     78    SUBROUTINE cxios_get_filegroup_convention_str(filegroup_hdl, convention_str, convention_str_size) BIND(C) 
     79      USE ISO_C_BINDING 
     80      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     81      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: convention_str 
     82      INTEGER  (kind = C_INT)     , VALUE        :: convention_str_size 
     83    END SUBROUTINE cxios_get_filegroup_convention_str 
     84 
     85    FUNCTION cxios_is_defined_filegroup_convention_str(filegroup_hdl) BIND(C) 
     86      USE ISO_C_BINDING 
     87      LOGICAL(kind=C_BOOL) :: cxios_is_defined_filegroup_convention_str 
     88      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     89    END FUNCTION cxios_is_defined_filegroup_convention_str 
     90 
     91 
    7192    SUBROUTINE cxios_set_filegroup_cyclic(filegroup_hdl, cyclic) BIND(C) 
    7293      USE ISO_C_BINDING 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/ifield_attr.F90

    r1005 r1205  
    1212 
    1313  SUBROUTINE xios(set_field_attr)  & 
    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 ) 
     14    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     15    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     16    , grid_path, grid_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 
     
    2425      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
    2526      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
     27      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active 
     28      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    2629      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2730      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    5962      (field_id,field_hdl) 
    6063      CALL xios(set_field_attr_hdl_)   & 
    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 ) 
     64      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     65      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     66      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     67      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     68       ) 
    6569 
    6670  END SUBROUTINE xios(set_field_attr) 
    6771 
    6872  SUBROUTINE xios(set_field_attr_hdl)  & 
    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 ) 
     73    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     74    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     75    , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     76    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     77     ) 
    7378 
    7479    IMPLICIT NONE 
     
    7883      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
    7984      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
     85      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active 
     86      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    8087      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    8188      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    111118 
    112119      CALL xios(set_field_attr_hdl_)  & 
    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 ) 
     120      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     121      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     122      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     123      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     124       ) 
    117125 
    118126  END SUBROUTINE xios(set_field_attr_hdl) 
    119127 
    120128  SUBROUTINE xios(set_field_attr_hdl_)   & 
    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     ) 
     129    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_, compression_level_  & 
     130    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     131    , freq_op_, grid_path_, grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_  & 
     132    , read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_  & 
     133    , valid_max_, valid_min_ ) 
    126134 
    127135    IMPLICIT NONE 
     
    131139      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_ 
    132140      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode_ 
     141      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active_ 
     142      LOGICAL (KIND=C_BOOL) :: check_if_active__tmp 
    133143      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    134144      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value_ 
     
    183193      ENDIF 
    184194 
     195      IF (PRESENT(check_if_active_)) THEN 
     196        check_if_active__tmp = check_if_active_ 
     197        CALL cxios_set_field_check_if_active & 
     198      (field_hdl%daddr, check_if_active__tmp) 
     199      ENDIF 
     200 
    185201      IF (PRESENT(compression_level_)) THEN 
    186202        CALL cxios_set_field_compression_level & 
     
    321337 
    322338  SUBROUTINE xios(get_field_attr)  & 
    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 ) 
     339    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     340    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     341    , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     342    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     343     ) 
    327344 
    328345    IMPLICIT NONE 
     
    333350      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
    334351      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     352      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active 
     353      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    335354      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    336355      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    368387      (field_id,field_hdl) 
    369388      CALL xios(get_field_attr_hdl_)   & 
    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 ) 
     389      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     390      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     391      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     392      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     393       ) 
    374394 
    375395  END SUBROUTINE xios(get_field_attr) 
    376396 
    377397  SUBROUTINE xios(get_field_attr_hdl)  & 
    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 ) 
     398    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     399    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     400    , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     401    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     402     ) 
    382403 
    383404    IMPLICIT NONE 
     
    387408      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
    388409      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     410      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active 
     411      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    389412      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    390413      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    420443 
    421444      CALL xios(get_field_attr_hdl_)  & 
    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 ) 
     445      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     446      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     447      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     448      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     449       ) 
    426450 
    427451  END SUBROUTINE xios(get_field_attr_hdl) 
    428452 
    429453  SUBROUTINE xios(get_field_attr_hdl_)   & 
    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     ) 
     454    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_, compression_level_  & 
     455    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     456    , freq_op_, grid_path_, grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_  & 
     457    , read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_  & 
     458    , valid_max_, valid_min_ ) 
    435459 
    436460    IMPLICIT NONE 
     
    440464      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_ 
    441465      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
     466      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active_ 
     467      LOGICAL (KIND=C_BOOL) :: check_if_active__tmp 
    442468      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    443469      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value_ 
     
    492518      ENDIF 
    493519 
     520      IF (PRESENT(check_if_active_)) THEN 
     521        CALL cxios_get_field_check_if_active & 
     522      (field_hdl%daddr, check_if_active__tmp) 
     523        check_if_active_ = check_if_active__tmp 
     524      ENDIF 
     525 
    494526      IF (PRESENT(compression_level_)) THEN 
    495527        CALL cxios_get_field_compression_level & 
     
    630662 
    631663  SUBROUTINE xios(is_defined_field_attr)  & 
    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 ) 
     664    ( field_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     665    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     666    , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     667    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     668     ) 
    636669 
    637670    IMPLICIT NONE 
     
    646679      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    647680      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
     681      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active 
     682      LOGICAL(KIND=C_BOOL) :: check_if_active_tmp 
    648683      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    649684      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    702737      (field_id,field_hdl) 
    703738      CALL xios(is_defined_field_attr_hdl_)   & 
    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 ) 
     739      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     740      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     741      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     742      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     743       ) 
    708744 
    709745  END SUBROUTINE xios(is_defined_field_attr) 
    710746 
    711747  SUBROUTINE xios(is_defined_field_attr_hdl)  & 
    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 ) 
     748    ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     749    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     750    , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     751    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     752     ) 
    716753 
    717754    IMPLICIT NONE 
     
    725762      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    726763      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
     764      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active 
     765      LOGICAL(KIND=C_BOOL) :: check_if_active_tmp 
    727766      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    728767      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    779818 
    780819      CALL xios(is_defined_field_attr_hdl_)  & 
    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 ) 
     820      ( field_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     821      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     822      , grid_path, grid_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
     823      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
     824       ) 
    785825 
    786826  END SUBROUTINE xios(is_defined_field_attr_hdl) 
    787827 
    788828  SUBROUTINE xios(is_defined_field_attr_hdl_)   & 
    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     ) 
     829    ( field_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_, compression_level_  & 
     830    , default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_, freq_offset_  & 
     831    , freq_op_, grid_path_, grid_ref_, indexed_output_, level_, long_name_, name_, operation_, prec_  & 
     832    , read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_, ts_split_freq_, unit_  & 
     833    , valid_max_, valid_min_ ) 
    794834 
    795835    IMPLICIT NONE 
     
    803843      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
    804844      LOGICAL(KIND=C_BOOL) :: cell_methods_mode__tmp 
     845      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active_ 
     846      LOGICAL(KIND=C_BOOL) :: check_if_active__tmp 
    805847      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level_ 
    806848      LOGICAL(KIND=C_BOOL) :: compression_level__tmp 
     
    880922      ENDIF 
    881923 
     924      IF (PRESENT(check_if_active_)) THEN 
     925        check_if_active__tmp = cxios_is_defined_field_check_if_active & 
     926      (field_hdl%daddr) 
     927        check_if_active_ = check_if_active__tmp 
     928      ENDIF 
     929 
    882930      IF (PRESENT(compression_level_)) THEN 
    883931        compression_level__tmp = cxios_is_defined_field_compression_level & 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/ifieldgroup_attr.F90

    r1005 r1205  
    1212 
    1313  SUBROUTINE xios(set_fieldgroup_attr)  & 
    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  & 
     14    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     15    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     16    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    1717    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    1818     ) 
     
    2525      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
    2626      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
     27      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active 
     28      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    2729      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2830      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    6163      (fieldgroup_id,fieldgroup_hdl) 
    6264      CALL xios(set_fieldgroup_attr_hdl_)   & 
    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  & 
     65      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     66      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     67      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    6668      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    6769       ) 
     
    7072 
    7173  SUBROUTINE xios(set_fieldgroup_attr_hdl)  & 
    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  & 
     74    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     75    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     76    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    7577    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    7678     ) 
     
    8284      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods 
    8385      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode 
     86      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active 
     87      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    8488      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    8589      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value 
     
    116120 
    117121      CALL xios(set_fieldgroup_attr_hdl_)  & 
    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  & 
     122      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     123      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     124      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    121125      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    122126       ) 
     
    125129 
    126130  SUBROUTINE xios(set_fieldgroup_attr_hdl_)   & 
    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_ ) 
     131    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_  & 
     132    , compression_level_, default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_  & 
     133    , freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_  & 
     134    , name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_  & 
     135    , ts_split_freq_, unit_, valid_max_, valid_min_ ) 
    132136 
    133137    IMPLICIT NONE 
     
    137141      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_ 
    138142      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: cell_methods_mode_ 
     143      LOGICAL  , OPTIONAL, INTENT(IN) :: check_if_active_ 
     144      LOGICAL (KIND=C_BOOL) :: check_if_active__tmp 
    139145      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    140146      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: default_value_ 
     
    190196      ENDIF 
    191197 
     198      IF (PRESENT(check_if_active_)) THEN 
     199        check_if_active__tmp = check_if_active_ 
     200        CALL cxios_set_fieldgroup_check_if_active & 
     201      (fieldgroup_hdl%daddr, check_if_active__tmp) 
     202      ENDIF 
     203 
    192204      IF (PRESENT(compression_level_)) THEN 
    193205        CALL cxios_set_fieldgroup_compression_level & 
     
    333345 
    334346  SUBROUTINE xios(get_fieldgroup_attr)  & 
    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  & 
     347    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     348    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     349    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    338350    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    339351     ) 
     
    346358      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
    347359      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     360      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active 
     361      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    348362      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    349363      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    382396      (fieldgroup_id,fieldgroup_hdl) 
    383397      CALL xios(get_fieldgroup_attr_hdl_)   & 
    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  & 
     398      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     399      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     400      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    387401      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    388402       ) 
     
    391405 
    392406  SUBROUTINE xios(get_fieldgroup_attr_hdl)  & 
    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  & 
     407    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     408    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     409    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    396410    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    397411     ) 
     
    403417      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods 
    404418      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode 
     419      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active 
     420      LOGICAL (KIND=C_BOOL) :: check_if_active_tmp 
    405421      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    406422      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value 
     
    437453 
    438454      CALL xios(get_fieldgroup_attr_hdl_)  & 
    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  & 
     455      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     456      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     457      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    442458      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    443459       ) 
     
    446462 
    447463  SUBROUTINE xios(get_fieldgroup_attr_hdl_)   & 
    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_ ) 
     464    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_  & 
     465    , compression_level_, default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_  & 
     466    , freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_  & 
     467    , name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_  & 
     468    , ts_split_freq_, unit_, valid_max_, valid_min_ ) 
    453469 
    454470    IMPLICIT NONE 
     
    458474      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_ 
    459475      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
     476      LOGICAL  , OPTIONAL, INTENT(OUT) :: check_if_active_ 
     477      LOGICAL (KIND=C_BOOL) :: check_if_active__tmp 
    460478      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    461479      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: default_value_ 
     
    511529      ENDIF 
    512530 
     531      IF (PRESENT(check_if_active_)) THEN 
     532        CALL cxios_get_fieldgroup_check_if_active & 
     533      (fieldgroup_hdl%daddr, check_if_active__tmp) 
     534        check_if_active_ = check_if_active__tmp 
     535      ENDIF 
     536 
    513537      IF (PRESENT(compression_level_)) THEN 
    514538        CALL cxios_get_fieldgroup_compression_level & 
     
    654678 
    655679  SUBROUTINE xios(is_defined_fieldgroup_attr)  & 
    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  & 
     680    ( fieldgroup_id, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     681    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     682    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    659683    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    660684     ) 
     
    671695      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    672696      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
     697      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active 
     698      LOGICAL(KIND=C_BOOL) :: check_if_active_tmp 
    673699      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    674700      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    729755      (fieldgroup_id,fieldgroup_hdl) 
    730756      CALL xios(is_defined_fieldgroup_attr_hdl_)   & 
    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  & 
     757      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     758      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     759      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    734760      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    735761       ) 
     
    738764 
    739765  SUBROUTINE xios(is_defined_fieldgroup_attr_hdl)  & 
    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  & 
     766    ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     767    , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     768    , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    743769    , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    744770     ) 
     
    754780      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode 
    755781      LOGICAL(KIND=C_BOOL) :: cell_methods_mode_tmp 
     782      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active 
     783      LOGICAL(KIND=C_BOOL) :: check_if_active_tmp 
    756784      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level 
    757785      LOGICAL(KIND=C_BOOL) :: compression_level_tmp 
     
    810838 
    811839      CALL xios(is_defined_fieldgroup_attr_hdl_)  & 
    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  & 
     840      ( fieldgroup_hdl, add_offset, axis_ref, cell_methods, cell_methods_mode, check_if_active, compression_level  & 
     841      , default_value, detect_missing_value, domain_ref, enabled, expr, field_ref, freq_offset, freq_op  & 
     842      , grid_path, grid_ref, group_ref, indexed_output, level, long_name, name, operation, prec, read_access  & 
    815843      , scalar_ref, scale_factor, standard_name, ts_enabled, ts_split_freq, unit, valid_max, valid_min  & 
    816844       ) 
     
    819847 
    820848  SUBROUTINE xios(is_defined_fieldgroup_attr_hdl_)   & 
    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_ ) 
     849    ( fieldgroup_hdl, add_offset_, axis_ref_, cell_methods_, cell_methods_mode_, check_if_active_  & 
     850    , compression_level_, default_value_, detect_missing_value_, domain_ref_, enabled_, expr_, field_ref_  & 
     851    , freq_offset_, freq_op_, grid_path_, grid_ref_, group_ref_, indexed_output_, level_, long_name_  & 
     852    , name_, operation_, prec_, read_access_, scalar_ref_, scale_factor_, standard_name_, ts_enabled_  & 
     853    , ts_split_freq_, unit_, valid_max_, valid_min_ ) 
    826854 
    827855    IMPLICIT NONE 
     
    835863      LOGICAL, OPTIONAL, INTENT(OUT) :: cell_methods_mode_ 
    836864      LOGICAL(KIND=C_BOOL) :: cell_methods_mode__tmp 
     865      LOGICAL, OPTIONAL, INTENT(OUT) :: check_if_active_ 
     866      LOGICAL(KIND=C_BOOL) :: check_if_active__tmp 
    837867      LOGICAL, OPTIONAL, INTENT(OUT) :: compression_level_ 
    838868      LOGICAL(KIND=C_BOOL) :: compression_level__tmp 
     
    914944      ENDIF 
    915945 
     946      IF (PRESENT(check_if_active_)) THEN 
     947        check_if_active__tmp = cxios_is_defined_fieldgroup_check_if_active & 
     948      (fieldgroup_hdl%daddr) 
     949        check_if_active_ = check_if_active__tmp 
     950      ENDIF 
     951 
    916952      IF (PRESENT(compression_level_)) THEN 
    917953        compression_level__tmp = cxios_is_defined_fieldgroup_compression_level & 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/ifile_attr.F90

    r1052 r1205  
    1212 
    1313  SUBROUTINE xios(set_file_attr)  & 
    14     ( file_id, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    15     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    16     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    17     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     14    ( file_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     15    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     16    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     17    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    1818 
    1919    IMPLICIT NONE 
     
    2424      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2525      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention 
     26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str 
    2627      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic 
    2728      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    5556      (file_id,file_hdl) 
    5657      CALL xios(set_file_attr_hdl_)   & 
    57       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    58       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    59       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    60       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     58      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     59      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     60      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     61      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    6162 
    6263  END SUBROUTINE xios(set_file_attr) 
    6364 
    6465  SUBROUTINE xios(set_file_attr_hdl)  & 
    65     ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    66     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    67     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    68     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     66    ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     67    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     68    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     69    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    6970 
    7071    IMPLICIT NONE 
     
    7475      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    7576      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention 
     77      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str 
    7678      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic 
    7779      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    103105 
    104106      CALL xios(set_file_attr_hdl_)  & 
    105       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    106       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    107       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    108       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     107      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     108      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     109      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     110      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    109111 
    110112  END SUBROUTINE xios(set_file_attr_hdl) 
    111113 
    112114  SUBROUTINE xios(set_file_attr_hdl_)   & 
    113     ( file_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    114     , min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_, record_offset_  & 
    115     , split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_, time_stamp_format_  & 
    116     , time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_, uuid_name_ ) 
     115    ( file_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     116    , enabled_, format_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
     117    , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     118    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
     119    , uuid_name_ ) 
    117120 
    118121    IMPLICIT NONE 
     
    122125      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    123126      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_ 
     127      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str_ 
    124128      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic_ 
    125129      LOGICAL (KIND=C_BOOL) :: cyclic__tmp 
     
    166170      ENDIF 
    167171 
     172      IF (PRESENT(convention_str_)) THEN 
     173        CALL cxios_set_file_convention_str & 
     174      (file_hdl%daddr, convention_str_, len(convention_str_)) 
     175      ENDIF 
     176 
    168177      IF (PRESENT(cyclic_)) THEN 
    169178        cyclic__tmp = cyclic_ 
     
    296305 
    297306  SUBROUTINE xios(get_file_attr)  & 
    298     ( file_id, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    299     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    300     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    301     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     307    ( file_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     308    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     309    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     310    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    302311 
    303312    IMPLICIT NONE 
     
    308317      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    309318      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention 
     319      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str 
    310320      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic 
    311321      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    339349      (file_id,file_hdl) 
    340350      CALL xios(get_file_attr_hdl_)   & 
    341       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    342       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    343       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    344       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     351      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     352      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     353      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     354      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    345355 
    346356  END SUBROUTINE xios(get_file_attr) 
    347357 
    348358  SUBROUTINE xios(get_file_attr_hdl)  & 
    349     ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    350     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    351     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    352     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     359    ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     360    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     361    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     362    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    353363 
    354364    IMPLICIT NONE 
     
    358368      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    359369      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention 
     370      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str 
    360371      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic 
    361372      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    387398 
    388399      CALL xios(get_file_attr_hdl_)  & 
    389       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    390       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    391       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    392       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     400      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     401      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     402      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     403      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    393404 
    394405  END SUBROUTINE xios(get_file_attr_hdl) 
    395406 
    396407  SUBROUTINE xios(get_file_attr_hdl_)   & 
    397     ( file_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    398     , min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_, record_offset_  & 
    399     , split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_, time_stamp_format_  & 
    400     , time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_, uuid_name_ ) 
     408    ( file_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     409    , enabled_, format_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
     410    , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     411    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
     412    , uuid_name_ ) 
    401413 
    402414    IMPLICIT NONE 
     
    406418      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    407419      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_ 
     420      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str_ 
    408421      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic_ 
    409422      LOGICAL (KIND=C_BOOL) :: cyclic__tmp 
     
    450463      ENDIF 
    451464 
     465      IF (PRESENT(convention_str_)) THEN 
     466        CALL cxios_get_file_convention_str & 
     467      (file_hdl%daddr, convention_str_, len(convention_str_)) 
     468      ENDIF 
     469 
    452470      IF (PRESENT(cyclic_)) THEN 
    453471        CALL cxios_get_file_cyclic & 
     
    580598 
    581599  SUBROUTINE xios(is_defined_file_attr)  & 
    582     ( file_id, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    583     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    584     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    585     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     600    ( file_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     601    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     602    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     603    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    586604 
    587605    IMPLICIT NONE 
     
    594612      LOGICAL, OPTIONAL, INTENT(OUT) :: convention 
    595613      LOGICAL(KIND=C_BOOL) :: convention_tmp 
     614      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str 
     615      LOGICAL(KIND=C_BOOL) :: convention_str_tmp 
    596616      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic 
    597617      LOGICAL(KIND=C_BOOL) :: cyclic_tmp 
     
    648668      (file_id,file_hdl) 
    649669      CALL xios(is_defined_file_attr_hdl_)   & 
    650       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    651       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    652       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    653       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     670      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     671      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     672      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     673      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    654674 
    655675  END SUBROUTINE xios(is_defined_file_attr) 
    656676 
    657677  SUBROUTINE xios(is_defined_file_attr_hdl)  & 
    658     ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    659     , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    660     , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    661     , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     678    ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     679    , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     680    , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     681    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    662682 
    663683    IMPLICIT NONE 
     
    669689      LOGICAL, OPTIONAL, INTENT(OUT) :: convention 
    670690      LOGICAL(KIND=C_BOOL) :: convention_tmp 
     691      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str 
     692      LOGICAL(KIND=C_BOOL) :: convention_str_tmp 
    671693      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic 
    672694      LOGICAL(KIND=C_BOOL) :: cyclic_tmp 
     
    721743 
    722744      CALL xios(is_defined_file_attr_hdl_)  & 
    723       ( file_hdl, append, compression_level, convention, cyclic, description, enabled, format, min_digits  & 
    724       , mode, name, name_suffix, output_freq, output_level, par_access, record_offset, split_freq  & 
    725       , split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format, time_stamp_name  & 
    726       , time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     745      ( file_hdl, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     746      , format, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
     747      , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     748      , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    727749 
    728750  END SUBROUTINE xios(is_defined_file_attr_hdl) 
    729751 
    730752  SUBROUTINE xios(is_defined_file_attr_hdl_)   & 
    731     ( file_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    732     , min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_, record_offset_  & 
    733     , split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_, time_stamp_format_  & 
    734     , time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_, uuid_name_ ) 
     753    ( file_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     754    , enabled_, format_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
     755    , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     756    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
     757    , uuid_name_ ) 
    735758 
    736759    IMPLICIT NONE 
     
    742765      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_ 
    743766      LOGICAL(KIND=C_BOOL) :: convention__tmp 
     767      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str_ 
     768      LOGICAL(KIND=C_BOOL) :: convention_str__tmp 
    744769      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic_ 
    745770      LOGICAL(KIND=C_BOOL) :: cyclic__tmp 
     
    811836      ENDIF 
    812837 
     838      IF (PRESENT(convention_str_)) THEN 
     839        convention_str__tmp = cxios_is_defined_file_convention_str & 
     840      (file_hdl%daddr) 
     841        convention_str_ = convention_str__tmp 
     842      ENDIF 
     843 
    813844      IF (PRESENT(cyclic_)) THEN 
    814845        cyclic__tmp = cxios_is_defined_file_cyclic & 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/ifilegroup_attr.F90

    r1052 r1205  
    1212 
    1313  SUBROUTINE xios(set_filegroup_attr)  & 
    14     ( filegroup_id, append, compression_level, convention, cyclic, description, enabled, format  & 
    15     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    16     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     14    ( filegroup_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     15    , format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access  & 
     16    , record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    1717    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    1818 
     
    2424      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    2525      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention 
     26      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str 
    2627      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic 
    2728      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    5657      (filegroup_id,filegroup_hdl) 
    5758      CALL xios(set_filegroup_attr_hdl_)   & 
    58       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    59       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    60       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    61       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     59      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     60      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     61      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     62      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     63       ) 
    6264 
    6365  END SUBROUTINE xios(set_filegroup_attr) 
    6466 
    6567  SUBROUTINE xios(set_filegroup_attr_hdl)  & 
    66     ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    67     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    68     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    69     , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     68    ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     69    , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     70    , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     71    , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     72     ) 
    7073 
    7174    IMPLICIT NONE 
     
    7578      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level 
    7679      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention 
     80      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str 
    7781      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic 
    7882      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    105109 
    106110      CALL xios(set_filegroup_attr_hdl_)  & 
    107       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    108       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    109       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    110       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     111      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     112      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     113      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     114      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     115       ) 
    111116 
    112117  END SUBROUTINE xios(set_filegroup_attr_hdl) 
    113118 
    114119  SUBROUTINE xios(set_filegroup_attr_hdl_)   & 
    115     ( filegroup_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    116     , group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
    117     , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     120    ( filegroup_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     121    , enabled_, format_, group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_  & 
     122    , par_access_, record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
    118123    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
    119124    , uuid_name_ ) 
     
    125130      INTEGER  , OPTIONAL, INTENT(IN) :: compression_level_ 
    126131      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_ 
     132      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: convention_str_ 
    127133      LOGICAL  , OPTIONAL, INTENT(IN) :: cyclic_ 
    128134      LOGICAL (KIND=C_BOOL) :: cyclic__tmp 
     
    170176      ENDIF 
    171177 
     178      IF (PRESENT(convention_str_)) THEN 
     179        CALL cxios_set_filegroup_convention_str & 
     180      (filegroup_hdl%daddr, convention_str_, len(convention_str_)) 
     181      ENDIF 
     182 
    172183      IF (PRESENT(cyclic_)) THEN 
    173184        cyclic__tmp = cyclic_ 
     
    305316 
    306317  SUBROUTINE xios(get_filegroup_attr)  & 
    307     ( filegroup_id, append, compression_level, convention, cyclic, description, enabled, format  & 
    308     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    309     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     318    ( filegroup_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     319    , format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access  & 
     320    , record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    310321    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    311322 
     
    317328      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    318329      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention 
     330      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str 
    319331      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic 
    320332      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    349361      (filegroup_id,filegroup_hdl) 
    350362      CALL xios(get_filegroup_attr_hdl_)   & 
    351       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    352       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    353       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    354       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     363      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     364      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     365      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     366      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     367       ) 
    355368 
    356369  END SUBROUTINE xios(get_filegroup_attr) 
    357370 
    358371  SUBROUTINE xios(get_filegroup_attr_hdl)  & 
    359     ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    360     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    361     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    362     , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     372    ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     373    , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     374    , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     375    , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     376     ) 
    363377 
    364378    IMPLICIT NONE 
     
    368382      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level 
    369383      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention 
     384      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str 
    370385      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic 
    371386      LOGICAL (KIND=C_BOOL) :: cyclic_tmp 
     
    398413 
    399414      CALL xios(get_filegroup_attr_hdl_)  & 
    400       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    401       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    402       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    403       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     415      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     416      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     417      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     418      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     419       ) 
    404420 
    405421  END SUBROUTINE xios(get_filegroup_attr_hdl) 
    406422 
    407423  SUBROUTINE xios(get_filegroup_attr_hdl_)   & 
    408     ( filegroup_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    409     , group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
    410     , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     424    ( filegroup_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     425    , enabled_, format_, group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_  & 
     426    , par_access_, record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
    411427    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
    412428    , uuid_name_ ) 
     
    418434      INTEGER  , OPTIONAL, INTENT(OUT) :: compression_level_ 
    419435      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_ 
     436      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: convention_str_ 
    420437      LOGICAL  , OPTIONAL, INTENT(OUT) :: cyclic_ 
    421438      LOGICAL (KIND=C_BOOL) :: cyclic__tmp 
     
    463480      ENDIF 
    464481 
     482      IF (PRESENT(convention_str_)) THEN 
     483        CALL cxios_get_filegroup_convention_str & 
     484      (filegroup_hdl%daddr, convention_str_, len(convention_str_)) 
     485      ENDIF 
     486 
    465487      IF (PRESENT(cyclic_)) THEN 
    466488        CALL cxios_get_filegroup_cyclic & 
     
    598620 
    599621  SUBROUTINE xios(is_defined_filegroup_attr)  & 
    600     ( filegroup_id, append, compression_level, convention, cyclic, description, enabled, format  & 
    601     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    602     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
     622    ( filegroup_id, append, compression_level, convention, convention_str, cyclic, description, enabled  & 
     623    , format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access  & 
     624    , record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    603625    , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
    604626 
     
    612634      LOGICAL, OPTIONAL, INTENT(OUT) :: convention 
    613635      LOGICAL(KIND=C_BOOL) :: convention_tmp 
     636      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str 
     637      LOGICAL(KIND=C_BOOL) :: convention_str_tmp 
    614638      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic 
    615639      LOGICAL(KIND=C_BOOL) :: cyclic_tmp 
     
    668692      (filegroup_id,filegroup_hdl) 
    669693      CALL xios(is_defined_filegroup_attr_hdl_)   & 
    670       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    671       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    672       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    673       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     694      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     695      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     696      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     697      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     698       ) 
    674699 
    675700  END SUBROUTINE xios(is_defined_filegroup_attr) 
    676701 
    677702  SUBROUTINE xios(is_defined_filegroup_attr_hdl)  & 
    678     ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    679     , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    680     , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    681     , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     703    ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     704    , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     705    , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     706    , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     707     ) 
    682708 
    683709    IMPLICIT NONE 
     
    689715      LOGICAL, OPTIONAL, INTENT(OUT) :: convention 
    690716      LOGICAL(KIND=C_BOOL) :: convention_tmp 
     717      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str 
     718      LOGICAL(KIND=C_BOOL) :: convention_str_tmp 
    691719      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic 
    692720      LOGICAL(KIND=C_BOOL) :: cyclic_tmp 
     
    743771 
    744772      CALL xios(is_defined_filegroup_attr_hdl_)  & 
    745       ( filegroup_hdl, append, compression_level, convention, cyclic, description, enabled, format  & 
    746       , group_ref, min_digits, mode, name, name_suffix, output_freq, output_level, par_access, record_offset  & 
    747       , split_freq, split_freq_format, sync_freq, time_counter, time_counter_name, time_stamp_format  & 
    748       , time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name ) 
     773      ( filegroup_hdl, append, compression_level, convention, convention_str, cyclic, description  & 
     774      , enabled, format, group_ref, min_digits, mode, name, name_suffix, output_freq, output_level  & 
     775      , par_access, record_offset, split_freq, split_freq_format, sync_freq, time_counter, time_counter_name  & 
     776      , time_stamp_format, time_stamp_name, time_units, timeseries, ts_prefix, type, uuid_format, uuid_name  & 
     777       ) 
    749778 
    750779  END SUBROUTINE xios(is_defined_filegroup_attr_hdl) 
    751780 
    752781  SUBROUTINE xios(is_defined_filegroup_attr_hdl_)   & 
    753     ( filegroup_hdl, append_, compression_level_, convention_, cyclic_, description_, enabled_, format_  & 
    754     , group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_, par_access_  & 
    755     , record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
     782    ( filegroup_hdl, append_, compression_level_, convention_, convention_str_, cyclic_, description_  & 
     783    , enabled_, format_, group_ref_, min_digits_, mode_, name_, name_suffix_, output_freq_, output_level_  & 
     784    , par_access_, record_offset_, split_freq_, split_freq_format_, sync_freq_, time_counter_, time_counter_name_  & 
    756785    , time_stamp_format_, time_stamp_name_, time_units_, timeseries_, ts_prefix_, type_, uuid_format_  & 
    757786    , uuid_name_ ) 
     
    765794      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_ 
    766795      LOGICAL(KIND=C_BOOL) :: convention__tmp 
     796      LOGICAL, OPTIONAL, INTENT(OUT) :: convention_str_ 
     797      LOGICAL(KIND=C_BOOL) :: convention_str__tmp 
    767798      LOGICAL, OPTIONAL, INTENT(OUT) :: cyclic_ 
    768799      LOGICAL(KIND=C_BOOL) :: cyclic__tmp 
     
    836867      ENDIF 
    837868 
     869      IF (PRESENT(convention_str_)) THEN 
     870        convention_str__tmp = cxios_is_defined_filegroup_convention_str & 
     871      (filegroup_hdl%daddr) 
     872        convention_str_ = convention_str__tmp 
     873      ENDIF 
     874 
    838875      IF (PRESENT(cyclic_)) THEN 
    839876        cyclic__tmp = cxios_is_defined_filegroup_cyclic & 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/iinterpolate_domain_attr.F90

    r1040 r1205  
    1212 
    1313  SUBROUTINE xios(set_interpolate_domain_attr)  & 
    14     ( interpolate_domain_id, mode, order, renormalize, weight_filename, write_weight ) 
     14    ( interpolate_domain_id, mode, order, quantity, renormalize, weight_filename, write_weight ) 
    1515 
    1616    IMPLICIT NONE 
     
    1919      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode 
    2020      INTEGER  , OPTIONAL, INTENT(IN) :: order 
     21      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity 
     22      LOGICAL (KIND=C_BOOL) :: quantity_tmp 
    2123      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize 
    2224      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     
    2830      (interpolate_domain_id,interpolate_domain_hdl) 
    2931      CALL xios(set_interpolate_domain_attr_hdl_)   & 
    30       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     32      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     33       ) 
    3134 
    3235  END SUBROUTINE xios(set_interpolate_domain_attr) 
    3336 
    3437  SUBROUTINE xios(set_interpolate_domain_attr_hdl)  & 
    35     ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     38    ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     39     ) 
    3640 
    3741    IMPLICIT NONE 
     
    3943      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode 
    4044      INTEGER  , OPTIONAL, INTENT(IN) :: order 
     45      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity 
     46      LOGICAL (KIND=C_BOOL) :: quantity_tmp 
    4147      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize 
    4248      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     
    4652 
    4753      CALL xios(set_interpolate_domain_attr_hdl_)  & 
    48       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     54      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     55       ) 
    4956 
    5057  END SUBROUTINE xios(set_interpolate_domain_attr_hdl) 
    5158 
    5259  SUBROUTINE xios(set_interpolate_domain_attr_hdl_)   & 
    53     ( interpolate_domain_hdl, mode_, order_, renormalize_, weight_filename_, write_weight_ ) 
     60    ( interpolate_domain_hdl, mode_, order_, quantity_, renormalize_, weight_filename_, write_weight_  & 
     61     ) 
    5462 
    5563    IMPLICIT NONE 
     
    5765      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: mode_ 
    5866      INTEGER  , OPTIONAL, INTENT(IN) :: order_ 
     67      LOGICAL  , OPTIONAL, INTENT(IN) :: quantity_ 
     68      LOGICAL (KIND=C_BOOL) :: quantity__tmp 
    5969      LOGICAL  , OPTIONAL, INTENT(IN) :: renormalize_ 
    6070      LOGICAL (KIND=C_BOOL) :: renormalize__tmp 
     
    7383      ENDIF 
    7484 
     85      IF (PRESENT(quantity_)) THEN 
     86        quantity__tmp = quantity_ 
     87        CALL cxios_set_interpolate_domain_quantity & 
     88      (interpolate_domain_hdl%daddr, quantity__tmp) 
     89      ENDIF 
     90 
    7591      IF (PRESENT(renormalize_)) THEN 
    7692        renormalize__tmp = renormalize_ 
     
    93109 
    94110  SUBROUTINE xios(get_interpolate_domain_attr)  & 
    95     ( interpolate_domain_id, mode, order, renormalize, weight_filename, write_weight ) 
     111    ( interpolate_domain_id, mode, order, quantity, renormalize, weight_filename, write_weight ) 
    96112 
    97113    IMPLICIT NONE 
     
    100116      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode 
    101117      INTEGER  , OPTIONAL, INTENT(OUT) :: order 
     118      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity 
     119      LOGICAL (KIND=C_BOOL) :: quantity_tmp 
    102120      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize 
    103121      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     
    109127      (interpolate_domain_id,interpolate_domain_hdl) 
    110128      CALL xios(get_interpolate_domain_attr_hdl_)   & 
    111       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     129      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     130       ) 
    112131 
    113132  END SUBROUTINE xios(get_interpolate_domain_attr) 
    114133 
    115134  SUBROUTINE xios(get_interpolate_domain_attr_hdl)  & 
    116     ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     135    ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     136     ) 
    117137 
    118138    IMPLICIT NONE 
     
    120140      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode 
    121141      INTEGER  , OPTIONAL, INTENT(OUT) :: order 
     142      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity 
     143      LOGICAL (KIND=C_BOOL) :: quantity_tmp 
    122144      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize 
    123145      LOGICAL (KIND=C_BOOL) :: renormalize_tmp 
     
    127149 
    128150      CALL xios(get_interpolate_domain_attr_hdl_)  & 
    129       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     151      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     152       ) 
    130153 
    131154  END SUBROUTINE xios(get_interpolate_domain_attr_hdl) 
    132155 
    133156  SUBROUTINE xios(get_interpolate_domain_attr_hdl_)   & 
    134     ( interpolate_domain_hdl, mode_, order_, renormalize_, weight_filename_, write_weight_ ) 
     157    ( interpolate_domain_hdl, mode_, order_, quantity_, renormalize_, weight_filename_, write_weight_  & 
     158     ) 
    135159 
    136160    IMPLICIT NONE 
     
    138162      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: mode_ 
    139163      INTEGER  , OPTIONAL, INTENT(OUT) :: order_ 
     164      LOGICAL  , OPTIONAL, INTENT(OUT) :: quantity_ 
     165      LOGICAL (KIND=C_BOOL) :: quantity__tmp 
    140166      LOGICAL  , OPTIONAL, INTENT(OUT) :: renormalize_ 
    141167      LOGICAL (KIND=C_BOOL) :: renormalize__tmp 
     
    154180      ENDIF 
    155181 
     182      IF (PRESENT(quantity_)) THEN 
     183        CALL cxios_get_interpolate_domain_quantity & 
     184      (interpolate_domain_hdl%daddr, quantity__tmp) 
     185        quantity_ = quantity__tmp 
     186      ENDIF 
     187 
    156188      IF (PRESENT(renormalize_)) THEN 
    157189        CALL cxios_get_interpolate_domain_renormalize & 
     
    174206 
    175207  SUBROUTINE xios(is_defined_interpolate_domain_attr)  & 
    176     ( interpolate_domain_id, mode, order, renormalize, weight_filename, write_weight ) 
     208    ( interpolate_domain_id, mode, order, quantity, renormalize, weight_filename, write_weight ) 
    177209 
    178210    IMPLICIT NONE 
     
    183215      LOGICAL, OPTIONAL, INTENT(OUT) :: order 
    184216      LOGICAL(KIND=C_BOOL) :: order_tmp 
     217      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity 
     218      LOGICAL(KIND=C_BOOL) :: quantity_tmp 
    185219      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize 
    186220      LOGICAL(KIND=C_BOOL) :: renormalize_tmp 
     
    193227      (interpolate_domain_id,interpolate_domain_hdl) 
    194228      CALL xios(is_defined_interpolate_domain_attr_hdl_)   & 
    195       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     229      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     230       ) 
    196231 
    197232  END SUBROUTINE xios(is_defined_interpolate_domain_attr) 
    198233 
    199234  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl)  & 
    200     ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     235    ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     236     ) 
    201237 
    202238    IMPLICIT NONE 
     
    206242      LOGICAL, OPTIONAL, INTENT(OUT) :: order 
    207243      LOGICAL(KIND=C_BOOL) :: order_tmp 
     244      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity 
     245      LOGICAL(KIND=C_BOOL) :: quantity_tmp 
    208246      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize 
    209247      LOGICAL(KIND=C_BOOL) :: renormalize_tmp 
     
    214252 
    215253      CALL xios(is_defined_interpolate_domain_attr_hdl_)  & 
    216       ( interpolate_domain_hdl, mode, order, renormalize, weight_filename, write_weight ) 
     254      ( interpolate_domain_hdl, mode, order, quantity, renormalize, weight_filename, write_weight  & 
     255       ) 
    217256 
    218257  END SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl) 
    219258 
    220259  SUBROUTINE xios(is_defined_interpolate_domain_attr_hdl_)   & 
    221     ( interpolate_domain_hdl, mode_, order_, renormalize_, weight_filename_, write_weight_ ) 
     260    ( interpolate_domain_hdl, mode_, order_, quantity_, renormalize_, weight_filename_, write_weight_  & 
     261     ) 
    222262 
    223263    IMPLICIT NONE 
     
    227267      LOGICAL, OPTIONAL, INTENT(OUT) :: order_ 
    228268      LOGICAL(KIND=C_BOOL) :: order__tmp 
     269      LOGICAL, OPTIONAL, INTENT(OUT) :: quantity_ 
     270      LOGICAL(KIND=C_BOOL) :: quantity__tmp 
    229271      LOGICAL, OPTIONAL, INTENT(OUT) :: renormalize_ 
    230272      LOGICAL(KIND=C_BOOL) :: renormalize__tmp 
     
    246288      ENDIF 
    247289 
     290      IF (PRESENT(quantity_)) THEN 
     291        quantity__tmp = cxios_is_defined_interpolate_domain_quantity & 
     292      (interpolate_domain_hdl%daddr) 
     293        quantity_ = quantity__tmp 
     294      ENDIF 
     295 
    248296      IF (PRESENT(renormalize_)) THEN 
    249297        renormalize__tmp = cxios_is_defined_interpolate_domain_renormalize & 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/interpolate_domain_interface_attr.F90

    r1040 r1205  
    4848      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
    4949    END FUNCTION cxios_is_defined_interpolate_domain_order 
     50 
     51 
     52    SUBROUTINE cxios_set_interpolate_domain_quantity(interpolate_domain_hdl, quantity) BIND(C) 
     53      USE ISO_C_BINDING 
     54      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     55      LOGICAL (KIND=C_BOOL)      , VALUE :: quantity 
     56    END SUBROUTINE cxios_set_interpolate_domain_quantity 
     57 
     58    SUBROUTINE cxios_get_interpolate_domain_quantity(interpolate_domain_hdl, quantity) BIND(C) 
     59      USE ISO_C_BINDING 
     60      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     61      LOGICAL (KIND=C_BOOL)             :: quantity 
     62    END SUBROUTINE cxios_get_interpolate_domain_quantity 
     63 
     64    FUNCTION cxios_is_defined_interpolate_domain_quantity(interpolate_domain_hdl) BIND(C) 
     65      USE ISO_C_BINDING 
     66      LOGICAL(kind=C_BOOL) :: cxios_is_defined_interpolate_domain_quantity 
     67      INTEGER (kind = C_INTPTR_T), VALUE :: interpolate_domain_hdl 
     68    END FUNCTION cxios_is_defined_interpolate_domain_quantity 
    5069 
    5170 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/izoom_axis_attr.F90

    r966 r1205  
    1212 
    1313  SUBROUTINE xios(set_zoom_axis_attr)  & 
    14     ( zoom_axis_id, begin, n ) 
     14    ( zoom_axis_id, begin, index, n ) 
    1515 
    1616    IMPLICIT NONE 
     
    1818      CHARACTER(LEN=*), INTENT(IN) ::zoom_axis_id 
    1919      INTEGER  , OPTIONAL, INTENT(IN) :: begin 
     20      INTEGER  , OPTIONAL, INTENT(IN) :: index(:) 
    2021      INTEGER  , OPTIONAL, INTENT(IN) :: n 
    2122 
     
    2324      (zoom_axis_id,zoom_axis_hdl) 
    2425      CALL xios(set_zoom_axis_attr_hdl_)   & 
    25       ( zoom_axis_hdl, begin, n ) 
     26      ( zoom_axis_hdl, begin, index, n ) 
    2627 
    2728  END SUBROUTINE xios(set_zoom_axis_attr) 
    2829 
    2930  SUBROUTINE xios(set_zoom_axis_attr_hdl)  & 
    30     ( zoom_axis_hdl, begin, n ) 
     31    ( zoom_axis_hdl, begin, index, n ) 
    3132 
    3233    IMPLICIT NONE 
    3334      TYPE(txios(zoom_axis)) , INTENT(IN) :: zoom_axis_hdl 
    3435      INTEGER  , OPTIONAL, INTENT(IN) :: begin 
     36      INTEGER  , OPTIONAL, INTENT(IN) :: index(:) 
    3537      INTEGER  , OPTIONAL, INTENT(IN) :: n 
    3638 
    3739      CALL xios(set_zoom_axis_attr_hdl_)  & 
    38       ( zoom_axis_hdl, begin, n ) 
     40      ( zoom_axis_hdl, begin, index, n ) 
    3941 
    4042  END SUBROUTINE xios(set_zoom_axis_attr_hdl) 
    4143 
    4244  SUBROUTINE xios(set_zoom_axis_attr_hdl_)   & 
    43     ( zoom_axis_hdl, begin_, n_ ) 
     45    ( zoom_axis_hdl, begin_, index_, n_ ) 
    4446 
    4547    IMPLICIT NONE 
    4648      TYPE(txios(zoom_axis)) , INTENT(IN) :: zoom_axis_hdl 
    4749      INTEGER  , OPTIONAL, INTENT(IN) :: begin_ 
     50      INTEGER  , OPTIONAL, INTENT(IN) :: index_(:) 
    4851      INTEGER  , OPTIONAL, INTENT(IN) :: n_ 
    4952 
     
    5154        CALL cxios_set_zoom_axis_begin & 
    5255      (zoom_axis_hdl%daddr, begin_) 
     56      ENDIF 
     57 
     58      IF (PRESENT(index_)) THEN 
     59        CALL cxios_set_zoom_axis_index & 
     60      (zoom_axis_hdl%daddr, index_, SHAPE(index_)) 
    5361      ENDIF 
    5462 
     
    6169 
    6270  SUBROUTINE xios(get_zoom_axis_attr)  & 
    63     ( zoom_axis_id, begin, n ) 
     71    ( zoom_axis_id, begin, index, n ) 
    6472 
    6573    IMPLICIT NONE 
     
    6775      CHARACTER(LEN=*), INTENT(IN) ::zoom_axis_id 
    6876      INTEGER  , OPTIONAL, INTENT(OUT) :: begin 
     77      INTEGER  , OPTIONAL, INTENT(OUT) :: index(:) 
    6978      INTEGER  , OPTIONAL, INTENT(OUT) :: n 
    7079 
     
    7281      (zoom_axis_id,zoom_axis_hdl) 
    7382      CALL xios(get_zoom_axis_attr_hdl_)   & 
    74       ( zoom_axis_hdl, begin, n ) 
     83      ( zoom_axis_hdl, begin, index, n ) 
    7584 
    7685  END SUBROUTINE xios(get_zoom_axis_attr) 
    7786 
    7887  SUBROUTINE xios(get_zoom_axis_attr_hdl)  & 
    79     ( zoom_axis_hdl, begin, n ) 
     88    ( zoom_axis_hdl, begin, index, n ) 
    8089 
    8190    IMPLICIT NONE 
    8291      TYPE(txios(zoom_axis)) , INTENT(IN) :: zoom_axis_hdl 
    8392      INTEGER  , OPTIONAL, INTENT(OUT) :: begin 
     93      INTEGER  , OPTIONAL, INTENT(OUT) :: index(:) 
    8494      INTEGER  , OPTIONAL, INTENT(OUT) :: n 
    8595 
    8696      CALL xios(get_zoom_axis_attr_hdl_)  & 
    87       ( zoom_axis_hdl, begin, n ) 
     97      ( zoom_axis_hdl, begin, index, n ) 
    8898 
    8999  END SUBROUTINE xios(get_zoom_axis_attr_hdl) 
    90100 
    91101  SUBROUTINE xios(get_zoom_axis_attr_hdl_)   & 
    92     ( zoom_axis_hdl, begin_, n_ ) 
     102    ( zoom_axis_hdl, begin_, index_, n_ ) 
    93103 
    94104    IMPLICIT NONE 
    95105      TYPE(txios(zoom_axis)) , INTENT(IN) :: zoom_axis_hdl 
    96106      INTEGER  , OPTIONAL, INTENT(OUT) :: begin_ 
     107      INTEGER  , OPTIONAL, INTENT(OUT) :: index_(:) 
    97108      INTEGER  , OPTIONAL, INTENT(OUT) :: n_ 
    98109 
     
    100111        CALL cxios_get_zoom_axis_begin & 
    101112      (zoom_axis_hdl%daddr, begin_) 
     113      ENDIF 
     114 
     115      IF (PRESENT(index_)) THEN 
     116        CALL cxios_get_zoom_axis_index & 
     117      (zoom_axis_hdl%daddr, index_, SHAPE(index_)) 
    102118      ENDIF 
    103119 
     
    110126 
    111127  SUBROUTINE xios(is_defined_zoom_axis_attr)  & 
    112     ( zoom_axis_id, begin, n ) 
     128    ( zoom_axis_id, begin, index, n ) 
    113129 
    114130    IMPLICIT NONE 
     
    117133      LOGICAL, OPTIONAL, INTENT(OUT) :: begin 
    118134      LOGICAL(KIND=C_BOOL) :: begin_tmp 
     135      LOGICAL, OPTIONAL, INTENT(OUT) :: index 
     136      LOGICAL(KIND=C_BOOL) :: index_tmp 
    119137      LOGICAL, OPTIONAL, INTENT(OUT) :: n 
    120138      LOGICAL(KIND=C_BOOL) :: n_tmp 
     
    123141      (zoom_axis_id,zoom_axis_hdl) 
    124142      CALL xios(is_defined_zoom_axis_attr_hdl_)   & 
    125       ( zoom_axis_hdl, begin, n ) 
     143      ( zoom_axis_hdl, begin, index, n ) 
    126144 
    127145  END SUBROUTINE xios(is_defined_zoom_axis_attr) 
    128146 
    129147  SUBROUTINE xios(is_defined_zoom_axis_attr_hdl)  & 
    130     ( zoom_axis_hdl, begin, n ) 
     148    ( zoom_axis_hdl, begin, index, n ) 
    131149 
    132150    IMPLICIT NONE 
     
    134152      LOGICAL, OPTIONAL, INTENT(OUT) :: begin 
    135153      LOGICAL(KIND=C_BOOL) :: begin_tmp 
     154      LOGICAL, OPTIONAL, INTENT(OUT) :: index 
     155      LOGICAL(KIND=C_BOOL) :: index_tmp 
    136156      LOGICAL, OPTIONAL, INTENT(OUT) :: n 
    137157      LOGICAL(KIND=C_BOOL) :: n_tmp 
    138158 
    139159      CALL xios(is_defined_zoom_axis_attr_hdl_)  & 
    140       ( zoom_axis_hdl, begin, n ) 
     160      ( zoom_axis_hdl, begin, index, n ) 
    141161 
    142162  END SUBROUTINE xios(is_defined_zoom_axis_attr_hdl) 
    143163 
    144164  SUBROUTINE xios(is_defined_zoom_axis_attr_hdl_)   & 
    145     ( zoom_axis_hdl, begin_, n_ ) 
     165    ( zoom_axis_hdl, begin_, index_, n_ ) 
    146166 
    147167    IMPLICIT NONE 
     
    149169      LOGICAL, OPTIONAL, INTENT(OUT) :: begin_ 
    150170      LOGICAL(KIND=C_BOOL) :: begin__tmp 
     171      LOGICAL, OPTIONAL, INTENT(OUT) :: index_ 
     172      LOGICAL(KIND=C_BOOL) :: index__tmp 
    151173      LOGICAL, OPTIONAL, INTENT(OUT) :: n_ 
    152174      LOGICAL(KIND=C_BOOL) :: n__tmp 
     
    156178      (zoom_axis_hdl%daddr) 
    157179        begin_ = begin__tmp 
     180      ENDIF 
     181 
     182      IF (PRESENT(index_)) THEN 
     183        index__tmp = cxios_is_defined_zoom_axis_index & 
     184      (zoom_axis_hdl%daddr) 
     185        index_ = index__tmp 
    158186      ENDIF 
    159187 
  • XIOS/dev/branch_yushan_merged/src/interface/fortran_attr/zoom_axis_interface_attr.F90

    r787 r1205  
    2929 
    3030 
     31    SUBROUTINE cxios_set_zoom_axis_index(zoom_axis_hdl, index, extent) BIND(C) 
     32      USE ISO_C_BINDING 
     33      INTEGER (kind = C_INTPTR_T), VALUE       :: zoom_axis_hdl 
     34      INTEGER (KIND=C_INT)     , DIMENSION(*) :: index 
     35      INTEGER (kind = C_INT), DIMENSION(*)     :: extent 
     36    END SUBROUTINE cxios_set_zoom_axis_index 
     37 
     38    SUBROUTINE cxios_get_zoom_axis_index(zoom_axis_hdl, index, extent) BIND(C) 
     39      USE ISO_C_BINDING 
     40      INTEGER (kind = C_INTPTR_T), VALUE       :: zoom_axis_hdl 
     41      INTEGER (KIND=C_INT)     , DIMENSION(*) :: index 
     42      INTEGER (kind = C_INT), DIMENSION(*)     :: extent 
     43    END SUBROUTINE cxios_get_zoom_axis_index 
     44 
     45    FUNCTION cxios_is_defined_zoom_axis_index(zoom_axis_hdl) BIND(C) 
     46      USE ISO_C_BINDING 
     47      LOGICAL(kind=C_BOOL) :: cxios_is_defined_zoom_axis_index 
     48      INTEGER (kind = C_INTPTR_T), VALUE :: zoom_axis_hdl 
     49    END FUNCTION cxios_is_defined_zoom_axis_index 
     50 
     51 
    3152    SUBROUTINE cxios_set_zoom_axis_n(zoom_axis_hdl, n) BIND(C) 
    3253      USE ISO_C_BINDING 
Note: See TracChangeset for help on using the changeset viewer.