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_cs.f90

    r537 r549  
    55  INTEGER :: size 
    66  INTEGER :: ierr 
    7    
     7 
    88  CALL MPI_INIT(ierr) 
    99  CALL MPI_COMM_RANK(MPI_COMM_WORLD,rank,ierr) 
    1010  CALL MPI_COMM_SIZE(MPI_COMM_WORLD,size,ierr) 
    11    
     11 
    1212  IF (rank<11) THEN 
    1313   CALL client("client",rank,11) 
    14   ELSE  
     14  ELSE 
    1515    CALL server 
    1616  ENDIF 
    17    
    18    
     17 
     18 
    1919  CALL MPI_FINALIZE(ierr) 
    20    
     20 
    2121END PROGRAM test_cs 
    2222 
     
    3232  TYPE(xios_duration) :: dtime 
    3333  TYPE(xios_context) :: ctx_hdl 
    34   INTEGER,PARAMETER :: ni_glo=100  
    35   INTEGER,PARAMETER :: nj_glo=100  
    36   INTEGER,PARAMETER :: llm=3  
     34  INTEGER,PARAMETER :: ni_glo=100 
     35  INTEGER,PARAMETER :: nj_glo=100 
     36  INTEGER,PARAMETER :: llm=3 
    3737  DOUBLE PRECISION  :: lval(llm)=(/1.0,2.0,3.0/) 
    3838  TYPE(xios_field) :: field_hdl 
    3939  TYPE(xios_fieldgroup) :: fieldgroup_hdl 
    4040  TYPE(xios_file) :: file_hdl 
    41    
    42    
     41 
     42 
    4343  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo 
    4444  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm) 
     
    4747  INTEGER :: ni,ibegin,iend,nj,jbegin,jend,data_ibegin,data_ni 
    4848  INTEGER :: i,j,k,l,ts,n,nij_begin 
    49    
    50    
     49 
     50 
    5151  CALL init_wait 
    52    
    53    
     52 
     53 
    5454  DO j=1,nj_glo 
    5555    DO i=1,ni_glo 
     
    6363  ni=ni_glo ; ibegin=1 
    6464 
    65    
     65 
    6666  nij_begin=1 
    6767  DO n=0,size-1 
     
    7070    IF (n==rank) THEN 
    7171      ibegin=1 ; iend=ni_glo ; ni=iend-ibegin+1 
    72       jbegin=(nij_begin-1)/ni_glo +1  
     72      jbegin=(nij_begin-1)/ni_glo +1 
    7373      jend=MOD(nij_begin-1 + data_ni-1,ni_glo) +1 
    7474      nj = jend-jbegin+1 
     
    7979    ENDIF 
    8080  ENDDO 
    81    
     81 
    8282 
    8383  ALLOCATE(lon(ni),lat(nj),field_A(data_ni,llm),lonvalue(ni*nj)) 
     
    9292    field_A(k,:)=field_A_glo(i,j,:) 
    9393  ENDDO 
    94    
     94 
    9595  mask(:,:)=.TRUE. 
    9696  mask(1:ni,6)=.TRUE. 
    97    
     97 
    9898 
    9999  CALL xios_initialize(id,return_comm=comm) 
     
    102102  CALL xios_get_handle("test",ctx_hdl) 
    103103  CALL xios_set_current_context(ctx_hdl) 
    104    
    105   CALL xios_set_context_attr("test",calendar_type="Gregorian")  
    106   CALL xios_set_context_attr("test",calendar_type="Gregorian")  
    107   CALL xios_set_context_attr("test",calendar_type="Gregorian")  
    108 !  CALL xios_set_context_attr("test",start_date="01/01/2000 - 00:00:00") 
    109   CALL xios_set_context_attr("test",calendar_type="Gregorian")  
     104 
     105! CALL xios_define_calendar(type="Gregorian") 
     106! CALL xios_set_start_date(start_date=xios_date(2000, 01, 01, 00, 00, 00)) 
    110107  CALL xios_set_axis_attr("axis_A",size=llm ,value=lval) ; 
    111108  CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, iend=iend,jbegin=jbegin,jend=jend) 
    112 !  CALL xios_set_domain_attr("domain_A",zoom_ni=10,zoom_ibegin=5,zoom_nj=nj_glo,zoom_jbegin=1) 
     109! CALL xios_set_domain_attr("domain_A",zoom_ni=10,zoom_ibegin=5,zoom_nj=nj_glo,zoom_jbegin=1) 
    113110  CALL xios_set_domain_attr("domain_A",data_dim=1, data_ibegin=data_ibegin, data_ni=data_ni) 
    114111  CALL xios_set_domain_attr("domain_A",lonvalue=lon,latvalue=lat) 
    115 !  CALL xios_set_domain_attr("domain_A",mask=mask) 
     112! CALL xios_set_domain_attr("domain_A",mask=mask) 
    116113  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.) 
    117    
     114 
    118115  CALL xios_get_handle("field_definition",fieldgroup_hdl) 
    119116  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B") 
    120117  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B") 
    121    
     118 
    122119  CALL xios_get_handle("output",file_hdl) 
    123120  CALL xios_add_child(file_hdl,field_hdl) 
    124121  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_C") 
    125      
    126   
     122 
     123 
    127124    dtime%second=3600 
    128     CALL xios_set_context_attr("test", timestep=dtime) 
    129      
     125    CALL xios_set_timestep(timestep=dtime) 
     126 
    130127!    ni=0 ; lonvalue(:)=0 
    131128!    CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue=lonvalue) 
    132      
     129 
    133130!    print *,"ni",ni 
    134131!    print *,"lonvalue",lonvalue ; 
    135132 
    136133    CALL xios_close_context_definition() 
    137      
     134 
    138135    PRINT*,"field field_A is active ? ",xios_field_is_active("field_A") 
    139136    DO ts=1,24*10 
     
    142139      CALL wait_us(5000) ; 
    143140    ENDDO 
    144    
     141 
    145142    CALL xios_context_finalize() 
    146143    CALL xios_finalize() 
    147       
     144 
    148145  END SUBROUTINE client 
    149    
    150146 
    151    
     147 
     148 
    152149  SUBROUTINE server 
    153150  USE xios 
    154151  IMPLICIT NONE 
    155    
     152 
    156153    CALL xios_init_server 
    157   
     154 
    158155  END SUBROUTINE server 
    159    
    160156 
    161    
     157 
     158 
Note: See TracChangeset for help on using the changeset viewer.