source: XIOS/dev/dev_trunk_omp/src/test/test_complete_omp.f90 @ 1702

Last change on this file since 1702 was 1677, checked in by yushan, 5 years ago

MARK: Dynamic workflow graph developement. Branch up to date with trunk @1663.

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