source: XIOS/trunk/src/test/test_xios_interface.f90 @ 537

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

Add a new attribute type for durations and use it for the context's timestep.

Note that the "xios_time" type and the "xios_set_timestep" procedure have been removed from the Fortran interface. Instead, the "xios_duration" type and the "xios_get_context_attr"/"xios_set_context_attr" procedures should now be used to get/set the timestep.

  • 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.7 KB
RevLine 
[489]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
[532]14  TYPE(xios_date)      :: start_date, time_origin
[537]15  TYPE(xios_duration)  :: dtime
[489]16  TYPE(xios_context) :: ctx_hdl
[510]17  INTEGER,PARAMETER :: ni_glo=10
18  INTEGER,PARAMETER :: nj_glo=10
[489]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_set_context_attr("atmosphere",calendar_type="Gregorian")
[532]99  start_date = xios_date(2000, 01, 01, 00, 00, 00)
100  CALL xios_set_context_attr("atmosphere",start_date=start_date)
101  time_origin = xios_date(1999, 01, 01, 15, 00, 00)
102  CALL xios_set_context_attr("atmosphere",time_origin=time_origin)
[489]103
104  CALL xios_set_axis_attr("axis_atm",size=llm ,value=lval) ;
105
106  CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
107  CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
108  CALL xios_set_domain_attr("domain_atm",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
109
110  CALL xios_set_domain_attr("domain_atm_zoom",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
111  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)
112  CALL xios_set_domain_attr("domain_atm_zoom",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
113
114!!! Activation du groupe field_definition
115  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
116
117!!! Création d un nouveau champ
118  CALL xios_get_handle("field_definition",fieldgroup_hdl)
119  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_atm")
120
121!!! Heritage des attributs d un autre champ
122  CALL xios_set_attr(field_hdl,field_ref="field_A_atm",name="field_B_atm")
123
124!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
125
126  CALL xios_get_handle("output_atmosphere",file_hdl)
127  CALL xios_add_child(file_hdl,field_hdl)
128  CALL xios_set_attr(field_hdl,field_ref="field_B_atm",name="field_C_atm")
129
130!!! Definition du timestep
131
132  dtime%second=3600
[537]133  CALL xios_set_context_attr("atmosphere", timestep=dtime)
[489]134
135!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
136
137  ni=0 ; lonvalue(:)=0
138  CALL xios_get_domain_attr("domain_atm",ni=ni,lonvalue=lonvalue)
139
140  PRINT *,"ni",ni
141  PRINT *,"lonvalue",lonvalue ;
142
143!!! Fin de la definition du contexte
144
145  CALL xios_close_context_definition()
146
147!!! Test des valeurs des champs/fichiers
148
149  !!! Attribut defini ?
150
151  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok)
152  PRINT *,"field_A_atm : attribute enabled is defined ? ",ok
153
154  !!! Recuperer la valeur d un attribut
155
156  CALL xios_get_field_attr("field_A_atm",name=crname)
157  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname)
158
159  !!! Champ actif (besoin de fournir la valeur) ?
160
161    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm")
162
163  !!! Champ defini ?
164
165    PRINT*,"field field_A_atm is valid ?",xios_is_valid_field("field_A_atm")
166
167
168!###########################################################################
169! Contexte SRF
170!###########################################################################
171
172!!! Initialisation des coordonnées globales et locales pour la grille indexee (1 point sur 2)
173
174    nb_pt=ni*nj/2
175    ALLOCATE(kindex(nb_pt),field_A_srf(nb_pt,llm))
176    DO i=1,nb_pt
177      kindex(i)=2*i-1
178    ENDDO
179    field_A_srf(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin:iend:2,jbegin:jend,:),(/ nb_pt,llm /))
180
181  CALL xios_context_initialize("surface",comm)
182  CALL xios_get_handle("surface",ctx_hdl)
183  CALL xios_set_current_context(ctx_hdl)
184
185  CALL xios_set_context_attr("surface",calendar_type="Gregorian")
[532]186  start_date = xios_date(2000, 01, 01, 00, 00, 00)
187  CALL xios_set_context_attr("surface",start_date=start_date)
188  time_origin = xios_date(1999, 01, 01, 15, 00, 00)
189  CALL xios_set_context_attr("surface",time_origin=time_origin)
[489]190
191  CALL xios_set_axis_attr("axis_srf",size=llm ,value=lval) ;
192  CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
193  CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt)
194  CALL xios_set_domain_attr("domain_srf",data_n_index=nb_pt, data_i_index=kindex)
195  CALL xios_set_domain_attr("domain_srf",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
196
197!!! Création d un nouveau champ
198
199  CALL xios_get_handle("field_definition",fieldgroup_hdl)
200  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_srf")
201
202!!! Heritage des attributs d un autre champ
203
204  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf")
205
206!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
207
208  CALL xios_get_handle("output_surface",file_hdl)
209  CALL xios_add_child(file_hdl,field_hdl)
210  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf")
211
212!!! Definition du timestep
213
214  dtime%second=1800
[537]215  CALL xios_set_context_attr("surface", timestep=dtime)
[489]216
217!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
218
219  ni=0 ; lonvalue(:)=0
220  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue=lonvalue)
221
222  PRINT *,"ni",ni
223  PRINT *,"lonvalue",lonvalue ;
224
225!!! Fin de la definition du contexte SRF
226!-------------------------------------------------------------------------------
227!
228! Get/set variable in differenct contexts
229!
230!-------------------------------------------------------------------------------
231
232  !! Try getting some variable values
233  var_id = "my_attribute1"
234  ok = xios_getVar(var_id, var_val_char)
235  if (ok) then
236    print*, "Value of ", var_id, " is : ", var_val_char
237  end if
238
239  var_id = "my_attribute2"
240  ok = xios_getVar(var_id, var_val_int)
241  if (ok) then
242    print*, "Value of ", var_id, " is : ", var_val_int
243  end if
244
245  var_id = "my_attribute3"
246  ok = xios_getVar(var_id, var_val_float)
247  if (ok) then
248    print*, "Value of ", var_id, " is : ", var_val_float
249  end if
250
251  var_id = "my_attribute4"
252  ok = xios_getVar(var_id, var_val_double)
253  if (ok) then
254    print*, "Value of ", var_id, " is : ", var_val_double
255  end if
256
257  var_id = "my_global_attribute_bool"
258  ok = xios_getVar(var_id, var_val_bool)
259  if (ok) then
260    print*, "Value of ", var_id, " is : ", var_val_bool
261  end if
262
263  !! Try setting some variables
264  var_id = "my_attribute1"
265  var_val_char = "ocean_att"
266  ok = xios_setVar(var_id, var_val_char)
267  if (ok) then
268    print*, "New value of ", var_id, " is : ", var_val_char
269  end if
270
271  var_id = "my_attribute2"
272  var_val_int = 50
273  ok = xios_setVar(var_id, var_val_int)
274  if (ok) then
275    print*, "New value of ", var_id, " is : ", var_val_int
276  end if
277
278  var_id = "my_attribute3"
279  var_val_float = 7.8
280  ok = xios_setVar(var_id, var_val_float)
281  if (ok) then
282    print*, "New value of ", var_id, " is : ", var_val_float
283  end if
284
285  var_id = "my_attribute4"
286  var_val_double=300.21
287  ok = xios_setVar(var_id, var_val_double)
288  if (ok) then
289    print*, "New value of ", var_id, " is : ", var_val_double
290  end if
291
292  var_id = "my_global_attribute_bool"
293  var_val_bool = .true.
294  ok = xios_setVar(var_id, var_val_bool)
295  if (ok) then
296    print*, "New value of ", var_id, " is : ", var_val_bool
297  end if
[510]298!
299!!!! Fin de la definition du contexte SRF
300  CALL xios_close_context_definition()
[489]301
302!####################################################################################
303!!! Boucle temporelle
304!####################################################################################
305
306    DO ts=1,24*10
307
308      CALL xios_get_handle("atmosphere",ctx_hdl)
309      CALL xios_set_current_context(ctx_hdl)
310
311!!! Mise a jour du pas de temps
312
313      CALL xios_update_calendar(ts)
314
315!!! On donne la valeur du champ atm
316
317      CALL xios_send_field("field_A_atm",field_A_atm)
318
319!!! On change de contexte
320
321      CALL xios_get_handle("surface",ctx_hdl)
322      CALL xios_set_current_context(ctx_hdl)
323
324!!! Mise a jour du pas de temps
325
326      CALL xios_update_calendar(ts)
327
328!!! On donne la valeur du champ srf
329
330      CALL xios_send_field("field_A_srf",field_A_srf)
331
332      CALL wait_us(5000) ;
333    ENDDO
334
335!####################################################################################
336!!! Finalisation
337!####################################################################################
338
339!!! Fin des contextes
340
341    CALL xios_context_finalize()
342    CALL xios_get_handle("atmosphere",ctx_hdl)
343    CALL xios_set_current_context(ctx_hdl)
344    CALL xios_context_finalize()
345
346!!! Fin de XIOS
347
348    CALL xios_finalize()
349
350    CALL MPI_FINALIZE(ierr)
351
352  END PROGRAM test_xios_interface
353
354
355
356
357
358
Note: See TracBrowser for help on using the repository browser.