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

Last change on this file since 501 was 501, checked in by ymipsl, 10 years ago

Add licence copyright to all file ond directory src using the command :
svn propset -R copyright -F header_licence src

XIOS is now officialy under CeCILL licence

YM

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