source: XIOS/trunk/src/test/test_unstruct_complete.f90 @ 953

Last change on this file since 953 was 953, checked in by ymipsl, 8 years ago

Add gaussian grid support./n YM

  • Property copyright set to
    Software name : XIOS (Xml I/O Server)
    http://forge.ipsl.jussieu.fr/ioserver
    Creation date : January 2009
    Licence : CeCCIL version2
    see license file in root directory : Licence_CeCILL_V2-en.txt
    or http://www.cecill.info/licences/Licence_CeCILL_V2-en.html
    Holder : CEA/LSCE (Laboratoire des Sciences du CLimat et de l'Environnement)
    CNRS/IPSL (Institut Pierre Simon Laplace)
    Project Manager : Yann Meurdesoif
    yann.meurdesoif@cea.fr
File size: 9.3 KB
Line 
1PROGRAM test_unstruct_complete
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=1
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  TYPE(xios_domain) :: domain_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
44  INTEGER,ALLOCATABLE :: data_i_index(:)
45  DOUBLE PRECISION,ALLOCATABLE :: field_A_compressed(:,:)
46
47  CALL xios_initialize(id,return_comm=comm)
48  CALL MPI_COMM_RANK(comm,mpi_rank,ierr)
49  CALL MPI_COMM_SIZE(comm,mpi_size,ierr)
50
51  CALL init_wait
52
53  ncell_glo=0
54  DO j=1,nlat
55    n =  NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
56    IF (n<8) n=8
57    ncell_glo=ncell_glo+n
58  ENDDO
59
60  ALLOCATE(lon_glo(ncell_glo))
61  ALLOCATE(lat_glo(ncell_glo))
62  ALLOCATE(bounds_lon_glo(4,ncell_glo))
63  ALLOCATE(bounds_lat_glo(4,ncell_glo))
64  ALLOCATE(i_index_glo(ncell_glo))
65  ALLOCATE(field_A_glo(ncell_glo,llm))
66  ALLOCATE(mask_glo(ncell_glo))
67
68  ind=0
69  DO j=1,nlat
70    n = NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
71    if (j==1) PRINT*,"--- ",n
72    if (j==nlat) PRINT*,"--- ",n
73    IF (n<8) n=8
74
75    DO i=1,n
76      ind=ind+1
77      list_ind(i,j)=ind
78      ilon=i-0.5
79      ilat=j-0.5
80
81      lat_glo(ind)= 90-(ilat*180./nlat)
82      lon_glo(ind)= (ilon*360./n)
83
84
85      bounds_lat_glo(1,ind)= 90-((ilat-0.5)*180./nlat)
86      bounds_lon_glo(1,ind)=((ilon-0.5)*360./n)
87
88      bounds_lat_glo(2,ind)= 90-((ilat-0.5)*180./nlat)
89      bounds_lon_glo(2,ind)=((ilon+0.5)*360./n)
90
91      bounds_lat_glo(3,ind)= 90-((ilat+0.5)*180./nlat)
92      bounds_lon_glo(3,ind)=((ilon+0.5)*360./n)
93
94      bounds_lat_glo(4,ind)= 90-((ilat+0.5)*180./nlat)
95      bounds_lon_glo(4,ind)=((ilon-0.5)*360./n)
96
97    ENDDO
98  ENDDO
99
100!  mpi_size=32
101  rank=(mpi_size-1)/2
102  ncell_x=sqrt(ncell_glo*1./mpi_size)
103
104  j1=nlat/2
105  DO WHILE(rank>=0)
106    j2=MAX(j1-ncell_x+1,1)
107    j=(j1+j2)/2
108    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
109    np = MIN(n/ncell_x,rank+1) ;
110    if (j2==1) np=rank+1
111
112    PRINT *,"domain ",j2,j1,rank,np ;
113    DO j=j2,j1
114      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
115      IF (n<8) n=8
116      DO i=1,n
117        ind=list_ind(i,j)
118        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
119          i_index_glo(ind) = rank - (i-1)/(n/np+1)
120        ELSE
121          i_index_glo(ind) = rank-(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
122        ENDIF
123      ENDDO
124    ENDDO
125    rank=rank-np
126    j1=j2-1
127  ENDDO
128
129  rank=(mpi_size-1)/2+1
130  ncell_x=sqrt(ncell_glo*1./mpi_size)
131
132  j1=nlat/2+1
133  DO WHILE(rank<=mpi_size-1)
134    j2=MIN(j1+ncell_x-1,nlat)
135    j=(j1+j2)/2
136    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
137    np = MIN(n/ncell_x,mpi_size-rank) ;
138    if (j2==nlat) np=mpi_size-rank
139
140    PRINT *,"domain ",j2,j1,rank,np ;
141    DO j=j1,j2
142      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
143      IF (n<8) n=8
144      DO i=1,n
145        ind=list_ind(i,j)
146        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
147          i_index_glo(ind) = rank + (i-1)/(n/np+1)
148        ELSE
149          i_index_glo(ind) = rank+(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
150        ENDIF
151      ENDDO
152    ENDDO
153    rank=rank+np
154    j1=j2+1
155  ENDDO
156
157  ncell=0
158  DO ind=1,ncell_glo
159    IF (i_index_glo(ind)==mpi_rank) ncell=ncell+1
160  ENDDO
161  ALLOCATE(i_index(ncell))
162  ALLOCATE(lon(ncell))
163  ALLOCATE(lat(ncell))
164  ALLOCATE(bounds_lon(4,ncell))
165  ALLOCATE(bounds_lat(4,ncell))
166  ALLOCATE(field_A_srf(ncell,llm))
167  ALLOCATE(mask(ncell))
168  ALLOCATE(n_local(ncell))
169  ncell=0
170  data_n_index=0
171  DO ind=1,ncell_glo
172    IF (i_index_glo(ind)==mpi_rank) THEN
173      ncell=ncell+1
174      i_index(ncell)=ind-1
175      lon(ncell)=lon_glo(ind)
176      lat(ncell)=lat_glo(ind)
177      bounds_lon(:,ncell)=bounds_lon_glo(:,ind)
178      bounds_lat(:,ncell)=bounds_lat_glo(:,ind)
179      field_A_srf(ncell,:)=i_index_glo(ind)
180      IF (MOD(ind,8)>=0 .AND. MOD(ind,8)<2) THEN
181        mask(ncell)=.FALSE.
182!        data_n_index=data_n_index+1
183      ELSE
184        mask(ncell)=.TRUE.
185        data_n_index=data_n_index+1
186      ENDIF
187    ENDIF
188  ENDDO
189
190  ALLOCATE(field_A_compressed(data_n_index,llm))
191  ALLOCATE(data_i_index(data_n_index))
192  data_n_index=0
193  DO ind=1,ncell
194    IF (mask(ind)) THEN
195      data_n_index=data_n_index+1
196      data_i_index(data_n_index)=ind-1
197      field_A_compressed(data_n_index,:)=field_A_srf(ind,:)
198    ENDIF
199  ENDDO
200
201  CALL xios_context_initialize("surface",comm)
202  CALL xios_get_handle("surface",ctx_hdl)
203  CALL xios_set_current_context(ctx_hdl)
204
205  CALL xios_set_axis_attr("axis_srf",n_glo=llm ,value=lval) ;
206  CALL xios_set_domain_attr("domain_srf", ni_glo=ncell_glo, ni=ncell, ibegin=0, i_index=i_index)
207  CALL xios_set_domain_attr("domain_srf", type='unstructured', data_dim=1, data_ni=data_n_index, &
208                                          data_i_index=data_i_index)
209  CALL xios_set_domain_attr("domain_srf", lonvalue_1D=lon, latvalue_1D=lat)
210  CALL xios_set_domain_attr("domain_srf", nvertex=4, bounds_lon_1D=bounds_lon, bounds_lat_1D=bounds_lat)
211!  CALL xios_set_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
212
213
214
215  dtime%second=3600
216  CALL xios_set_timestep(dtime)
217
218  !CALL MSE_XIOS_GAUSS_GRID(NDGLG,NDLON,NPRGPNS ,NPRGPEW,MYSETA,MYSETB)
219   CALL MSE_XIOS_GAUSS_GRID(127  ,255  ,mpi_size,1      ,mpi_rank+1, 1)
220
221  CALL xios_close_context_definition()
222
223  CALL xios_field_get_domain("field_A_expand",domain_hdl)
224  CALL xios_get_attr(domain_hdl,ni=ni)
225  PRINT *, "Domain destination ni = ",ni, "Domain source n= ",ncell
226  CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor_max=nbMax)
227  ALLOCATE(local_neighbor(nbMax,ncell))
228  CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
229  PRINT *, "Connectivity max = ",nbMax
230
231   DO ts=1,1
232     CALL xios_update_calendar(ts)
233     CALL xios_send_field("field_A_srf",field_A_compressed)
234     CALL xios_send_field("field_B_srf",field_A_compressed(:,1))
235    ENDDO
236
237    CALL xios_context_finalize()
238
239  DEALLOCATE(lon_glo)
240  DEALLOCATE(lat_glo)
241  DEALLOCATE(bounds_lon_glo)
242  DEALLOCATE(bounds_lat_glo)
243  DEALLOCATE(i_index_glo)
244  DEALLOCATE(field_A_glo)
245  DEALLOCATE(mask_glo)
246  DEALLOCATE(i_index)
247  DEALLOCATE(lon)
248  DEALLOCATE(lat)
249  DEALLOCATE(bounds_lon)
250  DEALLOCATE(bounds_lat)
251  DEALLOCATE(field_A_srf)
252  DEALLOCATE(mask)
253  DEALLOCATE(field_A_compressed)
254  DEALLOCATE(data_i_index)
255
256  CALL MPI_COMM_FREE(comm, ierr)
257
258  CALL xios_finalize()
259
260CONTAINS
261SUBROUTINE MSE_XIOS_GAUSS_GRID(NDGLG,NDLON,NPRGPNS, NPRGPEW,MYSETA, MYSETB)
262!!
263!!     PURPOSE : declare to XIOS a distribution for a rectilinear grid
264!!     --------
265!
266USE XIOS     , ONLY : XIOS_DOMAIN, XIOS_DOMAINGROUP,XIOS_GET_HANDLE, &
267                      XIOS_ADD_CHILD, XIOS_SET_DOMAIN_ATTR
268!
269!
270IMPLICIT NONE
271!
272INTEGER, INTENT(IN) :: NDGLG,NDLON,NPRGPNS, NPRGPEW,MYSETA, MYSETB
273!
274!
275!*       0.2   Declarations of local variables
276!              -------------------------------
277!
278CHARACTER(LEN=8), PARAMETER       :: YNAMGRID="complete"
279INTEGER                           :: NI,NJ,I,J,IOFF,JOFF
280REAL                   :: ZINCR
281DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:)   :: ZLATI,ZLONG
282!
283TYPE(xios_domaingroup)            :: domaingroup_hdl
284TYPE(xios_domain)                 :: domain_hdl
285!
286! Basic XIOS declarations
287 CALL XIOS_GET_HANDLE("domain_definition",domaingroup_hdl)
288 CALL XIOS_ADD_CHILD(domaingroup_hdl,domain_hdl,YNAMGRID)
289 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, type="rectilinear", data_dim=2)
290!
291! Compute domain size in longitude
292!
293IF (MOD(NDLON,NPRGPEW)==0) THEN
294   NI=NDLON/NPRGPEW
295   IOFF=(MYSETB-1)*NI
296ELSE
297   NI=NDLON/NPRGPEW+1
298   IOFF=(MYSETB-1)*NI
299   IF (MYSETB==NPRGPEW) NI=MOD(NDLON,NI)
300ENDIF
301!
302! Compute evenly spaced longitudes
303!
304ALLOCATE(ZLONG(NI))
305ZINCR=360./NDLON
306DO I=1,NI
307   ZLONG(I)=(IOFF+I)*ZINCR
308ENDDO
309!
310write(0,*) 'i=',IOFF+1,IOFF+NI
311CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, ni_glo=NDLON, ni=NI,ibegin=IOFF)
312 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, lonvalue_1d=ZLONG(:))
313!
314! Compute domain size in latitude
315!
316IF (MOD(NDGLG,NPRGPNS)==0) THEN
317   NJ=NDGLG/NPRGPNS
318   JOFF=(MYSETA-1)*NJ
319ELSE
320   NJ=NDGLG/NPRGPNS+1
321   JOFF=(MYSETA-1)*NJ
322   IF (MYSETA==NPRGPNS) NJ=MOD(NDGLG,NJ)
323ENDIF
324!
325ALLOCATE(ZLATI(NJ))
326ZINCR=180./NDGLG
327DO J=1,NJ
328   ZLATI(J)=(JOFF+J)*ZINCR
329ENDDO
330!
331!write(0,*) 'j=',JOFF+1,JOFF+NJ ; call flush(0)
332 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID, nj_glo=NDGLG, nj=NJ, jbegin=JOFF)
333 CALL XIOS_SET_DOMAIN_ATTR(YNAMGRID,latvalue_1d=ZLATI(:)-90.)
334!
335 DEALLOCATE(ZLATI,ZLONG)!,ZLATIC,ZLONGC)
336END SUBROUTINE MSE_XIOS_GAUSS_GRID
337
338END PROGRAM test_unstruct_complete
339
340
341
342
343
Note: See TracBrowser for help on using the repository browser.