Changeset 318


Ignore:
Timestamp:
02/21/12 15:34:27 (12 years ago)
Author:
ymipsl
Message:
  • Adding new file attribut : sync_freq : flush file for a given frequency
  • Now, when a file has a single domain, domain id is not anymore appended to the coordinate name.

YM

Location:
XIOS/trunk/src
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • XIOS/trunk/src/config/file_attribute.conf

    r286 r318  
    66DECLARE_ATTRIBUTE(StdString, output_freq) 
    77DECLARE_ATTRIBUTE(int,       output_level) 
    8  
     8DECLARE_ATTRIBUTE(StdString, sync_freq) 
     9DECLARE_ATTRIBUTE(StdString, split_freq) 
    910DECLARE_ATTRIBUTE(bool,      enabled) 
    1011DECLARE_ATTRIBUTE(StdString,      type) 
  • XIOS/trunk/src/fortran_attr_interface/file_interface_attr.f90

    r314 r318  
    9595     
    9696     
     97    SUBROUTINE cxios_set_file_split_freq(file_hdl, split_freq, split_freq_size) BIND(C) 
     98      USE ISO_C_BINDING 
     99      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     100      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
     101      INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     102    END SUBROUTINE cxios_set_file_split_freq 
     103     
     104    SUBROUTINE cxios_get_file_split_freq(file_hdl, split_freq, split_freq_size) BIND(C) 
     105      USE ISO_C_BINDING 
     106      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     107      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
     108      INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     109    END SUBROUTINE cxios_get_file_split_freq 
     110     
     111     
     112    SUBROUTINE cxios_set_file_sync_freq(file_hdl, sync_freq, sync_freq_size) BIND(C) 
     113      USE ISO_C_BINDING 
     114      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     115      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
     116      INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     117    END SUBROUTINE cxios_set_file_sync_freq 
     118     
     119    SUBROUTINE cxios_get_file_sync_freq(file_hdl, sync_freq, sync_freq_size) BIND(C) 
     120      USE ISO_C_BINDING 
     121      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     122      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
     123      INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     124    END SUBROUTINE cxios_get_file_sync_freq 
     125     
     126     
    97127    SUBROUTINE cxios_set_file_type(file_hdl, type, type_size) BIND(C) 
    98128      USE ISO_C_BINDING 
  • XIOS/trunk/src/fortran_attr_interface/filegroup_interface_attr.f90

    r314 r318  
    110110     
    111111     
     112    SUBROUTINE cxios_set_filegroup_split_freq(filegroup_hdl, split_freq, split_freq_size) BIND(C) 
     113      USE ISO_C_BINDING 
     114      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     115      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
     116      INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     117    END SUBROUTINE cxios_set_filegroup_split_freq 
     118     
     119    SUBROUTINE cxios_get_filegroup_split_freq(filegroup_hdl, split_freq, split_freq_size) BIND(C) 
     120      USE ISO_C_BINDING 
     121      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     122      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
     123      INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     124    END SUBROUTINE cxios_get_filegroup_split_freq 
     125     
     126     
     127    SUBROUTINE cxios_set_filegroup_sync_freq(filegroup_hdl, sync_freq, sync_freq_size) BIND(C) 
     128      USE ISO_C_BINDING 
     129      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     130      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
     131      INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     132    END SUBROUTINE cxios_set_filegroup_sync_freq 
     133     
     134    SUBROUTINE cxios_get_filegroup_sync_freq(filegroup_hdl, sync_freq, sync_freq_size) BIND(C) 
     135      USE ISO_C_BINDING 
     136      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     137      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
     138      INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     139    END SUBROUTINE cxios_get_filegroup_sync_freq 
     140     
     141     
    112142    SUBROUTINE cxios_set_filegroup_type(filegroup_hdl, type, type_size) BIND(C) 
    113143      USE ISO_C_BINDING 
  • XIOS/trunk/src/fortran_attr_interface/icfile_attr.cpp

    r314 r318  
    9999   
    100100   
     101  void cxios_set_file_split_freq(file_Ptr file_hdl, const char * split_freq, int split_freq_size) 
     102  { 
     103    std::string split_freq_str; 
     104    if(!cstr2string(split_freq, split_freq_size, split_freq_str)) return; 
     105    file_hdl->split_freq.setValue(split_freq_str); 
     106    file_hdl->sendAttributToServer(file_hdl->split_freq); 
     107  } 
     108   
     109  void cxios_get_file_split_freq(file_Ptr file_hdl, char * split_freq, int split_freq_size) 
     110  { 
     111    if(!string_copy(file_hdl->split_freq.getValue(),split_freq , split_freq_size)) 
     112      ERROR("void cxios_get_file_split_freq(file_Ptr file_hdl, char * split_freq, int split_freq_size)", <<"Input string is to short"); 
     113  } 
     114   
     115   
     116  void cxios_set_file_sync_freq(file_Ptr file_hdl, const char * sync_freq, int sync_freq_size) 
     117  { 
     118    std::string sync_freq_str; 
     119    if(!cstr2string(sync_freq, sync_freq_size, sync_freq_str)) return; 
     120    file_hdl->sync_freq.setValue(sync_freq_str); 
     121    file_hdl->sendAttributToServer(file_hdl->sync_freq); 
     122  } 
     123   
     124  void cxios_get_file_sync_freq(file_Ptr file_hdl, char * sync_freq, int sync_freq_size) 
     125  { 
     126    if(!string_copy(file_hdl->sync_freq.getValue(),sync_freq , sync_freq_size)) 
     127      ERROR("void cxios_get_file_sync_freq(file_Ptr file_hdl, char * sync_freq, int sync_freq_size)", <<"Input string is to short"); 
     128  } 
     129   
     130   
    101131  void cxios_set_file_type(file_Ptr file_hdl, const char * type, int type_size) 
    102132  { 
  • XIOS/trunk/src/fortran_attr_interface/icfilegroup_attr.cpp

    r314 r318  
    114114   
    115115   
     116  void cxios_set_filegroup_split_freq(filegroup_Ptr filegroup_hdl, const char * split_freq, int split_freq_size) 
     117  { 
     118    std::string split_freq_str; 
     119    if(!cstr2string(split_freq, split_freq_size, split_freq_str)) return; 
     120    filegroup_hdl->split_freq.setValue(split_freq_str); 
     121    filegroup_hdl->sendAttributToServer(filegroup_hdl->split_freq); 
     122  } 
     123   
     124  void cxios_get_filegroup_split_freq(filegroup_Ptr filegroup_hdl, char * split_freq, int split_freq_size) 
     125  { 
     126    if(!string_copy(filegroup_hdl->split_freq.getValue(),split_freq , split_freq_size)) 
     127      ERROR("void cxios_get_filegroup_split_freq(filegroup_Ptr filegroup_hdl, char * split_freq, int split_freq_size)", <<"Input string is to short"); 
     128  } 
     129   
     130   
     131  void cxios_set_filegroup_sync_freq(filegroup_Ptr filegroup_hdl, const char * sync_freq, int sync_freq_size) 
     132  { 
     133    std::string sync_freq_str; 
     134    if(!cstr2string(sync_freq, sync_freq_size, sync_freq_str)) return; 
     135    filegroup_hdl->sync_freq.setValue(sync_freq_str); 
     136    filegroup_hdl->sendAttributToServer(filegroup_hdl->sync_freq); 
     137  } 
     138   
     139  void cxios_get_filegroup_sync_freq(filegroup_Ptr filegroup_hdl, char * sync_freq, int sync_freq_size) 
     140  { 
     141    if(!string_copy(filegroup_hdl->sync_freq.getValue(),sync_freq , sync_freq_size)) 
     142      ERROR("void cxios_get_filegroup_sync_freq(filegroup_Ptr filegroup_hdl, char * sync_freq, int sync_freq_size)", <<"Input string is to short"); 
     143  } 
     144   
     145   
    116146  void cxios_set_filegroup_type(filegroup_Ptr filegroup_hdl, const char * type, int type_size) 
    117147  { 
  • XIOS/trunk/src/fortran_attr_interface/ifile_attr.F90

    r314 r318  
    1212   
    1313  SUBROUTINE xios(set_file_attr)  & 
    14     ( file_id, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     14    ( file_id, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     15    , type ) 
    1516     
    1617    IMPLICIT NONE 
     
    2425      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
    2526      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
     27      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     28      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
    2629      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    2730       
    2831      CALL xios(get_file_handle)(file_id,file_hdl) 
    2932      CALL xios(set_file_attr_hdl_)   & 
    30       ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     33      ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     34      , type ) 
    3135     
    3236  END SUBROUTINE xios(set_file_attr) 
    3337   
    3438  SUBROUTINE xios(set_file_attr_hdl)  & 
    35     ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     39    ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     40    , type ) 
    3641     
    3742    IMPLICIT NONE 
     
    4449      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
    4550      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
     51      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     52      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
    4653      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    4754       
    4855      CALL xios(set_file_attr_hdl_)  & 
    49       ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     56      ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     57      , type ) 
    5058     
    5159  END SUBROUTINE xios(set_file_attr_hdl) 
    5260   
    5361  SUBROUTINE xios(set_file_attr_hdl_)   & 
    54     ( file_hdl, description_, enabled_, name_, name_suffix_, output_freq_, output_level_, type_  & 
    55     ) 
     62    ( file_hdl, description_, enabled_, name_, name_suffix_, output_freq_, output_level_, split_freq_  & 
     63    , sync_freq_, type_ ) 
    5664     
    5765    IMPLICIT NONE 
     
    6472      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq_ 
    6573      INTEGER  , OPTIONAL, INTENT(IN) :: output_level_ 
     74      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_ 
     75      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq_ 
    6676      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_ 
    6777       
     
    91101      ENDIF 
    92102       
     103      IF (PRESENT(split_freq_)) THEN 
     104        CALL cxios_set_file_split_freq(file_hdl%daddr, split_freq_, len(split_freq_)) 
     105      ENDIF 
     106       
     107      IF (PRESENT(sync_freq_)) THEN 
     108        CALL cxios_set_file_sync_freq(file_hdl%daddr, sync_freq_, len(sync_freq_)) 
     109      ENDIF 
     110       
    93111      IF (PRESENT(type_)) THEN 
    94112        CALL cxios_set_file_type(file_hdl%daddr, type_, len(type_)) 
     
    100118   
    101119  SUBROUTINE xios(get_file_attr)  & 
    102     ( file_id, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     120    ( file_id, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     121    , type ) 
    103122     
    104123    IMPLICIT NONE 
     
    112131      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
    113132      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
     133      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     134      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
    114135      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    115136       
    116137      CALL xios(get_file_handle)(file_id,file_hdl) 
    117138      CALL xios(get_file_attr_hdl_)   & 
    118       ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     139      ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     140      , type ) 
    119141     
    120142  END SUBROUTINE xios(get_file_attr) 
    121143   
    122144  SUBROUTINE xios(get_file_attr_hdl)  & 
    123     ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     145    ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     146    , type ) 
    124147     
    125148    IMPLICIT NONE 
     
    132155      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
    133156      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
     157      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     158      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
    134159      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    135160       
    136161      CALL xios(get_file_attr_hdl_)  & 
    137       ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, type ) 
     162      ( file_hdl, description, enabled, name, name_suffix, output_freq, output_level, split_freq, sync_freq  & 
     163      , type ) 
    138164     
    139165  END SUBROUTINE xios(get_file_attr_hdl) 
    140166   
    141167  SUBROUTINE xios(get_file_attr_hdl_)   & 
    142     ( file_hdl, description_, enabled_, name_, name_suffix_, output_freq_, output_level_, type_  & 
    143     ) 
     168    ( file_hdl, description_, enabled_, name_, name_suffix_, output_freq_, output_level_, split_freq_  & 
     169    , sync_freq_, type_ ) 
    144170     
    145171    IMPLICIT NONE 
     
    152178      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq_ 
    153179      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level_ 
     180      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_ 
     181      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
    154182      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_ 
    155183       
     
    179207      ENDIF 
    180208       
     209      IF (PRESENT(split_freq_)) THEN 
     210        CALL cxios_get_file_split_freq(file_hdl%daddr, split_freq_, len(split_freq_)) 
     211      ENDIF 
     212       
     213      IF (PRESENT(sync_freq_)) THEN 
     214        CALL cxios_get_file_sync_freq(file_hdl%daddr, sync_freq_, len(sync_freq_)) 
     215      ENDIF 
     216       
    181217      IF (PRESENT(type_)) THEN 
    182218        CALL cxios_get_file_type(file_hdl%daddr, type_, len(type_)) 
  • XIOS/trunk/src/fortran_attr_interface/ifilegroup_attr.F90

    r314 r318  
    1313  SUBROUTINE xios(set_filegroup_attr)  & 
    1414    ( filegroup_id, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    15     , type ) 
     15    , split_freq, sync_freq, type ) 
    1616     
    1717    IMPLICIT NONE 
     
    2626      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
    2727      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
     28      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     29      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
    2830      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    2931       
     
    3133      CALL xios(set_filegroup_attr_hdl_)   & 
    3234      ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    33       , type ) 
     35      , split_freq, sync_freq, type ) 
    3436     
    3537  END SUBROUTINE xios(set_filegroup_attr) 
     
    3739  SUBROUTINE xios(set_filegroup_attr_hdl)  & 
    3840    ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    39     , type ) 
     41    , split_freq, sync_freq, type ) 
    4042     
    4143    IMPLICIT NONE 
     
    4951      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
    5052      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
     53      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     54      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
    5155      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    5256       
    5357      CALL xios(set_filegroup_attr_hdl_)  & 
    5458      ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    55       , type ) 
     59      , split_freq, sync_freq, type ) 
    5660     
    5761  END SUBROUTINE xios(set_filegroup_attr_hdl) 
     
    5963  SUBROUTINE xios(set_filegroup_attr_hdl_)   & 
    6064    ( filegroup_hdl, description_, enabled_, group_ref_, name_, name_suffix_, output_freq_, output_level_  & 
    61     , type_ ) 
     65    , split_freq_, sync_freq_, type_ ) 
    6266     
    6367    IMPLICIT NONE 
     
    7175      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq_ 
    7276      INTEGER  , OPTIONAL, INTENT(IN) :: output_level_ 
     77      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_ 
     78      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq_ 
    7379      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_ 
    7480       
     
    102108      ENDIF 
    103109       
     110      IF (PRESENT(split_freq_)) THEN 
     111        CALL cxios_set_filegroup_split_freq(filegroup_hdl%daddr, split_freq_, len(split_freq_)) 
     112      ENDIF 
     113       
     114      IF (PRESENT(sync_freq_)) THEN 
     115        CALL cxios_set_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_, len(sync_freq_)) 
     116      ENDIF 
     117       
    104118      IF (PRESENT(type_)) THEN 
    105119        CALL cxios_set_filegroup_type(filegroup_hdl%daddr, type_, len(type_)) 
     
    112126  SUBROUTINE xios(get_filegroup_attr)  & 
    113127    ( filegroup_id, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    114     , type ) 
     128    , split_freq, sync_freq, type ) 
    115129     
    116130    IMPLICIT NONE 
     
    125139      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
    126140      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
     141      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     142      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
    127143      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    128144       
     
    130146      CALL xios(get_filegroup_attr_hdl_)   & 
    131147      ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    132       , type ) 
     148      , split_freq, sync_freq, type ) 
    133149     
    134150  END SUBROUTINE xios(get_filegroup_attr) 
     
    136152  SUBROUTINE xios(get_filegroup_attr_hdl)  & 
    137153    ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    138     , type ) 
     154    , split_freq, sync_freq, type ) 
    139155     
    140156    IMPLICIT NONE 
     
    148164      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
    149165      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
     166      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     167      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
    150168      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    151169       
    152170      CALL xios(get_filegroup_attr_hdl_)  & 
    153171      ( filegroup_hdl, description, enabled, group_ref, name, name_suffix, output_freq, output_level  & 
    154       , type ) 
     172      , split_freq, sync_freq, type ) 
    155173     
    156174  END SUBROUTINE xios(get_filegroup_attr_hdl) 
     
    158176  SUBROUTINE xios(get_filegroup_attr_hdl_)   & 
    159177    ( filegroup_hdl, description_, enabled_, group_ref_, name_, name_suffix_, output_freq_, output_level_  & 
    160     , type_ ) 
     178    , split_freq_, sync_freq_, type_ ) 
    161179     
    162180    IMPLICIT NONE 
     
    170188      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq_ 
    171189      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level_ 
     190      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_ 
     191      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
    172192      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_ 
    173193       
     
    201221      ENDIF 
    202222       
     223      IF (PRESENT(split_freq_)) THEN 
     224        CALL cxios_get_filegroup_split_freq(filegroup_hdl%daddr, split_freq_, len(split_freq_)) 
     225      ENDIF 
     226       
     227      IF (PRESENT(sync_freq_)) THEN 
     228        CALL cxios_get_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_, len(sync_freq_)) 
     229      ENDIF 
     230       
    203231      IF (PRESENT(type_)) THEN 
    204232        CALL cxios_get_filegroup_type(filegroup_hdl%daddr, type_, len(type_)) 
  • XIOS/trunk/src/node/file.cpp

    r300 r318  
    1111#include "context_server.hpp" 
    1212#include "nc4_data_output.hpp" 
     13#include "calendar_util.hpp" 
     14#include "date.hpp" 
    1315 
    1416 
     
    125127 
    126128   //---------------------------------------------------------------- 
    127  
     129   bool CFile::isSyncTime(void) 
     130   { 
     131     shared_ptr<CContext> context=CObjectFactory::GetObject<CContext>(CObjectFactory::GetCurrentContextId()) ; 
     132     date::CDate& currentDate=context->calendar->getCurrentDate() ; 
     133     if (! sync_freq.isEmpty()) 
     134     { 
     135       if (*lastSync+syncFreq < currentDate) 
     136       { 
     137         *lastSync=currentDate ; 
     138         return true ; 
     139        } 
     140      } 
     141      return false ; 
     142    } 
     143       
    128144   void CFile::createHeader(void) 
    129145   { 
    130      
     146      shared_ptr<CContext> context=CObjectFactory::GetObject<CContext>(CObjectFactory::GetCurrentContextId()) ; 
     147 
     148      if (! sync_freq.isEmpty()) syncFreq = date::CDuration::FromString(sync_freq.getValue()); 
     149      lastSync=new date::CDate(context->calendar->getCurrentDate()) ; 
     150       
    131151      std::vector<boost::shared_ptr<CField> >::iterator it, end = this->enabledFields.end(); 
    132152 
    133153      AllDomainEmpty=true ; 
     154      set<CDomain*> setDomain ; 
    134155      for (it = this->enabledFields.begin() ;it != end; it++) 
    135156      { 
    136157         boost::shared_ptr<CField> field = *it; 
    137158         AllDomainEmpty&=field->grid->domain->isEmpty() ; 
    138       } 
    139        
     159         setDomain.insert(field->grid->domain.get()) ; 
     160      } 
     161      nbDomain=setDomain.size() ; 
     162 
    140163      if (!AllDomainEmpty ||  type.getValue()=="one_file") 
    141164      { 
     
    156179         }  
    157180          
    158          shared_ptr<CContext> context=CObjectFactory::GetObject<CContext>(CObjectFactory::GetCurrentContextId()) ; 
    159181         CContextServer* server=context->server ; 
    160182 
     
    188210     if (!AllDomainEmpty ||  type.getValue()=="one_file") 
    189211       this->data_out->closeFile(); 
     212     delete lastSync ; 
    190213   } 
    191214   //---------------------------------------------------------------- 
  • XIOS/trunk/src/node/file.hpp

    r300 r318  
    77#include "data_output.hpp" 
    88#include "declare_group.hpp" 
     9#include "date.hpp" 
    910 
    1011 
     
    102103         void recvAddFieldGroup(CBufferIn& buffer) ; 
    103104         static bool dispatchEvent(CEventServer& event) ; 
    104  
     105         bool isSyncTime(void) ; 
     106         date::CDate* lastSync ; 
     107         date::CDuration syncFreq ; 
     108         int nbDomain ; 
    105109      private : 
    106110 
  • XIOS/trunk/src/output/nc4_data_output.cpp

    r316 r318  
    7070         StdString domid     = (!domain->name.isEmpty()) 
    7171                             ? domain->name.getValue() : domain->getId(); 
    72          StdString lonid     = StdString("lon_").append(domid); 
    73          StdString latid     = StdString("lat_").append(domid); 
     72         StdString appendDomid  = (singleDomain) ? "" : "_"+domid ; 
     73 
     74         StdString lonid     = StdString("lon").append(appendDomid); 
     75         StdString latid     = StdString("lat").append(appendDomid); 
    7476         StdString lonid_loc = (server->intraCommSize > 1) 
    75                              ? StdString("lon_").append(domid).append("_local") 
     77                             ? StdString("lon").append(appendDomid).append("_local") 
    7678                             : lonid; 
    7779         StdString latid_loc = (server->intraCommSize > 1) 
    78                              ? StdString("lat_").append(domid).append("_local") 
     80                             ? StdString("lat").append(appendDomid).append("_local") 
    7981                             : latid; 
    8082// supress mask         StdString maskid    = StdString("mask_").append(domid).append("_local"); 
     
    101103               { 
    102104                 dim0.push_back(latid_loc); dim0.push_back(lonid_loc); 
    103                  lonid = StdString("nav_lon_").append(domid); 
    104                  latid = StdString("nav_lat_").append(domid); 
     105                 lonid = StdString("nav_lon").append(appendDomid); 
     106                 latid = StdString("nav_lat").append(appendDomid); 
    105107               } 
    106108               else 
     
    118120                                             domain->zoom_jbegin_srv, 
    119121                                             domain->zoom_nj_srv, 
    120                                              domid); 
     122                                             appendDomid); 
    121123               } 
    122124                
     
    172174               { 
    173175                  dim0.push_back(latid); dim0.push_back(lonid); 
    174                   lonid = StdString("nav_lon_").append(domid); 
    175                   latid = StdString("nav_lat_").append(domid); 
     176                  lonid = StdString("nav_lon").append(appendDomid); 
     177                  latid = StdString("nav_lat").append(appendDomid); 
    176178                  SuperClassWriter::addVariable(latid, NC_FLOAT, dim0); 
    177179                  SuperClassWriter::addVariable(lonid, NC_FLOAT, dim0); 
     
    283285         StdString domid     = (!domain->name.isEmpty()) 
    284286                             ? domain->name.getValue() : domain->getId(); 
    285          StdString lonid     = StdString("lon_").append(domid); 
    286          StdString latid     = StdString("lat_").append(domid); 
     287         StdString appendDomid  = (singleDomain) ? "" : "_"+domid ; 
     288 
     289         StdString lonid     = StdString("lon").append(appendDomid); 
     290         StdString latid     = StdString("lat").append(appendDomid); 
    287291         StdString lonid_loc = (server->intraCommSize > 1) 
    288                              ? StdString("lon_").append(domid).append("_local") 
     292                             ? StdString("lon").append(appendDomid).append("_local") 
    289293                             : lonid; 
    290294         StdString latid_loc = (server->intraCommSize > 1) 
    291                              ? StdString("lat_").append(domid).append("_local") 
     295                             ? StdString("lat").append(appendDomid).append("_local") 
    292296                             : latid; 
    293297         StdString fieldid   = (!field->name.isEmpty()) 
     
    324328         if (isCurvilinear) 
    325329         { 
    326             coodinates.push_back(StdString("nav_lat_").append(domid)); 
    327             coodinates.push_back(StdString("nav_lon_").append(domid)); 
     330            coodinates.push_back(StdString("nav_lat").append(appendDomid)); 
     331            coodinates.push_back(StdString("nav_lon").append(appendDomid)); 
    328332         } 
    329333         else 
     
    426430                                   StdString("An IPSL model"), 
    427431                                   this->getTimeStamp()); 
     432         if (file->nbDomain==1) singleDomain=true ; 
     433         else singleDomain=false ; 
    428434      } 
    429435 
     
    454460      { 
    455461         shared_ptr<CContext> context=CObjectFactory::GetObject<CContext>(CObjectFactory::GetCurrentContextId()) ; 
     462          if (field->getRelFile()->isSyncTime()) SuperClassWriter::sync() ; 
    456463 
    457464         boost::shared_ptr<CGrid> grid = field->grid ; 
     
    615622         (int ibegin, int ni, int jbegin, int nj, StdString domid) 
    616623      { 
    617          SuperClassWriter::addAttribute(StdString("ibegin_").append(domid), ibegin); 
    618          SuperClassWriter::addAttribute(StdString("ni_"    ).append(domid), ni); 
    619          SuperClassWriter::addAttribute(StdString("jbegin_").append(domid), jbegin); 
    620          SuperClassWriter::addAttribute(StdString("nj_"    ).append(domid), nj); 
     624         SuperClassWriter::addAttribute(StdString("ibegin").append(domid), ibegin); 
     625         SuperClassWriter::addAttribute(StdString("ni"    ).append(domid), ni); 
     626         SuperClassWriter::addAttribute(StdString("jbegin").append(domid), jbegin); 
     627         SuperClassWriter::addAttribute(StdString("nj"    ).append(domid), nj); 
    621628      } 
    622629 
  • XIOS/trunk/src/output/nc4_data_output.hpp

    r286 r318  
    3737            /// Destructeur /// 
    3838            virtual ~CNc4DataOutput(void); 
    39  
     39            bool singleDomain ; 
    4040         protected : 
    4141 
Note: See TracChangeset for help on using the changeset viewer.