Ignore:
Timestamp:
03/19/24 14:23:16 (4 months ago)
Author:
jderouillat
Message:

Add XIOS3 fortran interfaces (resources management, chunking, compression)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS3/trunk/src/interface/fortran_attr/iaxis_attr.F90

    r1492 r2616  
    1212 
    1313  SUBROUTINE xios(set_axis_attr)  & 
    14     ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    15     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    16     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    17     , value ) 
     14    ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     15    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     16    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     17    , unit, value ) 
    1818 
    1919    IMPLICIT NONE 
     
    2525      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds(:,:) 
    2626      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name 
     27      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: chunking_weight 
    2728      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment 
    2829      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin 
     
    5253      (axis_id,axis_hdl) 
    5354      CALL xios(set_axis_attr_hdl_)   & 
    54       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    55       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    56       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    57       , value ) 
     55      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     56      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     57      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     58      , unit, value ) 
    5859 
    5960  END SUBROUTINE xios(set_axis_attr) 
    6061 
    6162  SUBROUTINE xios(set_axis_attr_hdl)  & 
    62     ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    63     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    64     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    65     , value ) 
     63    ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     64    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     65    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     66    , unit, value ) 
    6667 
    6768    IMPLICIT NONE 
     
    7273      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds(:,:) 
    7374      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name 
     75      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: chunking_weight 
    7476      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment 
    7577      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin 
     
    9799 
    98100      CALL xios(set_axis_attr_hdl_)  & 
    99       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    100       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    101       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    102       , value ) 
     101      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     102      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     103      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     104      , unit, value ) 
    103105 
    104106  END SUBROUTINE xios(set_axis_attr_hdl) 
    105107 
    106108  SUBROUTINE xios(set_axis_attr_hdl_)   & 
    107     ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_, data_index_  & 
    108     , data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_, index_  & 
    109     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    110     , unit_, value_ ) 
     109    ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, chunking_weight_, comment_  & 
     110    , data_begin_, data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     111    , index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_  & 
     112    , prec_, standard_name_, unit_, value_ ) 
    111113 
    112114    IMPLICIT NONE 
     
    117119      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: bounds_(:,:) 
    118120      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: bounds_name_ 
     121      REAL (KIND=8) , OPTIONAL, INTENT(IN) :: chunking_weight_ 
    119122      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: comment_ 
    120123      INTEGER  , OPTIONAL, INTENT(IN) :: data_begin_ 
     
    166169      ENDIF 
    167170 
     171      IF (PRESENT(chunking_weight_)) THEN 
     172        CALL cxios_set_axis_chunking_weight & 
     173      (axis_hdl%daddr, chunking_weight_) 
     174      ENDIF 
     175 
    168176      IF (PRESENT(comment_)) THEN 
    169177        CALL cxios_set_axis_comment & 
     
    281289 
    282290  SUBROUTINE xios(get_axis_attr)  & 
    283     ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    284     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    285     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    286     , value ) 
     291    ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     292    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     293    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     294    , unit, value ) 
    287295 
    288296    IMPLICIT NONE 
     
    294302      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds(:,:) 
    295303      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name 
     304      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: chunking_weight 
    296305      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment 
    297306      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin 
     
    321330      (axis_id,axis_hdl) 
    322331      CALL xios(get_axis_attr_hdl_)   & 
    323       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    324       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    325       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    326       , value ) 
     332      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     333      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     334      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     335      , unit, value ) 
    327336 
    328337  END SUBROUTINE xios(get_axis_attr) 
    329338 
    330339  SUBROUTINE xios(get_axis_attr_hdl)  & 
    331     ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    332     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    333     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    334     , value ) 
     340    ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     341    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     342    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     343    , unit, value ) 
    335344 
    336345    IMPLICIT NONE 
     
    341350      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds(:,:) 
    342351      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name 
     352      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: chunking_weight 
    343353      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment 
    344354      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin 
     
    366376 
    367377      CALL xios(get_axis_attr_hdl_)  & 
    368       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    369       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    370       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    371       , value ) 
     378      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     379      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     380      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     381      , unit, value ) 
    372382 
    373383  END SUBROUTINE xios(get_axis_attr_hdl) 
    374384 
    375385  SUBROUTINE xios(get_axis_attr_hdl_)   & 
    376     ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_, data_index_  & 
    377     , data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_, index_  & 
    378     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    379     , unit_, value_ ) 
     386    ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, chunking_weight_, comment_  & 
     387    , data_begin_, data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     388    , index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_  & 
     389    , prec_, standard_name_, unit_, value_ ) 
    380390 
    381391    IMPLICIT NONE 
     
    386396      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: bounds_(:,:) 
    387397      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: bounds_name_ 
     398      REAL (KIND=8) , OPTIONAL, INTENT(OUT) :: chunking_weight_ 
    388399      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: comment_ 
    389400      INTEGER  , OPTIONAL, INTENT(OUT) :: data_begin_ 
     
    435446      ENDIF 
    436447 
     448      IF (PRESENT(chunking_weight_)) THEN 
     449        CALL cxios_get_axis_chunking_weight & 
     450      (axis_hdl%daddr, chunking_weight_) 
     451      ENDIF 
     452 
    437453      IF (PRESENT(comment_)) THEN 
    438454        CALL cxios_get_axis_comment & 
     
    550566 
    551567  SUBROUTINE xios(is_defined_axis_attr)  & 
    552     ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    553     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    554     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    555     , value ) 
     568    ( axis_id, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     569    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     570    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     571    , unit, value ) 
    556572 
    557573    IMPLICIT NONE 
     
    568584      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name 
    569585      LOGICAL(KIND=C_BOOL) :: bounds_name_tmp 
     586      LOGICAL, OPTIONAL, INTENT(OUT) :: chunking_weight 
     587      LOGICAL(KIND=C_BOOL) :: chunking_weight_tmp 
    570588      LOGICAL, OPTIONAL, INTENT(OUT) :: comment 
    571589      LOGICAL(KIND=C_BOOL) :: comment_tmp 
     
    616634      (axis_id,axis_hdl) 
    617635      CALL xios(is_defined_axis_attr_hdl_)   & 
    618       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    619       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    620       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    621       , value ) 
     636      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     637      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     638      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     639      , unit, value ) 
    622640 
    623641  END SUBROUTINE xios(is_defined_axis_attr) 
    624642 
    625643  SUBROUTINE xios(is_defined_axis_attr_hdl)  & 
    626     ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    627     , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    628     , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    629     , value ) 
     644    ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     645    , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     646    , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     647    , unit, value ) 
    630648 
    631649    IMPLICIT NONE 
     
    641659      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name 
    642660      LOGICAL(KIND=C_BOOL) :: bounds_name_tmp 
     661      LOGICAL, OPTIONAL, INTENT(OUT) :: chunking_weight 
     662      LOGICAL(KIND=C_BOOL) :: chunking_weight_tmp 
    643663      LOGICAL, OPTIONAL, INTENT(OUT) :: comment 
    644664      LOGICAL(KIND=C_BOOL) :: comment_tmp 
     
    687707 
    688708      CALL xios(is_defined_axis_attr_hdl_)  & 
    689       ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, comment, data_begin, data_index  & 
    690       , data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index, label  & 
    691       , long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name, unit  & 
    692       , value ) 
     709      ( axis_hdl, axis_ref, axis_type, begin, bounds, bounds_name, chunking_weight, comment, data_begin  & 
     710      , data_index, data_n, dim_name, formula, formula_bounds, formula_term, formula_term_bounds, index  & 
     711      , label, long_name, mask, n, n_distributed_partition, n_glo, name, positive, prec, standard_name  & 
     712      , unit, value ) 
    693713 
    694714  END SUBROUTINE xios(is_defined_axis_attr_hdl) 
    695715 
    696716  SUBROUTINE xios(is_defined_axis_attr_hdl_)   & 
    697     ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, comment_, data_begin_, data_index_  & 
    698     , data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_, index_  & 
    699     , label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_, prec_, standard_name_  & 
    700     , unit_, value_ ) 
     717    ( axis_hdl, axis_ref_, axis_type_, begin_, bounds_, bounds_name_, chunking_weight_, comment_  & 
     718    , data_begin_, data_index_, data_n_, dim_name_, formula_, formula_bounds_, formula_term_, formula_term_bounds_  & 
     719    , index_, label_, long_name_, mask_, n_, n_distributed_partition_, n_glo_, name_, positive_  & 
     720    , prec_, standard_name_, unit_, value_ ) 
    701721 
    702722    IMPLICIT NONE 
     
    712732      LOGICAL, OPTIONAL, INTENT(OUT) :: bounds_name_ 
    713733      LOGICAL(KIND=C_BOOL) :: bounds_name__tmp 
     734      LOGICAL, OPTIONAL, INTENT(OUT) :: chunking_weight_ 
     735      LOGICAL(KIND=C_BOOL) :: chunking_weight__tmp 
    714736      LOGICAL, OPTIONAL, INTENT(OUT) :: comment_ 
    715737      LOGICAL(KIND=C_BOOL) :: comment__tmp 
     
    787809      ENDIF 
    788810 
     811      IF (PRESENT(chunking_weight_)) THEN 
     812        chunking_weight__tmp = cxios_is_defined_axis_chunking_weight & 
     813      (axis_hdl%daddr) 
     814        chunking_weight_ = chunking_weight__tmp 
     815      ENDIF 
     816 
    789817      IF (PRESENT(comment_)) THEN 
    790818        comment__tmp = cxios_is_defined_axis_comment & 
Note: See TracChangeset for help on using the changeset viewer.