source: XIOS/trunk/src/test/test_cs.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: 3.9 KB
Line 
1PROGRAM test_cs
2IMPLICIT NONE
3  INCLUDE "mpif.h"
4  INTEGER :: rank
5  INTEGER :: size
6  INTEGER :: ierr
7
8  CALL MPI_INIT(ierr)
9  CALL MPI_COMM_RANK(MPI_COMM_WORLD,rank,ierr)
10  CALL MPI_COMM_SIZE(MPI_COMM_WORLD,size,ierr)
11
12  IF (rank<11) THEN
13   CALL client("client",rank,11)
14  ELSE
15    CALL server
16  ENDIF
17
18
19  CALL MPI_FINALIZE(ierr)
20
21END PROGRAM test_cs
22
23  SUBROUTINE client(id,rank,size)
24  USE xios
25  USE mod_wait
26  IMPLICIT NONE
27  INCLUDE 'mpif.h'
28  CHARACTER(len=*) :: id
29  INTEGER :: rank
30  INTEGER :: size
31  INTEGER :: comm
32  TYPE(xios_duration) :: dtime
33  TYPE(xios_context) :: ctx_hdl
34  INTEGER,PARAMETER :: ni_glo=100
35  INTEGER,PARAMETER :: nj_glo=100
36  INTEGER,PARAMETER :: llm=3
37  DOUBLE PRECISION  :: lval(llm)=(/1.0,2.0,3.0/)
38  TYPE(xios_field) :: field_hdl
39  TYPE(xios_fieldgroup) :: fieldgroup_hdl
40  TYPE(xios_file) :: file_hdl
41
42
43  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
44  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
45  DOUBLE PRECISION,ALLOCATABLE :: lon(:),lat(:),field_A(:,:), lonvalue(:) ;
46  LOGICAL,ALLOCATABLE :: mask(:,:)
47  INTEGER :: ni,ibegin,iend,nj,jbegin,jend,data_ibegin,data_ni
48  INTEGER :: i,j,k,l,ts,n,nij_begin
49
50
51  CALL init_wait
52
53
54  DO j=1,nj_glo
55    DO i=1,ni_glo
56      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
57      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
58      DO l=1,llm
59        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
60      ENDDO
61    ENDDO
62  ENDDO
63  ni=ni_glo ; ibegin=1
64
65
66  nij_begin=1
67  DO n=0,size-1
68    data_ni=(ni_glo*nj_glo)/size
69    IF (n < MOD (ni_glo*nj_glo,size)) data_ni=data_ni+1
70    IF (n==rank) THEN
71      ibegin=1 ; iend=ni_glo ; ni=iend-ibegin+1
72      jbegin=(nij_begin-1)/ni_glo +1
73      jend=MOD(nij_begin-1 + data_ni-1,ni_glo) +1
74      nj = jend-jbegin+1
75      data_ibegin=MOD(nij_begin-1,ni_glo)
76      exit
77    ELSE
78      nij_begin=nij_begin+data_ni
79    ENDIF
80  ENDDO
81
82
83  ALLOCATE(lon(ni),lat(nj),field_A(data_ni,llm),lonvalue(ni*nj))
84  ALLOCATE(mask(ni,nj))
85  lon(:)=lon_glo(ibegin:iend,1)
86  lat(:)=lat_glo(1,jbegin:jend)
87
88  DO k=1,data_ni
89    n=k-1+(jbegin-1)*ni_glo+data_ibegin
90    i=MOD(n,ni_glo)+1
91    j=n/ni_glo+1
92    field_A(k,:)=field_A_glo(i,j,:)
93  ENDDO
94
95  mask(:,:)=.TRUE.
96  mask(1:ni,6)=.TRUE.
97
98
99  CALL xios_initialize(id,return_comm=comm)
100
101  CALL xios_context_initialize("test",comm)
102  CALL xios_get_handle("test",ctx_hdl)
103  CALL xios_set_current_context(ctx_hdl)
104
105! CALL xios_define_calendar(type="Gregorian")
106! CALL xios_set_start_date(start_date=xios_date(2000, 01, 01, 00, 00, 00))
107  CALL xios_set_axis_attr("axis_A",size=llm ,value=lval) ;
108  CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, iend=iend,jbegin=jbegin,jend=jend)
109! CALL xios_set_domain_attr("domain_A",zoom_ni=10,zoom_ibegin=5,zoom_nj=nj_glo,zoom_jbegin=1)
110  CALL xios_set_domain_attr("domain_A",data_dim=1, data_ibegin=data_ibegin, data_ni=data_ni)
111  CALL xios_set_domain_attr("domain_A",lonvalue=lon,latvalue=lat)
112! CALL xios_set_domain_attr("domain_A",mask=mask)
113  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
114
115  CALL xios_get_handle("field_definition",fieldgroup_hdl)
116  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B")
117  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B")
118
119  CALL xios_get_handle("output",file_hdl)
120  CALL xios_add_child(file_hdl,field_hdl)
121  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_C")
122
123
124    dtime%second=3600
125    CALL xios_set_timestep(timestep=dtime)
126
127!    ni=0 ; lonvalue(:)=0
128!    CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue=lonvalue)
129
130!    print *,"ni",ni
131!    print *,"lonvalue",lonvalue ;
132
133    CALL xios_close_context_definition()
134
135    PRINT*,"field field_A is active ? ",xios_field_is_active("field_A")
136    DO ts=1,24*10
137      CALL xios_update_calendar(ts)
138      CALL xios_send_field("field_A",field_A)
139      CALL wait_us(5000) ;
140    ENDDO
141
142    CALL xios_context_finalize()
143    CALL xios_finalize()
144
145  END SUBROUTINE client
146
147
148
149  SUBROUTINE server
150  USE xios
151  IMPLICIT NONE
152
153    CALL xios_init_server
154
155  END SUBROUTINE server
156
157
158
Note: See TracBrowser for help on using the repository browser.