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

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

toy_cmip6_omp from Curie

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