Ignore:
Timestamp:
01/26/15 14:39:26 (9 years ago)
Author:
rlacroix
Message:

Revised calendar functionalities:

  • the calendar is now configured from a specific calendar child node of the context in the XML configuration file. Example: <calendar type="Gregorian" start_date="2012-03-01 15:00:00" time_origin="2012-02-29 15:00:00" timestep="1h" />
  • the calendar type should now be configured when defining the start time and/or the time origin.
  • the start time and the time origin are now optional, 0000-01-01 00:00:00 will be used by default. It is also possible to define them partially. For example, 2015 and 2014-12 are valid dates corresponding respectively to 2015-01-01 00:00:00 and 2014-12-01 00:00:00.
  • an optional duration offset can be added to the start date and time origin. For example, it's possible to define the date 2015-01-12 12:00:00 as 2015-01-11 + 36h or 2015-01-11 12:00:00 + 1d. The duration format is the same as the time step. Being that the date is optional, it is possible to only use a duration (for example + 42s is the same as 0000-01-01 00:00:00 + 42s). An error will be raised if a duration based on the time step is used before the time step was configured. For example, the following would cause an error: <calendar type="Gregorian" start_date="+ 1ts" /> but <calendar type="Gregorian" start_date="+ 1ts" timestep="0.5h" /> would not.
  • new Fortran interface to define the calendar:
    • xios_define_calendar(type[, timestep, start_date, time_origin]) will create a calendar when none had previously been defined. Only the type argument is mandatory, the rest is optional. Calendar operations on dates and durations are possible as soon as the calendar is created (either using this procedure or directly from the XML configuration file).
    • the following getter and setter procedures are available: xios_set_timestep, xios_set_start_date, xios_set_time_origin, xios_get_calendar_type, xios_get_timestep, xios_get_start_date, xios_get_time_origin.
  • new Fortran interface to interact with the calendar: xios_update_calendar, xios_get_current_date, xios_get_year_length_in_seconds, xios_get_day_length_in_seconds.
  • new Fortran interface for date conversion: xios_date_get_second_of_year, xios_date_get_day_of_year, xios_date_get_fraction_of_year, xios_date_get_second_of_day, xios_date_get_fraction_of_day.
  • two new placeholders are available to format the file name when splitting the output (split_freq_format attribute):
    • %S the number of seconds since the time origin
    • %D the integral number of days since the time origin
