source: XIOS/dev/branch_openmp/src/test/test_complete_omp.f90 @ 1544

Last change on this file since 1544 was 1544, checked in by yushan, 6 years ago

bug fix for tests in prod mode

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