source: XIOS/trunk/src/test/test_client.f90 @ 549

Last change on this file since 549 was 549, checked in by rlacroix, 9 years ago

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
  • Property copyright set to
    Software name : XIOS (Xml I/O Server)
    http://forge.ipsl.jussieu.fr/ioserver
    Creation date : January 2009
    Licence : CeCCIL version2
    see license file in root directory : Licence_CeCILL_V2-en.txt
    or http://www.cecill.info/licences/Licence_CeCILL_V2-en.html
    Holder : CEA/LSCE (Laboratoire des Sciences du CLimat et de l'Environnement)
    CNRS/IPSL (Institut Pierre Simon Laplace)
    Project Manager : Yann Meurdesoif
    yann.meurdesoif@cea.fr
File size: 4.5 KB
RevLine 
[374]1PROGRAM test_client
2
3  USE xios
4  USE mod_wait
5  IMPLICIT NONE
6  INCLUDE "mpif.h"
7  INTEGER :: rank
8  INTEGER :: size
9  INTEGER :: ierr
[549]10
[374]11  CHARACTER(len=*),PARAMETER :: id="client"
12  INTEGER :: comm
[537]13  TYPE(xios_duration) :: dtime
[545]14  TYPE(xios_date) :: date
[549]15  CHARACTER(len=10) :: calendar_type
[374]16  TYPE(xios_context) :: ctx_hdl
[432]17  INTEGER,PARAMETER :: ni_glo=100
[549]18  INTEGER,PARAMETER :: nj_glo=100
19  INTEGER,PARAMETER :: llm=5
[432]20  DOUBLE PRECISION  :: lval(llm)=1
[374]21  TYPE(xios_field) :: field_hdl
22  TYPE(xios_fieldgroup) :: fieldgroup_hdl
23  TYPE(xios_file) :: file_hdl
[432]24  LOGICAL :: ok
[549]25
[374]26  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
27  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
28  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A(:,:,:), lonvalue(:) ;
29  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
30  INTEGER :: i,j,l,ts,n
31
[455]32!!! MPI Initialization
33
[374]34  CALL MPI_INIT(ierr)
[549]35
[374]36  CALL init_wait
[549]37
[455]38!!! XIOS Initialization (get the local communicator)
39
40  CALL xios_initialize(id,return_comm=comm)
41
42  CALL MPI_COMM_RANK(comm,rank,ierr)
[549]43  CALL MPI_COMM_SIZE(comm,size,ierr)
44
[374]45  DO j=1,nj_glo
46    DO i=1,ni_glo
47      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
48      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
49      DO l=1,llm
50        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
51      ENDDO
52    ENDDO
53  ENDDO
54  ni=ni_glo ; ibegin=1
55
56  jbegin=1
57  DO n=0,size-1
58    nj=nj_glo/size
59    IF (n<MOD(nj_glo,size)) nj=nj+1
[549]60    IF (n==rank) exit
[374]61    jbegin=jbegin+nj
62  ENDDO
[549]63
[374]64  iend=ibegin+ni-1 ; jend=jbegin+nj-1
65
66  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni*nj))
67  lon(:,:)=lon_glo(ibegin:iend,jbegin:jend)
68  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend)
69  field_A(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:)
[549]70
[374]71  CALL xios_context_initialize("test",comm)
72  CALL xios_get_handle("test",ctx_hdl)
73  CALL xios_set_current_context(ctx_hdl)
[549]74
75  CALL xios_get_calendar_type(calendar_type)
76  PRINT *, "calendar_type = ", calendar_type
77
[374]78  CALL xios_set_axis_attr("axis_A",size=llm ,value=lval) ;
79  CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
80  CALL xios_set_domain_attr("domain_A",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
81  CALL xios_set_domain_attr("domain_A",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
82  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
[549]83
[374]84  CALL xios_get_handle("field_definition",fieldgroup_hdl)
85  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B")
86  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B")
[549]87
[374]88  CALL xios_get_handle("output",file_hdl)
89  CALL xios_add_child(file_hdl,field_hdl)
90  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_C")
[549]91
[545]92  dtime%second = 3600
[549]93  CALL xios_set_timestep(dtime)
[374]94
[549]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()
[545]100  PRINT *, "time_origin = ", date
[549]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)
[545]106  dtime%timestep = 1
107  dtime = 0.5 * dtime
108  PRINT *, "duration = ", dtime
109  date = date + 3 * (dtime + dtime)
110  PRINT *, "date = time_origin + 3 * (duration + duration) = ", date
111  PRINT *, "xios_date_convert_to_seconds(date) = ", xios_date_convert_to_seconds(date)
112  PRINT *, "xios_date_convert_to_seconds(date - 2.5h) = ", xios_date_convert_to_seconds(date - 2.5 * xios_hour)
[549]113
[545]114  ni=0 ; lonvalue(:)=0
115  CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue=lonvalue)
[549]116
[545]117  print *,"ni",ni
118  print *,"lonvalue",lonvalue ;
119
120  CALL xios_is_defined_field_attr("field_A",enabled=ok)
121  PRINT *,"field_A : attribute enabled is defined ? ",ok
122  CALL xios_close_context_definition()
[549]123
[545]124  PRINT*,"field field_A is active ? ",xios_field_is_active("field_A")
125  DO ts=1,24*10
126    CALL xios_update_calendar(ts)
127    CALL xios_send_field("field_A",field_A)
128    CALL wait_us(5000) ;
129  ENDDO
130
131  CALL xios_context_finalize()
132  CALL xios_finalize()
[549]133
[374]134  CALL MPI_FINALIZE(ierr)
[549]135
[374]136END PROGRAM test_client
137
138
139
[549]140
141
Note: See TracBrowser for help on using the repository browser.