1 | PROGRAM toy_cmip6_omp |
---|
2 | |
---|
3 | USE xios |
---|
4 | USE omp_lib |
---|
5 | USE mod_wait |
---|
6 | IMPLICIT NONE |
---|
7 | INCLUDE "mpif.h" |
---|
8 | |
---|
9 | INTEGER,PARAMETER :: il_unit=10 |
---|
10 | INTEGER :: comm, rank, size_loc, ierr |
---|
11 | INTEGER :: ni,ibegin,iend,nj,jbegin,jend |
---|
12 | INTEGER :: i,j,l,ts,n, nb_pt, il_run |
---|
13 | DOUBLE PRECISION :: sypd, timestep_in_seconds, simulated_seconds_per_seconds, elapsed_per_timestep |
---|
14 | CHARACTER(len=*),PARAMETER :: id="client" |
---|
15 | CHARACTER(1000):: duration, timestep |
---|
16 | INTEGER :: start_year,start_month,start_day |
---|
17 | TYPE(xios_date) :: cdate, edate |
---|
18 | TYPE(xios_duration) :: dtime |
---|
19 | TYPE(xios_context) :: ctx_hdl |
---|
20 | REAL :: ilon,jlat |
---|
21 | DOUBLE PRECISION,ALLOCATABLE :: lon_glo(:,:),lat_glo(:,:),lval(:) |
---|
22 | DOUBLE PRECISION,ALLOCATABLE :: field_A_glo (:,:,:), pressure_glo (:,:,:), height_glo (:,:,:) |
---|
23 | DOUBLE PRECISION,ALLOCATABLE :: bounds_lon_glo(:,:,:),bounds_lat_glo(:,:,:) |
---|
24 | DOUBLE PRECISION,ALLOCATABLE :: pressure (:,:,:), height (:,:,:) |
---|
25 | DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),lonvalue(:,:) |
---|
26 | DOUBLE PRECISION,ALLOCATABLE :: bounds_lon(:,:,:),bounds_lat(:,:,:) |
---|
27 | DOUBLE PRECISION,ALLOCATABLE :: field_atm_2D(:,:),field_atm_3D(:,:,:),field_srf_2D(:),field_srf_3D(:,:) |
---|
28 | DOUBLE PRECISION,ALLOCATABLE :: field_atm_2D_miss(:,:) |
---|
29 | DOUBLE PRECISION,ALLOCATABLE :: field_oce_2D(:,:),field_oce_3D(:,:,:) |
---|
30 | INTEGER, ALLOCATABLE :: kindex(:) |
---|
31 | INTEGER :: provided |
---|
32 | |
---|
33 | INTEGER :: ni_glo, nj_glo,llm |
---|
34 | |
---|
35 | NAMELIST /param_toy/ ni_glo, nj_glo,llm,timestep,duration,sypd,start_year,start_month,start_day |
---|
36 | |
---|
37 | !!! MPI Initialization |
---|
38 | |
---|
39 | CALL MPI_INIT_THREAD(3, provided, ierr) |
---|
40 | if(provided .NE. 3) then |
---|
41 | print*, "provided thread level = ", provided |
---|
42 | call MPI_Abort() |
---|
43 | endif |
---|
44 | |
---|
45 | CALL init_wait |
---|
46 | |
---|
47 | CALL MPI_COMM_RANK(MPI_COMM_WORLD,rank,ierr) |
---|
48 | CALL MPI_COMM_SIZE(MPI_COMM_WORLD,size_loc,ierr) |
---|
49 | if(rank < size_loc-2) then |
---|
50 | |
---|
51 | !!! Lecture des parametres du run |
---|
52 | |
---|
53 | OPEN(unit=il_unit, file='param.def',status='old',iostat=ierr) |
---|
54 | READ (il_unit, nml=param_toy) |
---|
55 | !PRINT *, ni_glo, nj_glo,llm,duration |
---|
56 | |
---|
57 | !$omp parallel default(firstprivate) |
---|
58 | |
---|
59 | !!! XIOS Initialization (get the local communicator) |
---|
60 | |
---|
61 | CALL xios_initialize(id,return_comm=comm) |
---|
62 | |
---|
63 | CALL MPI_COMM_RANK(comm,rank,ierr) |
---|
64 | CALL MPI_COMM_SIZE(comm,size_loc,ierr) |
---|
65 | |
---|
66 | rank = rank*omp_get_num_threads() + omp_get_thread_num() |
---|
67 | size_loc = size_loc*omp_get_num_threads() |
---|
68 | |
---|
69 | print*, "rank = ", rank, " size = ", size_loc |
---|
70 | |
---|
71 | !!! Initialisation et allocation des coordonnées globales et locales pour la grille réguliÚre |
---|
72 | |
---|
73 | ALLOCATE (lon_glo(ni_glo,nj_glo),lat_glo(ni_glo,nj_glo)) |
---|
74 | ALLOCATE(bounds_lon_glo(4,ni_glo,nj_glo)) |
---|
75 | ALLOCATE(bounds_lat_glo(4,ni_glo,nj_glo)) |
---|
76 | ALLOCATE (field_A_glo(ni_glo,nj_glo,llm)) |
---|
77 | ALLOCATE (pressure_glo(ni_glo,nj_glo,llm)) |
---|
78 | ALLOCATE (height_glo(ni_glo,nj_glo,llm)) |
---|
79 | ALLOCATE (lval(llm)) |
---|
80 | |
---|
81 | DO j=1,nj_glo |
---|
82 | DO i=1,ni_glo |
---|
83 | |
---|
84 | ilon=i-0.5 |
---|
85 | jlat=j-0.5 |
---|
86 | |
---|
87 | lat_glo(i,j)= 90-(jlat*180./nj_glo) |
---|
88 | lon_glo(i,j)= (ilon*360./ni_glo) |
---|
89 | !print*, 'i/lon=',i,'lon=',lon_glo(i,j), 'j/lat=',j,'lat=',lat_glo(i,j) |
---|
90 | |
---|
91 | bounds_lat_glo(1,i,j)= 90-((jlat-0.5)*180./nj_glo) |
---|
92 | bounds_lon_glo(1,i,j)=((ilon-0.5)*360./ni_glo) |
---|
93 | |
---|
94 | bounds_lat_glo(2,i,j)= 90-((jlat-0.5)*180./nj_glo) |
---|
95 | bounds_lon_glo(2,i,j)=((ilon+0.5)*360./ni_glo) |
---|
96 | |
---|
97 | bounds_lat_glo(3,i,j)= 90-((jlat+0.5)*180./nj_glo) |
---|
98 | bounds_lon_glo(3,i,j)=((ilon+0.5)*360./ni_glo) |
---|
99 | |
---|
100 | bounds_lat_glo(4,i,j)= 90-((jlat+0.5)*180./nj_glo) |
---|
101 | bounds_lon_glo(4,i,j)=((ilon-0.5)*360./ni_glo) |
---|
102 | |
---|
103 | WHERE (abs(bounds_lat_glo(:,i,j) - 90) < 0.000000001) bounds_lat_glo(:,i,j) = 90 |
---|
104 | WHERE (abs(bounds_lat_glo(:,i,j) + 90) < 0.000000001) bounds_lat_glo(:,i,j) = -90 |
---|
105 | |
---|
106 | DO l=1,llm |
---|
107 | field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l |
---|
108 | ! pressure at half levels. First index value is high altitude, low pressure |
---|
109 | pressure_glo(i,j,l)=((l-0.)/llm)*100000 + (jlat -nj_glo/2.)/nj_glo * 10000 |
---|
110 | height_glo(i,j,l)=(llm-l+0.5)/llm * 15000 + jlat * 100 |
---|
111 | ENDDO |
---|
112 | ENDDO |
---|
113 | ENDDO |
---|
114 | ni=ni_glo ; ibegin=0 |
---|
115 | |
---|
116 | jbegin=0 |
---|
117 | DO n=0,size_loc-1 |
---|
118 | nj=nj_glo/size_loc |
---|
119 | IF (n<MOD(nj_glo,size_loc)) nj=nj+1 |
---|
120 | IF (n==rank) exit |
---|
121 | jbegin=jbegin+nj |
---|
122 | ENDDO |
---|
123 | |
---|
124 | iend=ibegin+ni-1 ; jend=jbegin+nj-1 |
---|
125 | |
---|
126 | ALLOCATE(lon(ni,nj),lat(ni,nj),lonvalue(ni,nj)) |
---|
127 | ALLOCATE(bounds_lon(4,ni,nj)) |
---|
128 | ALLOCATE(bounds_lat(4,ni,nj)) |
---|
129 | lon(:,:)=lon_glo(ibegin+1:iend+1,jbegin+1:jend+1) |
---|
130 | lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1) |
---|
131 | bounds_lon(:,:,:)=bounds_lon_glo(:,ibegin+1:iend+1,jbegin+1:jend+1) |
---|
132 | bounds_lat(:,:,:)=bounds_lat_glo(:,ibegin+1:iend+1,jbegin+1:jend+1) |
---|
133 | |
---|
134 | |
---|
135 | DO i=1,llm |
---|
136 | lval(i)=i |
---|
137 | ENDDO |
---|
138 | |
---|
139 | |
---|
140 | |
---|
141 | !########################################################################### |
---|
142 | ! Contexte ATM |
---|
143 | !########################################################################### |
---|
144 | ALLOCATE(field_atm_2D(0:ni+1,-1:nj+2),field_atm_3D(0:ni+1,-1:nj+2,llm)) |
---|
145 | ALLOCATE(field_atm_2D_miss(0:ni+1,-1:nj+2)) |
---|
146 | ALLOCATE(pressure(0:ni+1,-1:nj+2,llm)) |
---|
147 | ALLOCATE(height(0:ni+1,-1:nj+2,llm)) |
---|
148 | field_atm_2D(1:ni,1:nj)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,1) |
---|
149 | field_atm_2D_miss(1:ni,1:nj)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,1) |
---|
150 | field_atm_3D(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) |
---|
151 | pressure(1:ni,1:nj,:)=pressure_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) |
---|
152 | height(1:ni,1:nj,:)=height_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) |
---|
153 | |
---|
154 | CALL xios_context_initialize("arpsfx",comm) |
---|
155 | CALL xios_define_calendar("Gregorian", & |
---|
156 | start_date=xios_date(start_year,start_month,start_day,0,0,0), & |
---|
157 | time_origin=xios_date(1850,1,1,0,0,0)) |
---|
158 | |
---|
159 | !write(0,*) 'atm context initialized' ; call flush(0) |
---|
160 | CALL xios_get_handle("arpsfx",ctx_hdl) |
---|
161 | CALL xios_set_current_context(ctx_hdl) |
---|
162 | |
---|
163 | CALL xios_set_axis_attr("axis_atm",n_glo=llm ,value=lval) ; |
---|
164 | |
---|
165 | CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, & |
---|
166 | ni=ni,jbegin=jbegin,nj=nj, type='rectilinear') |
---|
167 | CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, & |
---|
168 | data_ni=ni+2, data_jbegin=-2, data_nj=nj+4) |
---|
169 | CALL xios_set_domain_attr("domain_atm",lonvalue_2D=lon,latvalue_2D=lat) |
---|
170 | CALL xios_set_domain_attr("domain_atm", nvertex=4, bounds_lon_2d=bounds_lon, bounds_lat_2d=bounds_lat) |
---|
171 | print *,'latmax/min=',minval(lat),maxval(lat) |
---|
172 | print *,'latmax/min bounds=',minval(bounds_lat),maxval(bounds_lat) |
---|
173 | print *,'lonmax/min=',minval(lon),maxval(lon) |
---|
174 | print *,'lonmax/min bounds=',minval(bounds_lon),maxval(bounds_lon) |
---|
175 | |
---|
176 | |
---|
177 | !!! Definition du timestep |
---|
178 | |
---|
179 | CALL xios_get_start_date(cdate) |
---|
180 | edate=cdate+xios_duration_convert_from_string(duration) |
---|
181 | dtime=xios_duration_convert_from_string(timestep) |
---|
182 | CALL xios_set_timestep(timestep=dtime) |
---|
183 | |
---|
184 | !!! Fin de la definition du contexte |
---|
185 | |
---|
186 | !CALL xios_close_context_definition() |
---|
187 | |
---|
188 | !!! Calcul de temps elaps par seconde pour respecter le SYPD (hyp : pas de délai d'I/O) |
---|
189 | |
---|
190 | timestep_in_seconds=xios_date_convert_to_seconds(cdate+dtime) - xios_date_convert_to_seconds(cdate) |
---|
191 | simulated_seconds_per_seconds=sypd * 365 |
---|
192 | elapsed_per_timestep=timestep_in_seconds/simulated_seconds_per_seconds ! in seconds |
---|
193 | |
---|
194 | !########################################################################### |
---|
195 | ! Contexte SRF |
---|
196 | !########################################################################### |
---|
197 | |
---|
198 | !!! Initialisation des coordonnées globales et locales pour la grille indexee (1 point sur 2) |
---|
199 | |
---|
200 | nb_pt=ni*nj/2 |
---|
201 | ALLOCATE(kindex(nb_pt),field_srf_2D(nb_pt),field_srf_3D(nb_pt,llm)) |
---|
202 | DO i=1,nb_pt |
---|
203 | kindex(i)=2*i-1 |
---|
204 | ENDDO |
---|
205 | field_srf_2D(1:nb_pt)=RESHAPE(field_A_glo(ibegin+1:iend+1:2,jbegin+1:jend+1,1),(/ nb_pt /)) |
---|
206 | field_srf_3D(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin+1:iend+1:2,jbegin+1:jend+1,:),(/ nb_pt,llm /)) |
---|
207 | |
---|
208 | !CALL xios_context_initialize("surface",comm) |
---|
209 | !CALL xios_get_handle("surface",ctx_hdl) |
---|
210 | !CALL xios_set_current_context(ctx_hdl) |
---|
211 | |
---|
212 | CALL xios_set_axis_attr("axis_srf",n_glo=llm ,value=lval) |
---|
213 | CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj, type='rectilinear') |
---|
214 | CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt) |
---|
215 | CALL xios_set_domain_attr("domain_srf",data_i_index=kindex) |
---|
216 | CALL xios_set_domain_attr("domain_srf",lonvalue_2D=lon,latvalue_2D=lat) |
---|
217 | CALL xios_set_domain_attr("domain_srf", nvertex=4, bounds_lon_2d=bounds_lon, bounds_lat_2d=bounds_lat) |
---|
218 | |
---|
219 | !!! Definition du timestep |
---|
220 | |
---|
221 | !dtime%second=timestep |
---|
222 | !dtime=xios_duration_convert_from_string(timestep) |
---|
223 | !CALL xios_set_timestep(timestep=dtime) |
---|
224 | |
---|
225 | !!! Fin de la definition du contexte SRF |
---|
226 | |
---|
227 | CALL xios_close_context_definition() |
---|
228 | !write(0,*) 'srf context def closed' ; call flush(0) |
---|
229 | |
---|
230 | !########################################################################### |
---|
231 | ! Contexte OCE |
---|
232 | !########################################################################### |
---|
233 | ALLOCATE(field_oce_2D(0:ni+1,-1:nj+2),field_oce_3D(0:ni+1,-1:nj+2,llm)) |
---|
234 | field_oce_2D(1:ni,1:nj)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,1) |
---|
235 | field_oce_3D(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) |
---|
236 | |
---|
237 | CALL xios_context_initialize("nemo",comm) |
---|
238 | CALL xios_define_calendar("Gregorian", & |
---|
239 | start_date=xios_date(start_year,start_month,start_day,0,0,0), & |
---|
240 | time_origin=xios_date(1850,1,1,0,0,0)) |
---|
241 | CALL xios_get_handle("nemo",ctx_hdl) |
---|
242 | CALL xios_set_current_context(ctx_hdl) |
---|
243 | |
---|
244 | CALL xios_set_axis_attr("axis_oce",n_glo=llm ,value=lval) ; |
---|
245 | |
---|
246 | CALL xios_set_domain_attr("domain_oce",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj, type='curvilinear') |
---|
247 | CALL xios_set_domain_attr("domain_oce",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4) |
---|
248 | CALL xios_set_domain_attr("domain_oce",lonvalue_2D=lon,latvalue_2D=lat) |
---|
249 | |
---|
250 | |
---|
251 | !!! Definition du timestep |
---|
252 | |
---|
253 | dtime=xios_duration_convert_from_string(timestep) |
---|
254 | CALL xios_set_timestep(timestep=dtime) |
---|
255 | |
---|
256 | CALL xios_close_context_definition() |
---|
257 | |
---|
258 | !#################################################################################### |
---|
259 | !!! Boucle temporelle |
---|
260 | !#################################################################################### |
---|
261 | ts=1 |
---|
262 | cdate=cdate+dtime |
---|
263 | DO while ( cdate <= edate ) |
---|
264 | |
---|
265 | CALL xios_get_handle("arpsfx",ctx_hdl) |
---|
266 | CALL xios_set_current_context(ctx_hdl) |
---|
267 | |
---|
268 | !!! Mise a jour du pas de temps |
---|
269 | |
---|
270 | CALL xios_update_calendar(ts) |
---|
271 | |
---|
272 | !!! On donne la valeur du champ atm |
---|
273 | |
---|
274 | !print *,'sending field_atm_2d at timestep',ts |
---|
275 | CALL xios_send_field("field_atm_scalar",field_atm_2D(1,1)+ts) |
---|
276 | CALL xios_send_field("field_atm_1D",field_atm_3D(1,1,:)+ts) |
---|
277 | CALL xios_send_field("field_atm_2D",field_atm_2D+ts) |
---|
278 | CALL xios_send_field("field_atm_3D",field_atm_3D+ts) |
---|
279 | CALL xios_send_field("pressure" ,pressure) |
---|
280 | CALL xios_send_field("height" ,height) |
---|
281 | if (mod(ts,2)==0) then |
---|
282 | CALL xios_send_field("field_sub",field_atm_2D+ts) |
---|
283 | endif |
---|
284 | !! On crée un champ avec des missings qui bougent |
---|
285 | !! dans le temps : un bande verticale de 1 Ã ni-3 |
---|
286 | field_atm_2D_miss(:,:)= field_atm_2D(:,:)+ts |
---|
287 | field_atm_2D_miss(mod(ts,ni-3)+1,:)=1.e+20 |
---|
288 | CALL xios_send_field("field_miss",field_atm_2D_miss) |
---|
289 | |
---|
290 | !!! On change de contexte |
---|
291 | |
---|
292 | !CALL xios_get_handle("surface",ctx_hdl) |
---|
293 | !CALL xios_set_current_context(ctx_hdl) |
---|
294 | |
---|
295 | !!! Mise a jour du pas de temps |
---|
296 | |
---|
297 | !CALL xios_update_calendar(ts) |
---|
298 | |
---|
299 | !!! On donne la valeur du champ srf |
---|
300 | |
---|
301 | CALL xios_send_field("field_srf_2D",field_srf_2D) |
---|
302 | CALL xios_send_field("field_srf_3D",field_srf_3D) |
---|
303 | |
---|
304 | !!! On change de contexte |
---|
305 | |
---|
306 | CALL xios_get_handle("nemo",ctx_hdl) |
---|
307 | CALL xios_set_current_context(ctx_hdl) |
---|
308 | |
---|
309 | !!! Mise a jour du pas de temps |
---|
310 | |
---|
311 | CALL xios_update_calendar(ts) |
---|
312 | |
---|
313 | !!! On donne la valeur du champ oce |
---|
314 | |
---|
315 | CALL xios_send_field("field_oce_scalar",field_oce_2D(1,1)+ts) |
---|
316 | CALL xios_send_field("field_oce_grid_2D",field_oce_2D) |
---|
317 | CALL xios_send_field("field_oce_grid_3D",field_oce_3D) |
---|
318 | |
---|
319 | CALL wait_us(int(elapsed_per_timestep*1.e6)) ! micro-secondes |
---|
320 | cdate=cdate+dtime |
---|
321 | ts=ts+1 |
---|
322 | |
---|
323 | ENDDO |
---|
324 | |
---|
325 | !#################################################################################### |
---|
326 | !!! Finalisation |
---|
327 | !#################################################################################### |
---|
328 | |
---|
329 | !!! Fin des contextes |
---|
330 | |
---|
331 | CALL xios_context_finalize() |
---|
332 | CALL xios_get_handle("arpsfx",ctx_hdl) |
---|
333 | CALL xios_set_current_context(ctx_hdl) |
---|
334 | CALL xios_context_finalize() |
---|
335 | !CALL xios_get_handle("surface",ctx_hdl) |
---|
336 | !CALL xios_set_current_context(ctx_hdl) |
---|
337 | !CALL xios_context_finalize() |
---|
338 | |
---|
339 | DEALLOCATE(lon, lat, lonvalue, field_atm_2D, field_atm_3D) |
---|
340 | DEALLOCATE(pressure,height,pressure_glo,height_glo) |
---|
341 | DEALLOCATE(kindex, field_srf_2D, field_srf_3D) |
---|
342 | DEALLOCATE(field_oce_2D, field_oce_3D) |
---|
343 | DEALLOCATE(lon_glo,lat_glo,field_A_glo,lval) |
---|
344 | |
---|
345 | !!! Fin de XIOS |
---|
346 | |
---|
347 | CALL xios_finalize() |
---|
348 | print*, "xios finalize OK", rank, size_loc |
---|
349 | |
---|
350 | !$omp master |
---|
351 | !call MPI_Barrier(comm) |
---|
352 | CALL MPI_COMM_FREE(comm, ierr) |
---|
353 | !$omp end master |
---|
354 | |
---|
355 | !$omp barrier |
---|
356 | |
---|
357 | !$omp end parallel |
---|
358 | |
---|
359 | |
---|
360 | CALL MPI_FINALIZE(ierr) |
---|
361 | |
---|
362 | else |
---|
363 | |
---|
364 | CALL xios_init_server |
---|
365 | CALL MPI_FINALIZE(ierr) |
---|
366 | print *, "Server : xios_finalize ", rank |
---|
367 | |
---|
368 | endif |
---|
369 | |
---|
370 | |
---|
371 | !CALL MPI_FINALIZE(ierr) |
---|
372 | |
---|
373 | END PROGRAM toy_cmip6_omp |
---|
374 | |
---|
375 | |
---|
376 | |
---|
377 | |
---|
378 | |
---|
379 | |
---|