source: XIOS1/trunk/src/test/test_complete.f90 @ 2542

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

Modify test_complete so that zoom is actually tested.

Note that the trunk is currently broken and does not pass this test.

  • 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: 8.8 KB
Line 
1PROGRAM test_complete
2
3  USE xios
4  USE mod_wait
5  IMPLICIT NONE
6  INCLUDE "mpif.h"
7  INTEGER :: rank
8  INTEGER :: size_loc
9  INTEGER :: ierr
10 
11  CHARACTER(len=*),PARAMETER :: id="client"
12  INTEGER :: comm
13  TYPE(xios_time)      :: dtime
14  TYPE(xios_context) :: ctx_hdl
15  INTEGER,PARAMETER :: ni_glo=100
16  INTEGER,PARAMETER :: nj_glo=100 
17  INTEGER,PARAMETER :: llm=5 
18  DOUBLE PRECISION  :: lval(llm)=1
19  TYPE(xios_field) :: field_hdl
20  TYPE(xios_fieldgroup) :: fieldgroup_hdl
21  TYPE(xios_file) :: file_hdl
22  TYPE(xios_variable) :: var_hdl
23  LOGICAL :: ok
24  CHARACTER(len=256) :: crname, str_temp
25  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
26  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
27  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A_atm(:,:,:), field_A_srf(:,:), lonvalue(:)
28  INTEGER, ALLOCATABLE :: kindex(:)
29  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
30  INTEGER :: i,j,l,ts,n, nb_pt
31
32!!! MPI Initialization
33
34  CALL MPI_INIT(ierr)
35 
36  CALL init_wait
37 
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)
43  CALL MPI_COMM_SIZE(comm,size_loc,ierr) 
44 
45
46!###########################################################################
47! ATM Context
48!###########################################################################
49
50!!! Initialization of global and local coordinates for regular grid
51
52  DO j=1,nj_glo
53    DO i=1,ni_glo
54      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
55      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
56      DO l=1,llm
57        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
58      ENDDO
59    ENDDO
60  ENDDO
61  ni=ni_glo ; ibegin=1
62
63  jbegin=1
64  DO n=0,size_loc-1
65    nj=nj_glo/size_loc
66    IF (n<MOD(nj_glo,size_loc)) nj=nj+1
67    IF (n==rank) exit
68    jbegin=jbegin+nj
69  ENDDO
70 
71  iend=ibegin+ni-1 ; jend=jbegin+nj-1
72
73  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A_atm(0:ni+1,-1:nj+2,llm),lonvalue(ni*nj))
74  lon(:,:)=lon_glo(ibegin:iend,jbegin:jend)
75  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend)
76  field_A_atm(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:)
77 
78
79!!! ATMOSPHERE context
80
81  CALL xios_context_initialize("atmosphere",comm)
82  CALL xios_get_handle("atmosphere",ctx_hdl)
83  CALL xios_set_current_context(ctx_hdl)
84 
85  CALL xios_set_context_attr("atmosphere",calendar_type="Gregorian") 
86  CALL xios_set_context_attr("atmosphere",start_date="2000-01-01 00:00:00")
87  CALL xios_set_context_attr("atmosphere",time_origin="1999-01-01 15:00:00")
88
89  CALL xios_set_axis_attr("axis_atm",size=llm ,value=lval) ;
90
91  CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
92  CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
93  CALL xios_set_domain_attr("domain_atm",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
94
95  CALL xios_set_domain_attr("domain_atm_zoom",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
96  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)
97  CALL xios_set_domain_attr("domain_atm_zoom",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
98  CALL xios_set_domain_attr("domain_atm_zoom",zoom_ibegin=40, zoom_ni=20, zoom_jbegin=40, zoom_nj=10)
99
100!!! field_definition group activation
101
102  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
103
104!!! Creation of new field
105
106  CALL xios_get_handle("field_definition",fieldgroup_hdl)
107  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_atm")
108
109!!! Attribute inheritance from another field
110
111  CALL xios_set_attr(field_hdl,field_ref="field_A_atm",name="field_B_atm")
112 
113!!! Assign new field into a file (with a new name)
114
115  CALL xios_get_handle("output_atmosphere",file_hdl)
116  CALL xios_add_child(file_hdl,field_hdl)
117  CALL xios_set_attr(field_hdl,field_ref="field_B_atm",name="field_C_atm")
118   
119!!! Timestep definition
120
121  dtime%second=3600
122  CALL xios_set_timestep(dtime) 
123   
124!!! Get longitude values and local domain sizes (to check functionality)
125
126  ni=0 ; lonvalue(:)=0
127  CALL xios_get_domain_attr("domain_atm",ni=ni,lonvalue=lonvalue)
128   
129  PRINT *,"ni",ni
130  PRINT *,"lonvalue",lonvalue ;
131
132!!! End of context definition
133
134  CALL xios_close_context_definition()
135
136!!! Test on fields/files values
137 
138  !!! Is an attribute defined ?
139
140  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok)
141  PRINT *,"field_A_atm : attribute enabled is defined ? ",ok
142
143  !!! Get an attibute value
144 
145  CALL xios_get_field_attr("field_A_atm",name=crname)
146  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname)
147
148  !!! Is a field active (i.e need to give the value ) ?
149
150    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm")
151
152  !!! Is a field defined ?
153
154    PRINT*,"field field_A_atm is valid ?",xios_is_valid_field("field_A_atm")
155
156
157!###########################################################################
158! SRF Context
159!###########################################################################
160
161!!! Initialization of global and local coordinates for indexed grid (1 point every 2 points)
162
163    nb_pt=ni*nj/2
164    ALLOCATE(kindex(nb_pt),field_A_srf(nb_pt,llm))
165    DO i=1,nb_pt
166      kindex(i)=2*i-1
167    ENDDO
168    field_A_srf(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin:iend:2,jbegin:jend,:),(/ nb_pt,llm /))
169
170  CALL xios_context_initialize("surface",comm)
171  CALL xios_get_handle("surface",ctx_hdl)
172  CALL xios_set_current_context(ctx_hdl)
173 
174  CALL xios_set_context_attr("surface",calendar_type="Gregorian") 
175  CALL xios_set_context_attr("surface",start_date="2000-01-01 00:00:00")
176  CALL xios_set_context_attr("surface",time_origin="1999-01-01 15:00:00")
177
178  CALL xios_set_axis_attr("axis_srf",size=llm ,value=lval) ;
179  CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
180  CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt)
181  CALL xios_set_domain_attr("domain_srf",data_n_index=nb_pt, data_i_index=kindex)
182  CALL xios_set_domain_attr("domain_srf",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
183
184!!! Creation of new field
185
186  CALL xios_get_handle("field_definition",fieldgroup_hdl)
187  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_srf")
188
189!!! Attribute inheritance from another field
190
191  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf")
192
193!!! Assign new field into a file (with a new name)
194
195  CALL xios_get_handle("output_surface",file_hdl)
196  CALL xios_add_child(file_hdl,field_hdl)
197  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf")
198
199!!! Add a variable as field local attribute
200
201  CALL xios_add_child(field_hdl,var_hdl,"my_local_attribute")
202  CALL xios_set_attr(var_hdl,type="string")
203  ok=xios_setVar("my_local_attribute","attribute_local")
204
205!!! Add a variable as file global attribute
206
207  CALL xios_add_child(file_hdl,var_hdl,"my_global_attribute")
208  CALL xios_set_attr(var_hdl,type="string")
209  ok=xios_setVar("my_global_attribute","attribute_global")
210
211!!! Modify a variable used as attribute (defined in xml file)
212
213  ok=xios_setVar("my_global_attribute_xml","6h_file")
214
215!!! Get the value of a variable (defined in xml file)
216 
217  ok=xios_getVar("my_attribute1",str_temp)
218  PRINT *, "my_attribute1 is :",TRIM(str_temp)
219     
220!!! Timestep definition
221
222  dtime%second=1800
223  CALL xios_set_timestep(dtime) 
224   
225!!! Get longitude values and local domain sizes (to check functionality)
226
227  ni=0 ; lonvalue(:)=0
228  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue=lonvalue)
229   
230  PRINT *,"ni",ni
231  PRINT *,"lonvalue",lonvalue ;
232
233!!! End of SRF context definition
234
235  CALL xios_close_context_definition()
236
237!####################################################################################
238!!! Loop on timesteps
239!####################################################################################
240
241    DO ts=1,24*10
242
243      CALL xios_get_handle("atmosphere",ctx_hdl)
244      CALL xios_set_current_context(ctx_hdl)   
245
246!!! Update of calendar
247
248      CALL xios_update_calendar(ts)
249
250!!! Put the value of atm field
251
252      CALL xios_send_field("field_A_atm",field_A_atm)
253
254!!! Change of context
255
256      CALL xios_get_handle("surface",ctx_hdl)
257      CALL xios_set_current_context(ctx_hdl)   
258
259!!! Update of calendar
260
261      CALL xios_update_calendar(ts)
262
263!!! Put the value of srf field
264
265      CALL xios_send_field("field_A_srf",field_A_srf)
266
267      CALL wait_us(5000) ;
268    ENDDO
269
270!####################################################################################
271!!! Finalization
272!####################################################################################
273
274!!! End of contextes
275
276    CALL xios_context_finalize()
277    CALL xios_get_handle("atmosphere",ctx_hdl)
278    CALL xios_set_current_context(ctx_hdl)   
279    CALL xios_context_finalize()
280   
281!!! End of XIOS
282
283    CALL xios_finalize()
284 
285    CALL MPI_FINALIZE(ierr)
286 
287  END PROGRAM test_complete
288
289
290
291 
292
293 
Note: See TracBrowser for help on using the repository browser.