source: XIOS/dev/branch_yushan/src/test/test_complete.f90 @ 1115

Last change on this file since 1115 was 1115, checked in by yushan, 7 years ago

bug corrected in MPI_Gatherv

  • 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.9 KB
Line 
1PROGRAM test_complete
2
3  USE xios
4  USE mod_wait
5  IMPLICIT NONE
6  INCLUDE "mpif.h"
7  INTEGER :: rank, size
8  INTEGER :: size_loc
9  INTEGER :: ierr
10
11  CHARACTER(len=*),PARAMETER :: id="client"
12  INTEGER :: comm, comm2
13  TYPE(xios_duration)  :: 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  LOGICAL :: ok
23  CHARACTER(len=256) :: crname
24
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, provided
31
32!!! MPI Initialization
33
34  CALL MPI_INIT_THREAD(3, provided, ierr)
35    if(provided .NE. 3) then
36      print*, "provided thread level = ", provided
37      call MPI_Abort()
38    endif
39
40 
41
42  CALL init_wait
43
44  CALL MPI_COMM_RANK(MPI_COMM_WORLD,rank,ierr)
45  CALL MPI_COMM_SIZE(MPI_COMM_WORLD,size,ierr)
46  if(rank < size-1) then
47
48!!! XIOS Initialization (get the local communicator)
49
50  CALL xios_initialize(id,return_comm=comm)
51
52  CALL MPI_COMM_RANK(comm,rank,ierr)
53  CALL MPI_COMM_SIZE(comm,size_loc,ierr)
54
55
56!###########################################################################
57! Contexte ATM
58!###########################################################################
59
60!!! Initialisation des coordonnes globales et locales pour la grille rgulire
61
62  DO j=1,nj_glo
63    DO i=1,ni_glo
64      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
65      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
66      DO l=1,llm
67        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
68      ENDDO
69    ENDDO
70  ENDDO
71  ni=ni_glo ; ibegin=0
72
73  jbegin=0
74  DO n=0,size_loc-1
75    nj=nj_glo/size_loc
76    IF (n<MOD(nj_glo,size_loc)) nj=nj+1
77    IF (n==rank) exit
78    jbegin=jbegin+nj
79  ENDDO
80
81  iend=ibegin+ni-1 ; jend=jbegin+nj-1
82
83  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A_atm(0:ni+1,-1:nj+2,llm),lonvalue(ni,nj))
84  lon(:,:)=lon_glo(ibegin+1:iend+1,jbegin+1:jend+1)
85  lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1)
86  field_A_atm(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:)
87
88
89!!! Context ATMOSPHERE
90
91  CALL xios_context_initialize("atmosphere",comm)
92
93  CALL xios_get_handle("atmosphere",ctx_hdl)
94  CALL xios_set_current_context(ctx_hdl)
95
96  CALL xios_define_calendar(type="Gregorian", &
97                            start_date=xios_date(2000, 01, 01, 00, 00, 00), &
98                            time_origin=xios_date(1999, 01, 01, 15, 00, 00))
99
100  CALL xios_set_axis_attr("axis_atm",n_glo=llm ,value=lval) ;
101
102  CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj, type='curvilinear')
103  CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
104  CALL xios_set_domain_attr("domain_atm",lonvalue_2D=lon,latvalue_2D=lat)
105
106  CALL xios_set_domain_attr("domain_atm_zoom",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
107  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)
108  CALL xios_set_domain_attr("domain_atm_zoom",lonvalue_2D=lon,latvalue_2D=lat)
109
110
111!!! Activation du groupe field_definition
112
113  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
114
115!!! Cration d un nouveau champ
116
117  CALL xios_get_handle("field_definition",fieldgroup_hdl)
118  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_atm")
119
120!!! Heritage des attributs d un autre champ
121
122  CALL xios_set_attr(field_hdl,field_ref="field_A_atm_zoom",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
133  CALL xios_set_timestep(timestep=dtime)
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_2D=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   print *, "xios_close_context_definition(atmosphere)"
148
149!!! Test des valeurs des champs/fichiers
150
151  !!! Attribut defini ?
152
153  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok)
154  PRINT *,"field_A_atm : attribute enabled is defined ? ",ok
155
156  !!! Recuperer la valeur d un attribut
157
158  CALL xios_get_field_attr("field_A_atm",name=crname)
159  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname)
160
161  !!! Champ actif (besoin de fournir la valeur) ?
162
163    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm")
164
165  !!! Champ defini ?
166
167    PRINT*,"field field_A_atm is valid ?",xios_is_valid_field("field_A_atm")
168
169
170!###########################################################################
171! Contexte SRF
172!###########################################################################
173
174!!! Initialisation des coordonnes globales et locales pour la grille indexee (1 point sur 2)
175
176    nb_pt=ni*nj/2
177    ALLOCATE(kindex(nb_pt),field_A_srf(nb_pt,llm))
178    DO i=1,nb_pt
179      kindex(i)=2*i-1
180    ENDDO
181    field_A_srf(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin+1:iend+1:2,jbegin+1:jend+1,:),(/ nb_pt,llm /))
182
183  CALL xios_context_initialize("surface",comm)
184
185
186  CALL xios_get_handle("surface",ctx_hdl)
187  CALL xios_set_current_context(ctx_hdl)
188
189  CALL xios_define_calendar(type="Gregorian", &
190                            start_date=xios_date(2000, 01, 01, 00, 00, 00), &
191                            time_origin=xios_date(1999, 01, 01, 15, 00, 00))
192
193  CALL xios_set_axis_attr("axis_srf",n_glo=llm ,value=lval)
194  CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj, type='curvilinear')
195  CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt)
196  CALL xios_set_domain_attr("domain_srf",data_i_index=kindex)
197  CALL xios_set_domain_attr("domain_srf",lonvalue_2D=lon,latvalue_2D=lat)
198
199!!! Cration d un nouveau champ
200
201  CALL xios_get_handle("field_definition",fieldgroup_hdl)
202  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_srf")
203
204!!! Heritage des attributs d un autre champ
205
206  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf")
207
208!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
209
210  CALL xios_get_handle("output_surface",file_hdl)
211  CALL xios_add_child(file_hdl,field_hdl)
212  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf")
213
214!!! Definition du timestep
215
216  dtime%second=1800
217  CALL xios_set_timestep(timestep=dtime)
218
219!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalit)
220
221  ni=0 ; lonvalue(:,:)=0
222  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue_2D=lonvalue)
223
224  !PRINT *,"ni",ni
225  !PRINT *,"lonvalue",lonvalue ;
226
227!!! Fin de la definition du contexte SRF
228
229  CALL xios_close_context_definition()
230
231  print *, "xios_close_context_definition(surface)" 
232
233
234!####################################################################################
235!!! Boucle temporelle
236!####################################################################################
237
238    !DO ts=1,24*10
239    DO ts=1,24
240
241      CALL xios_get_handle("atmosphere",ctx_hdl)
242      CALL xios_set_current_context(ctx_hdl)
243
244!!! Mise a jour du pas de temps
245
246      CALL xios_update_calendar(ts)
247
248!!! On donne la valeur du champ atm
249
250      CALL xios_send_field("field_A_atm",field_A_atm)
251
252!!! On change de contexte
253
254      CALL xios_get_handle("surface",ctx_hdl)
255      CALL xios_set_current_context(ctx_hdl)
256
257!!! Mise a jour du pas de temps
258
259      CALL xios_update_calendar(ts)
260
261!!! On donne la valeur du champ srf
262
263      CALL xios_send_field("field_A_srf",field_A_srf)
264
265      CALL wait_us(5000) ;
266
267
268    ENDDO
269
270     print *, "end temporal loop"
271
272!####################################################################################
273!!! Finalisation
274!####################################################################################
275
276!!! Fin des contextes
277
278
279    CALL xios_get_handle("surface",ctx_hdl) 
280
281    CALL xios_set_current_context(ctx_hdl)
282
283    CALL xios_context_finalize()
284
285    print *, "xios_context_finalize(surface)" 
286
287     CALL xios_get_handle("atmosphere",ctx_hdl)
288
289     CALL xios_set_current_context(ctx_hdl)
290
291     CALL xios_context_finalize()
292
293     print *, "xios_context_finalize(atmosphere)"
294
295   
296
297!!! Fin de XIOS
298
299   
300
301    CALL xios_finalize()
302
303    DEALLOCATE(lon, lat, field_A_atm, lonvalue)
304    DEALLOCATE(kindex, field_A_srf)
305
306     print *, "Client : xios_finalize "
307
308    CALL MPI_COMM_FREE(comm, ierr)
309
310  else
311
312    CALL xios_init_server
313    print *, "Server : xios_finalize "
314 
315    endif
316
317
318    CALL MPI_FINALIZE(ierr)
319
320  END PROGRAM test_complete
321
322
323
324
325
326
Note: See TracBrowser for help on using the repository browser.