source: XIOS/trunk/src/test/test_xios_interface.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: 10.4 KB
Line 
1PROGRAM test_xios_interface
2
3  ! This test is based on test_complete
4  USE xios
5  USE mod_wait
6  IMPLICIT NONE
7  INCLUDE "mpif.h"
8  INTEGER :: rank
9  INTEGER :: size_loc
10  INTEGER :: ierr
11
12  CHARACTER(len=*),PARAMETER :: id="client"
13  INTEGER :: comm
14  TYPE(xios_date)      :: start_date, time_origin
15  TYPE(xios_duration)  :: dtime
16  TYPE(xios_context) :: ctx_hdl
17  INTEGER,PARAMETER :: ni_glo=10
18  INTEGER,PARAMETER :: nj_glo=10
19  INTEGER,PARAMETER :: llm=5
20  DOUBLE PRECISION  :: lval(llm)=1
21  TYPE(xios_field) :: field_hdl
22  TYPE(xios_fieldgroup) :: fieldgroup_hdl
23  TYPE(xios_file) :: file_hdl
24  LOGICAL :: ok
25  CHARACTER(len=256) :: crname
26
27  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
28  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
29  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A_atm(:,:,:), field_A_srf(:,:), lonvalue(:)
30  INTEGER, ALLOCATABLE :: kindex(:)
31  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
32  INTEGER :: i,j,l,ts,n, nb_pt
33
34  INTEGER :: var_val_int
35  REAL :: var_val_float
36  DOUBLE PRECISION :: var_val_double
37  LOGICAL :: var_val_bool
38  CHARACTER(len=256) :: var_val_char =""
39  CHARACTER(len=256) :: var_id
40
41!!! MPI Initialization
42
43  CALL MPI_INIT(ierr)
44
45  CALL init_wait
46
47!!! XIOS Initialization (get the local communicator)
48
49  CALL xios_initialize(id,return_comm=comm)
50
51  CALL MPI_COMM_RANK(comm,rank,ierr)
52  CALL MPI_COMM_SIZE(comm,size_loc,ierr)
53
54!-------------------------------------------------------------------------------
55!
56! Define all neccessary values for test
57!
58!-------------------------------------------------------------------------------
59!###########################################################################
60! Contexte ATM
61!###########################################################################
62
63!!! Initialisation des coordonnées globales et locales pour la grille réguliÚre
64
65  DO j=1,nj_glo
66    DO i=1,ni_glo
67      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
68      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
69      DO l=1,llm
70        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
71      ENDDO
72    ENDDO
73  ENDDO
74  ni=ni_glo ; ibegin=1
75
76  jbegin=1
77  DO n=0,size_loc-1
78    nj=nj_glo/size_loc
79    IF (n<MOD(nj_glo,size_loc)) nj=nj+1
80    IF (n==rank) exit
81    jbegin=jbegin+nj
82  ENDDO
83
84  iend=ibegin+ni-1 ; jend=jbegin+nj-1
85
86  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A_atm(0:ni+1,-1:nj+2,llm),lonvalue(ni*nj))
87  lon(:,:)=lon_glo(ibegin:iend,jbegin:jend)
88  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend)
89  field_A_atm(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:)
90
91
92!!! Context ATMOSPHERE
93
94  CALL xios_context_initialize("atmosphere",comm)
95  CALL xios_get_handle("atmosphere",ctx_hdl)
96  CALL xios_set_current_context(ctx_hdl)
97
98  CALL xios_define_calendar(type="Gregorian", &
99                            start_date=xios_date(2000, 01, 01, 00, 00, 00), &
100                            time_origin=xios_date(1999, 01, 01, 15, 00, 00))
101
102  CALL xios_set_axis_attr("axis_atm",size=llm ,value=lval) ;
103
104  CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
105  CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
106  CALL xios_set_domain_attr("domain_atm",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
107
108  CALL xios_set_domain_attr("domain_atm_zoom",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
109  CALL xios_set_domain_attr("domain_atm_zoom",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
110  CALL xios_set_domain_attr("domain_atm_zoom",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
111
112!!! Activation du groupe field_definition
113  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
114
115!!! Création d un nouveau champ
116  CALL xios_get_handle("field_definition",fieldgroup_hdl)
117  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_atm")
118
119!!! Heritage des attributs d un autre champ
120  CALL xios_set_attr(field_hdl,field_ref="field_A_atm",name="field_B_atm")
121
122!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
123
124  CALL xios_get_handle("output_atmosphere",file_hdl)
125  CALL xios_add_child(file_hdl,field_hdl)
126  CALL xios_set_attr(field_hdl,field_ref="field_B_atm",name="field_C_atm")
127
128!!! Definition du timestep
129
130  dtime%second=3600
131  CALL xios_set_timestep(timestep=dtime)
132
133!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
134
135  ni=0 ; lonvalue(:)=0
136  CALL xios_get_domain_attr("domain_atm",ni=ni,lonvalue=lonvalue)
137
138  PRINT *,"ni",ni
139  PRINT *,"lonvalue",lonvalue ;
140
141!!! Fin de la definition du contexte
142
143  CALL xios_close_context_definition()
144
145!!! Test des valeurs des champs/fichiers
146
147  !!! Attribut defini ?
148
149  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok)
150  PRINT *,"field_A_atm : attribute enabled is defined ? ",ok
151
152  !!! Recuperer la valeur d un attribut
153
154  CALL xios_get_field_attr("field_A_atm",name=crname)
155  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname)
156
157  !!! Champ actif (besoin de fournir la valeur) ?
158
159    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm")
160
161  !!! Champ defini ?
162
163    PRINT*,"field field_A_atm is valid ?",xios_is_valid_field("field_A_atm")
164
165
166!###########################################################################
167! Contexte SRF
168!###########################################################################
169
170!!! Initialisation des coordonnées globales et locales pour la grille indexee (1 point sur 2)
171
172    nb_pt=ni*nj/2
173    ALLOCATE(kindex(nb_pt),field_A_srf(nb_pt,llm))
174    DO i=1,nb_pt
175      kindex(i)=2*i-1
176    ENDDO
177    field_A_srf(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin:iend:2,jbegin:jend,:),(/ nb_pt,llm /))
178
179  CALL xios_context_initialize("surface",comm)
180  CALL xios_get_handle("surface",ctx_hdl)
181  CALL xios_set_current_context(ctx_hdl)
182
183  CALL xios_define_calendar(type="Gregorian", &
184                            start_date=xios_date(2000, 01, 01, 00, 00, 00), &
185                            time_origin=xios_date(1999, 01, 01, 15, 00, 00))
186
187  CALL xios_set_axis_attr("axis_srf",size=llm ,value=lval) ;
188  CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
189  CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt)
190  CALL xios_set_domain_attr("domain_srf",data_n_index=nb_pt, data_i_index=kindex)
191  CALL xios_set_domain_attr("domain_srf",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
192
193!!! Création d un nouveau champ
194
195  CALL xios_get_handle("field_definition",fieldgroup_hdl)
196  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_srf")
197
198!!! Heritage des attributs d un autre champ
199
200  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf")
201
202!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
203
204  CALL xios_get_handle("output_surface",file_hdl)
205  CALL xios_add_child(file_hdl,field_hdl)
206  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf")
207
208!!! Definition du timestep
209
210  dtime%second=1800
211  CALL xios_set_timestep(timestep=dtime)
212
213!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
214
215  ni=0 ; lonvalue(:)=0
216  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue=lonvalue)
217
218  PRINT *,"ni",ni
219  PRINT *,"lonvalue",lonvalue ;
220
221!!! Fin de la definition du contexte SRF
222!-------------------------------------------------------------------------------
223!
224! Get/set variable in differenct contexts
225!
226!-------------------------------------------------------------------------------
227
228  !! Try getting some variable values
229  var_id = "my_attribute1"
230  ok = xios_getVar(var_id, var_val_char)
231  if (ok) then
232    print*, "Value of ", var_id, " is : ", var_val_char
233  end if
234
235  var_id = "my_attribute2"
236  ok = xios_getVar(var_id, var_val_int)
237  if (ok) then
238    print*, "Value of ", var_id, " is : ", var_val_int
239  end if
240
241  var_id = "my_attribute3"
242  ok = xios_getVar(var_id, var_val_float)
243  if (ok) then
244    print*, "Value of ", var_id, " is : ", var_val_float
245  end if
246
247  var_id = "my_attribute4"
248  ok = xios_getVar(var_id, var_val_double)
249  if (ok) then
250    print*, "Value of ", var_id, " is : ", var_val_double
251  end if
252
253  var_id = "my_global_attribute_bool"
254  ok = xios_getVar(var_id, var_val_bool)
255  if (ok) then
256    print*, "Value of ", var_id, " is : ", var_val_bool
257  end if
258
259  !! Try setting some variables
260  var_id = "my_attribute1"
261  var_val_char = "ocean_att"
262  ok = xios_setVar(var_id, var_val_char)
263  if (ok) then
264    print*, "New value of ", var_id, " is : ", var_val_char
265  end if
266
267  var_id = "my_attribute2"
268  var_val_int = 50
269  ok = xios_setVar(var_id, var_val_int)
270  if (ok) then
271    print*, "New value of ", var_id, " is : ", var_val_int
272  end if
273
274  var_id = "my_attribute3"
275  var_val_float = 7.8
276  ok = xios_setVar(var_id, var_val_float)
277  if (ok) then
278    print*, "New value of ", var_id, " is : ", var_val_float
279  end if
280
281  var_id = "my_attribute4"
282  var_val_double=300.21
283  ok = xios_setVar(var_id, var_val_double)
284  if (ok) then
285    print*, "New value of ", var_id, " is : ", var_val_double
286  end if
287
288  var_id = "my_global_attribute_bool"
289  var_val_bool = .true.
290  ok = xios_setVar(var_id, var_val_bool)
291  if (ok) then
292    print*, "New value of ", var_id, " is : ", var_val_bool
293  end if
294!
295!!!! Fin de la definition du contexte SRF
296  CALL xios_close_context_definition()
297
298!####################################################################################
299!!! Boucle temporelle
300!####################################################################################
301
302    DO ts=1,24*10
303
304      CALL xios_get_handle("atmosphere",ctx_hdl)
305      CALL xios_set_current_context(ctx_hdl)
306
307!!! Mise a jour du pas de temps
308
309      CALL xios_update_calendar(ts)
310
311!!! On donne la valeur du champ atm
312
313      CALL xios_send_field("field_A_atm",field_A_atm)
314
315!!! On change de contexte
316
317      CALL xios_get_handle("surface",ctx_hdl)
318      CALL xios_set_current_context(ctx_hdl)
319
320!!! Mise a jour du pas de temps
321
322      CALL xios_update_calendar(ts)
323
324!!! On donne la valeur du champ srf
325
326      CALL xios_send_field("field_A_srf",field_A_srf)
327
328      CALL wait_us(5000) ;
329    ENDDO
330
331!####################################################################################
332!!! Finalisation
333!####################################################################################
334
335!!! Fin des contextes
336
337    CALL xios_context_finalize()
338    CALL xios_get_handle("atmosphere",ctx_hdl)
339    CALL xios_set_current_context(ctx_hdl)
340    CALL xios_context_finalize()
341
342!!! Fin de XIOS
343
344    CALL xios_finalize()
345
346    CALL MPI_FINALIZE(ierr)
347
348  END PROGRAM test_xios_interface
349
350
351
352
353
354
Note: See TracBrowser for help on using the repository browser.