source: XIOS/dev/branch_openmp/src/test/test_unstruct_omp.f90 @ 1209

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

bug corrected. happened when certain threads send 0 elements in the allgatherv call

File size: 10.1 KB
RevLine 
[1177]1PROGRAM test_unstruct_omp
2
3  USE xios
4  USE mod_wait
5  use omp_lib
6  IMPLICIT NONE
7  INCLUDE "mpif.h"
8  INTEGER :: mpi_rank
9  INTEGER :: mpi_size
10  INTEGER :: ierr
11
12  CHARACTER(len=*),PARAMETER :: id="client"
13  INTEGER :: comm
14  TYPE(xios_duration) :: dtime
15  TYPE(xios_context) :: ctx_hdl
16  INTEGER, PARAMETER :: nlon=60
17  INTEGER, PARAMETER :: nlat=30
18  INTEGER,PARAMETER :: ni_glo=100
19  INTEGER,PARAMETER :: nj_glo=100
20  INTEGER,PARAMETER :: llm=5
21  DOUBLE PRECISION  :: lval(llm)=1
22  TYPE(xios_field) :: field_hdl
23  TYPE(xios_fieldgroup) :: fieldgroup_hdl
24  TYPE(xios_file) :: file_hdl
25  LOGICAL :: ok
26
27  DOUBLE PRECISION,ALLOCATABLE :: lon_glo(:),lat_glo(:)
28  DOUBLE PRECISION,ALLOCATABLE :: bounds_lon_glo(:,:),bounds_lat_glo(:,:)
29  DOUBLE PRECISION,ALLOCATABLE :: field_A_glo(:,:)
30  INTEGER,ALLOCATABLE :: i_index_glo(:)
31  INTEGER,ALLOCATABLE :: i_index(:)
32  LOGICAL,ALLOCATABLE :: mask_glo(:),mask(:)
33  INTEGER,ALLOCATABLE :: n_local(:),local_neighbor(:,:)
34  DOUBLE PRECISION,ALLOCATABLE :: lon(:),lat(:),field_A_srf(:,:), lonvalue(:) ;
35  DOUBLE PRECISION,ALLOCATABLE :: bounds_lon(:,:),bounds_lat(:,:) ;
36  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
37  INTEGER :: i,j,l,ts,n, nbMax
38  INTEGER :: ncell_glo,ncell,ind
39  REAL :: ilon,ilat
40  DOUBLE PRECISION, PARAMETER :: Pi=3.14159265359
41  INTEGER :: list_ind(nlon,nlat)
42  INTEGER :: rank,j1,j2,np,ncell_x
43  INTEGER :: data_n_index, provided
44  INTEGER,ALLOCATABLE :: data_i_index(:)
45  DOUBLE PRECISION,ALLOCATABLE :: field_A_compressed(:,:)
46
47  CALL MPI_INIT_THREAD(3, provided, ierr)
48    if(provided .NE. 3) then
49      print*, "provided thread level = ", provided
50      call MPI_Abort()
51    endif
52  CALL init_wait
53  CALL MPI_COMM_RANK(MPI_COMM_WORLD,mpi_rank,ierr)
54  CALL MPI_COMM_SIZE(MPI_COMM_WORLD,mpi_size,ierr)
55  if(mpi_rank < mpi_size-2) then
56
[1209]57  !$omp parallel default(firstprivate) firstprivate(dtime)
[1177]58
59  CALL xios_initialize(id,return_comm=comm)
60  CALL MPI_COMM_RANK(comm,mpi_rank,ierr)
61  CALL MPI_COMM_SIZE(comm,mpi_size,ierr)
62
63  mpi_rank = mpi_rank*omp_get_num_threads() + omp_get_thread_num()
64  mpi_size = mpi_size*omp_get_num_threads()
65
66
67  ncell_glo=0
68  DO j=1,nlat
69    n =  NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
70    IF (n<8) n=8
71    ncell_glo=ncell_glo+n
72  ENDDO
73
74  ALLOCATE(lon_glo(ncell_glo))
75  ALLOCATE(lat_glo(ncell_glo))
76  ALLOCATE(bounds_lon_glo(4,ncell_glo))
77  ALLOCATE(bounds_lat_glo(4,ncell_glo))
78  ALLOCATE(i_index_glo(ncell_glo))
79  ALLOCATE(field_A_glo(ncell_glo,llm))
80  ALLOCATE(mask_glo(ncell_glo))
81
[1209]82  lon_glo(:) = 0
83  lat_glo(:) = 0
84  bounds_lon_glo(:,:) = 0
85  bounds_lat_glo(:,:) = 0
86  i_index_glo(:) = 0
87  field_A_glo(:,:) = 0
88  mask_glo(:) = 0
89
[1177]90  ind=0
91  DO j=1,nlat
92    n = NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
93    if (j==1) PRINT*,"--- ",n
94    if (j==nlat) PRINT*,"--- ",n
95    IF (n<8) n=8
96
97    DO i=1,n
98      ind=ind+1
99      list_ind(i,j)=ind
100      ilon=i-0.5
101      ilat=j-0.5
102
103      lat_glo(ind)= 90-(ilat*180./nlat)
104      lon_glo(ind)= (ilon*360./n)
105
106
107      bounds_lat_glo(1,ind)= 90-((ilat-0.5)*180./nlat)
108      bounds_lon_glo(1,ind)=((ilon-0.5)*360./n)
109
110      bounds_lat_glo(2,ind)= 90-((ilat-0.5)*180./nlat)
111      bounds_lon_glo(2,ind)=((ilon+0.5)*360./n)
112
113      bounds_lat_glo(3,ind)= 90-((ilat+0.5)*180./nlat)
114      bounds_lon_glo(3,ind)=((ilon+0.5)*360./n)
115
116      bounds_lat_glo(4,ind)= 90-((ilat+0.5)*180./nlat)
117      bounds_lon_glo(4,ind)=((ilon-0.5)*360./n)
118
119    ENDDO
120  ENDDO
121
122!  mpi_size=32
123  rank=(mpi_size-1)/2
124  ncell_x=sqrt(ncell_glo*1./mpi_size)
125
126  j1=nlat/2
127  DO WHILE(rank>=0)
128    j2=MAX(j1-ncell_x+1,1)
129    j=(j1+j2)/2
130    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
131    np = MIN(n/ncell_x,rank+1) ;
132    if (j2==1) np=rank+1
133
134    PRINT *,"domain ",j2,j1,rank,np ;
135    DO j=j2,j1
136      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
137      IF (n<8) n=8
138      DO i=1,n
139        ind=list_ind(i,j)
140        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
141          i_index_glo(ind) = rank - (i-1)/(n/np+1)
142        ELSE
143          i_index_glo(ind) = rank-(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
144        ENDIF
145      ENDDO
146    ENDDO
147    rank=rank-np
148    j1=j2-1
149  ENDDO
150
151  rank=(mpi_size-1)/2+1
152  ncell_x=sqrt(ncell_glo*1./mpi_size)
153
154  j1=nlat/2+1
155  DO WHILE(rank<=mpi_size-1)
156    j2=MIN(j1+ncell_x-1,nlat)
157    j=(j1+j2)/2
158    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
159    np = MIN(n/ncell_x,mpi_size-rank) ;
160    if (j2==nlat) np=mpi_size-rank
161
162    PRINT *,"domain ",j2,j1,rank,np ;
163    DO j=j1,j2
164      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
165      IF (n<8) n=8
166      DO i=1,n
167        ind=list_ind(i,j)
168        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
169          i_index_glo(ind) = rank + (i-1)/(n/np+1)
170        ELSE
171          i_index_glo(ind) = rank+(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
172        ENDIF
173      ENDDO
174    ENDDO
175    rank=rank+np
176    j1=j2+1
177  ENDDO
178
179  ncell=0
180  DO ind=1,ncell_glo
181    IF (i_index_glo(ind)==mpi_rank) ncell=ncell+1
182  ENDDO
183  ALLOCATE(i_index(ncell))
184  ALLOCATE(lon(ncell))
185  ALLOCATE(lat(ncell))
186  ALLOCATE(bounds_lon(4,ncell))
187  ALLOCATE(bounds_lat(4,ncell))
188  ALLOCATE(field_A_srf(ncell,llm))
189  ALLOCATE(mask(ncell))
190  ALLOCATE(n_local(ncell))
[1209]191 
192  i_index(:)=0
193  lon(:)=0
194  lat(:)=0
195  bounds_lon(:,:)=0
196  bounds_lat(:,:)=0
197  field_A_srf(:,:)=0
198  mask(:)=0
199  n_local(:)=0
200
[1177]201  ncell=0
202  data_n_index=0
203  DO ind=1,ncell_glo
204    IF (i_index_glo(ind)==mpi_rank) THEN
205      ncell=ncell+1
206      i_index(ncell)=ind-1
207      lon(ncell)=lon_glo(ind)
208      lat(ncell)=lat_glo(ind)
209      bounds_lon(:,ncell)=bounds_lon_glo(:,ind)
210      bounds_lat(:,ncell)=bounds_lat_glo(:,ind)
211      field_A_srf(ncell,:)=i_index_glo(ind)
212      IF (MOD(ind,8)>=0 .AND. MOD(ind,8)<2) THEN
213        mask(ncell)=.FALSE.
214      ELSE
215        mask(ncell)=.TRUE.
216        data_n_index=data_n_index+1
217      ENDIF
218    ENDIF
219  ENDDO
220
221  ALLOCATE(field_A_compressed(data_n_index,llm))
222  ALLOCATE(data_i_index(data_n_index))
[1209]223  field_A_compressed(:,:)=0
224  data_i_index(:)=0
225
226
[1177]227  data_n_index=0
228  DO ind=1,ncell
229    IF (mask(ind)) THEN
230      data_n_index=data_n_index+1
231      data_i_index(data_n_index)=ind-1
232      field_A_compressed(data_n_index,:)=field_A_srf(ind,:)
233    ENDIF
234  ENDDO
235
236  CALL xios_context_initialize("surface",comm)
237  CALL xios_get_handle("surface",ctx_hdl)
238  CALL xios_set_current_context(ctx_hdl)
239
240  CALL xios_set_axis_attr("axis_srf",n_glo=llm ,value=lval) ;
241  CALL xios_set_domain_attr("domain_srf", ni_glo=ncell_glo, ni=ncell, ibegin=0, i_index=i_index)
242  CALL xios_set_domain_attr("domain_srf", type='unstructured', data_dim=1, data_ni=data_n_index, &
243                                          data_i_index=data_i_index)
244  CALL xios_set_domain_attr("domain_srf", lonvalue_1D=lon, latvalue_1D=lat)
245  CALL xios_set_domain_attr("domain_srf", nvertex=4, bounds_lon_1D=bounds_lon, bounds_lat_1D=bounds_lat)
246!  CALL xios_set_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
247
248
249
250  dtime%second=3600
251  CALL xios_set_timestep(dtime)
252
253  !CALL MSE_XIOS_GAUSS_GRID(NDGLG,NDLON,NPRGPNS ,NPRGPEW,MYSETA,MYSETB)
254   CALL MSE_XIOS_GAUSS_GRID(127  ,255  ,mpi_size,1      ,mpi_rank+1, 1)
255
256  CALL xios_close_context_definition()
257
258  !CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor_max=nbMax)
259  !ALLOCATE(local_neighbor(nbMax,ncell))
260  !CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
261
262   DO ts=1,24*10
263     CALL xios_update_calendar(ts)
264     CALL xios_send_field("field_A_srf",field_A_compressed)
265     CALL xios_send_field("field_B_srf",field_A_compressed(:,1))
266    ENDDO
267
268    CALL xios_context_finalize()
269
270  DEALLOCATE(lon_glo)
271  DEALLOCATE(lat_glo)
272  DEALLOCATE(bounds_lon_glo)
273  DEALLOCATE(bounds_lat_glo)
274  DEALLOCATE(i_index_glo)
275  DEALLOCATE(field_A_glo)
276  DEALLOCATE(mask_glo)
277  DEALLOCATE(i_index)
278  DEALLOCATE(lon)
279  DEALLOCATE(lat)
280  DEALLOCATE(bounds_lon)
281  DEALLOCATE(bounds_lat)
282  DEALLOCATE(field_A_srf)
283  DEALLOCATE(mask)
284  DEALLOCATE(field_A_compressed)
285  DEALLOCATE(data_i_index)
286  !DEALLOCATE(local_neighbor)
287 
288
289  CALL xios_finalize()
290
[1203]291print *, mpi_rank, "Client : xios_finalize "
[1177]292
293  !$omp barrier
294
295  !$omp master
296  CALL MPI_COMM_FREE(comm, ierr)
297  !$omp end master
298
299  !$omp barrier
300
301  !$omp end parallel
302
303
304    else
305
306    CALL xios_init_server
307    print *, "Server : xios_finalize "
308 
309    endif
310
311
312CONTAINS
313SUBROUTINE MSE_XIOS_GAUSS_GRID(NDGLG,NDLON,NPRGPNS, NPRGPEW,MYSETA, MYSETB)
314!!
315!!     PURPOSE : declare to XIOS a distribution for a rectilinear grid
316!!     --------
317!
318USE XIOS     , ONLY : XIOS_DOMAIN, XIOS_DOMAINGROUP,XIOS_GET_HANDLE, &
319                      XIOS_ADD_CHILD, XIOS_SET_DOMAIN_ATTR
320!
321!
322IMPLICIT NONE
323!
324INTEGER, INTENT(IN) :: NDGLG,NDLON,NPRGPNS, NPRGPEW,MYSETA, MYSETB
325!
326!
327!*       0.2   Declarations of local variables
328!              -------------------------------
329!
330CHARACTER(LEN=8), PARAMETER       :: YNAMGRID="complete"
331INTEGER                           :: NI,NJ,I,J,IOFF,JOFF
332REAL                   :: ZINCR
333DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:)   :: ZLATI,ZLONG
334!
335TYPE(xios_domaingroup)            :: domaingroup_hdl
336TYPE(xios_domain)                 :: domain_hdl
337!
338! Basic XIOS declarations
339 CALL XIOS_GET_HANDLE("domain_definition",domaingroup_hdl)
340 CALL XIOS_ADD_CHILD(domaingroup_hdl,domain_hdl,YNAMGRID)
341 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, type="rectilinear", data_dim=2)
342!
343! Compute domain size in longitude
344!
345IF (MOD(NDLON,NPRGPEW)==0) THEN
346   NI=NDLON/NPRGPEW
347   IOFF=(MYSETB-1)*NI
348ELSE
349   NI=NDLON/NPRGPEW+1
350   IOFF=(MYSETB-1)*NI
351   IF (MYSETB==NPRGPEW) NI=MOD(NDLON,NI)
352ENDIF
353!
354! Compute evenly spaced longitudes
355!
356ALLOCATE(ZLONG(NI))
357ZINCR=360./NDLON
358DO I=1,NI
359   ZLONG(I)=(IOFF+I)*ZINCR
360ENDDO
361!
362write(0,*) 'i=',IOFF+1,IOFF+NI
363CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, ni_glo=NDLON, ni=NI,ibegin=IOFF)
364 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, lonvalue_1d=ZLONG(:))
365!
366! Compute domain size in latitude
367!
368IF (MOD(NDGLG,NPRGPNS)==0) THEN
369   NJ=NDGLG/NPRGPNS
370   JOFF=(MYSETA-1)*NJ
371ELSE
372   NJ=NDGLG/NPRGPNS+1
373   JOFF=(MYSETA-1)*NJ
374   IF (MYSETA==NPRGPNS) NJ=MOD(NDGLG,NJ)
375ENDIF
376!
377ALLOCATE(ZLATI(NJ))
378ZINCR=180./NDGLG
379DO J=1,NJ
380   ZLATI(J)=(JOFF+J)*ZINCR
381ENDDO
382!
383!write(0,*) 'j=',JOFF+1,JOFF+NJ ; call flush(0)
384 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, nj_glo=NDGLG, nj=NJ, jbegin=JOFF)
385 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID,latvalue_1d=ZLATI(:)-90.)
386!
387 DEALLOCATE(ZLATI,ZLONG)!,ZLATIC,ZLONGC)
388END SUBROUTINE MSE_XIOS_GAUSS_GRID
389
390END PROGRAM test_unstruct_omp
391
392
393
394
395
Note: See TracBrowser for help on using the repository browser.