File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/trunk/src/test/test_complete.f90

    r537 r549  
    88  INTEGER :: size_loc 
    99  INTEGER :: ierr 
    10    
     10 
    1111  CHARACTER(len=*),PARAMETER :: id="client" 
    1212  INTEGER :: comm 
    13   TYPE(xios_date)      :: start_date, time_origin 
    1413  TYPE(xios_duration)  :: dtime 
    1514  TYPE(xios_context) :: ctx_hdl 
    1615  INTEGER,PARAMETER :: ni_glo=100 
    17   INTEGER,PARAMETER :: nj_glo=100  
    18   INTEGER,PARAMETER :: llm=5  
     16  INTEGER,PARAMETER :: nj_glo=100 
     17  INTEGER,PARAMETER :: llm=5 
    1918  DOUBLE PRECISION  :: lval(llm)=1 
    2019  TYPE(xios_field) :: field_hdl 
     
    3433 
    3534  CALL MPI_INIT(ierr) 
    36    
     35 
    3736  CALL init_wait 
    38   
     37 
    3938!!! XIOS Initialization (get the local communicator) 
    4039 
     
    4241 
    4342  CALL MPI_COMM_RANK(comm,rank,ierr) 
    44   CALL MPI_COMM_SIZE(comm,size_loc,ierr)   
    45    
     43  CALL MPI_COMM_SIZE(comm,size_loc,ierr) 
     44 
    4645 
    4746!########################################################################### 
     
    6665    nj=nj_glo/size_loc 
    6766    IF (n<MOD(nj_glo,size_loc)) nj=nj+1 
    68     IF (n==rank) exit  
     67    IF (n==rank) exit 
    6968    jbegin=jbegin+nj 
    7069  ENDDO 
    71    
     70 
    7271  iend=ibegin+ni-1 ; jend=jbegin+nj-1 
    7372 
     
    7675  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend) 
    7776  field_A_atm(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:) 
    78   
     77 
    7978 
    8079!!! Context ATMOSPHERE 
     
    8382  CALL xios_get_handle("atmosphere",ctx_hdl) 
    8483  CALL xios_set_current_context(ctx_hdl) 
    85    
    86   CALL xios_set_context_attr("atmosphere",calendar_type="Gregorian") 
    87   start_date = xios_date(2000, 01, 01, 00, 00, 00) 
    88   CALL xios_set_context_attr("atmosphere",start_date=start_date) 
    89   time_origin = xios_date(1999, 01, 01, 15, 00, 00) 
    90   CALL xios_set_context_attr("atmosphere",time_origin=time_origin) 
     84 
     85  CALL xios_define_calendar(type="Gregorian", & 
     86                            start_date=xios_date(2000, 01, 01, 00, 00, 00), & 
     87                            time_origin=xios_date(1999, 01, 01, 15, 00, 00)) 
    9188 
    9289  CALL xios_set_axis_attr("axis_atm",size=llm ,value=lval) ; 
     
    104101  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.) 
    105102 
    106 !!! Création d un nouveau champ  
     103!!! Création d un nouveau champ 
    107104 
    108105  CALL xios_get_handle("field_definition",fieldgroup_hdl) 
     
    112109 
    113110  CALL xios_set_attr(field_hdl,field_ref="field_A_atm",name="field_B_atm") 
    114    
     111 
    115112!!! Affectation de ce nouveau champ au fichier avec un nouveau nom 
    116113 
     
    118115  CALL xios_add_child(file_hdl,field_hdl) 
    119116  CALL xios_set_attr(field_hdl,field_ref="field_B_atm",name="field_C_atm") 
    120      
     117 
    121118!!! Definition du timestep 
    122119 
    123120  dtime%second=3600 
    124   CALL xios_set_context_attr("atmosphere", timestep=dtime) 
    125      
     121  CALL xios_set_timestep(timestep=dtime) 
     122 
    126123!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité) 
    127124 
    128125  ni=0 ; lonvalue(:)=0 
    129126  CALL xios_get_domain_attr("domain_atm",ni=ni,lonvalue=lonvalue) 
    130      
     127 
    131128  PRINT *,"ni",ni 
    132129  PRINT *,"lonvalue",lonvalue ; 
     
    137134 
    138135!!! Test des valeurs des champs/fichiers 
    139    
    140   !!! Attribut defini ?  
     136 
     137  !!! Attribut defini ? 
    141138 
    142139  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok) 
     
    144141 
    145142  !!! Recuperer la valeur d un attribut 
    146    
     143 
    147144  CALL xios_get_field_attr("field_A_atm",name=crname) 
    148145  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname) 
    149146 
    150   !!! Champ actif (besoin de fournir la valeur) ?  
     147  !!! Champ actif (besoin de fournir la valeur) ? 
    151148 
    152149    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm") 
     
    173170  CALL xios_get_handle("surface",ctx_hdl) 
    174171  CALL xios_set_current_context(ctx_hdl) 
    175    
    176   CALL xios_set_context_attr("surface",calendar_type="Gregorian") 
    177   start_date = xios_date(2000, 01, 01, 00, 00, 00) 
    178   CALL xios_set_context_attr("surface",start_date=start_date) 
    179   time_origin = xios_date(1999, 01, 01, 15, 00, 00) 
    180   CALL xios_set_context_attr("surface",time_origin=time_origin) 
     172 
     173  CALL xios_define_calendar(type="Gregorian", & 
     174                            start_date=xios_date(2000, 01, 01, 00, 00, 00), & 
     175                            time_origin=xios_date(1999, 01, 01, 15, 00, 00)) 
    181176 
    182177  CALL xios_set_axis_attr("axis_srf",size=llm ,value=lval) ; 
     
    186181  CALL xios_set_domain_attr("domain_srf",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/))) 
    187182 
    188 !!! Création d un nouveau champ  
     183!!! Création d un nouveau champ 
    189184 
    190185  CALL xios_get_handle("field_definition",fieldgroup_hdl) 
     
    194189 
    195190  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf") 
    196    
     191 
    197192!!! Affectation de ce nouveau champ au fichier avec un nouveau nom 
    198193 
     
    200195  CALL xios_add_child(file_hdl,field_hdl) 
    201196  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf") 
    202      
     197 
    203198!!! Definition du timestep 
    204199 
    205200  dtime%second=1800 
    206   CALL xios_set_context_attr("surface", timestep=dtime) 
    207      
     201  CALL xios_set_timestep(timestep=dtime) 
     202 
    208203!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité) 
    209204 
    210205  ni=0 ; lonvalue(:)=0 
    211206  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue=lonvalue) 
    212      
     207 
    213208  PRINT *,"ni",ni 
    214209  PRINT *,"lonvalue",lonvalue ; 
     
    226221 
    227222      CALL xios_get_handle("atmosphere",ctx_hdl) 
    228       CALL xios_set_current_context(ctx_hdl)     
     223      CALL xios_set_current_context(ctx_hdl) 
    229224 
    230225!!! Mise a jour du pas de temps 
     
    239234 
    240235      CALL xios_get_handle("surface",ctx_hdl) 
    241       CALL xios_set_current_context(ctx_hdl)     
     236      CALL xios_set_current_context(ctx_hdl) 
    242237 
    243238!!! Mise a jour du pas de temps 
     
    257252 
    258253!!! Fin des contextes 
    259      
     254 
    260255    CALL xios_context_finalize() 
    261256    CALL xios_get_handle("atmosphere",ctx_hdl) 
    262     CALL xios_set_current_context(ctx_hdl)     
     257    CALL xios_set_current_context(ctx_hdl) 
    263258    CALL xios_context_finalize() 
    264      
     259 
    265260!!! Fin de XIOS 
    266261 
    267262    CALL xios_finalize() 
    268    
     263 
    269264    CALL MPI_FINALIZE(ierr) 
    270    
     265 
    271266  END PROGRAM test_complete 
    272267 
    273268 
    274269 
    275    
    276  
    277    
     270 
     271 
     272 
Note: See TracChangeset for help on using the changeset viewer.