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

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

save dev. TO DO : test with xios

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