source: XIOS/dev/branch_yushan/src/test/test_complete_omp.f90 @ 1126

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

test_complete OK with openmp. Missing : arithmetic filter

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