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

    r545 r549  
    88  INTEGER :: size 
    99  INTEGER :: ierr 
    10    
     10 
    1111  CHARACTER(len=*),PARAMETER :: id="client" 
    1212  INTEGER :: comm 
    1313  TYPE(xios_duration) :: dtime 
    1414  TYPE(xios_date) :: date 
     15  CHARACTER(len=10) :: calendar_type 
    1516  TYPE(xios_context) :: ctx_hdl 
    1617  INTEGER,PARAMETER :: ni_glo=100 
    17   INTEGER,PARAMETER :: nj_glo=100  
    18   INTEGER,PARAMETER :: llm=5  
     18  INTEGER,PARAMETER :: nj_glo=100 
     19  INTEGER,PARAMETER :: llm=5 
    1920  DOUBLE PRECISION  :: lval(llm)=1 
    2021  TYPE(xios_field) :: field_hdl 
     
    2223  TYPE(xios_file) :: file_hdl 
    2324  LOGICAL :: ok 
    24    
     25 
    2526  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo 
    2627  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm) 
     
    3233 
    3334  CALL MPI_INIT(ierr) 
    34    
     35 
    3536  CALL init_wait 
    36   
     37 
    3738!!! XIOS Initialization (get the local communicator) 
    3839 
     
    4041 
    4142  CALL MPI_COMM_RANK(comm,rank,ierr) 
    42   CALL MPI_COMM_SIZE(comm,size,ierr)   
    43    
     43  CALL MPI_COMM_SIZE(comm,size,ierr) 
     44 
    4445  DO j=1,nj_glo 
    4546    DO i=1,ni_glo 
     
    5758    nj=nj_glo/size 
    5859    IF (n<MOD(nj_glo,size)) nj=nj+1 
    59     IF (n==rank) exit  
     60    IF (n==rank) exit 
    6061    jbegin=jbegin+nj 
    6162  ENDDO 
    62    
     63 
    6364  iend=ibegin+ni-1 ; jend=jbegin+nj-1 
    6465 
     
    6768  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend) 
    6869  field_A(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:) 
    69    
     70 
    7071  CALL xios_context_initialize("test",comm) 
    7172  CALL xios_get_handle("test",ctx_hdl) 
    7273  CALL xios_set_current_context(ctx_hdl) 
    73    
    74   CALL xios_set_context_attr("test",calendar_type="Gregorian")  
     74 
     75  CALL xios_get_calendar_type(calendar_type) 
     76  PRINT *, "calendar_type = ", calendar_type 
     77 
    7578  CALL xios_set_axis_attr("axis_A",size=llm ,value=lval) ; 
    7679  CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj) 
     
    7881  CALL xios_set_domain_attr("domain_A",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/))) 
    7982  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.) 
    80    
     83 
    8184  CALL xios_get_handle("field_definition",fieldgroup_hdl) 
    8285  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B") 
    8386  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B") 
    84    
     87 
    8588  CALL xios_get_handle("output",file_hdl) 
    8689  CALL xios_add_child(file_hdl,field_hdl) 
    8790  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_C") 
    88      
    89   
     91 
    9092  dtime%second = 3600 
    91   CALL xios_set_context_attr("test", timestep=dtime) 
     93  CALL xios_set_timestep(dtime) 
    9294 
    93   ! Create the calendar before closing the context definition 
    94   ! so that calendar operations can be used 
    95   CALL xios_set_calendar() 
    96   CALL xios_get_context_attr("test", time_origin=date) 
     95  ! The calendar is created as soon as the calendar type is defined. This way 
     96  ! calendar operations can be used before the context definition is closed 
     97  CALL xios_get_time_origin(date) 
     98  PRINT *, "--> year length = ", xios_get_year_length_in_seconds(date%year) 
     99  PRINT *, "--> day length = ", xios_get_day_length_in_seconds() 
    97100  PRINT *, "time_origin = ", date 
     101  PRINT *, "xios_date_get_second_of_year(time_origin) = ", xios_date_get_second_of_year(date) 
     102  PRINT *, "xios_date_get_day_of_year(time_origin) = ", xios_date_get_day_of_year(date) 
     103  PRINT *, "xios_date_get_fraction_of_year(time_origin) = ", xios_date_get_fraction_of_year(date) 
     104  PRINT *, "xios_date_get_second_of_day(time_origin) = ", xios_date_get_second_of_day(date) 
     105  PRINT *, "xios_date_get_fraction_of_day(time_origin) = ", xios_date_get_fraction_of_day(date) 
    98106  dtime%timestep = 1 
    99107  dtime = 0.5 * dtime 
     
    103111  PRINT *, "xios_date_convert_to_seconds(date) = ", xios_date_convert_to_seconds(date) 
    104112  PRINT *, "xios_date_convert_to_seconds(date - 2.5h) = ", xios_date_convert_to_seconds(date - 2.5 * xios_hour) 
    105    
     113 
    106114  ni=0 ; lonvalue(:)=0 
    107115  CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue=lonvalue) 
    108    
     116 
    109117  print *,"ni",ni 
    110118  print *,"lonvalue",lonvalue ; 
     
    113121  PRINT *,"field_A : attribute enabled is defined ? ",ok 
    114122  CALL xios_close_context_definition() 
    115    
     123 
    116124  PRINT*,"field field_A is active ? ",xios_field_is_active("field_A") 
    117125  DO ts=1,24*10 
     
    123131  CALL xios_context_finalize() 
    124132  CALL xios_finalize() 
    125    
     133 
    126134  CALL MPI_FINALIZE(ierr) 
    127    
     135 
    128136END PROGRAM test_client 
    129137 
    130138 
    131    
    132139 
    133    
     140 
     141 
Note: See TracChangeset for help on using the changeset viewer.