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

Last change on this file since 934 was 934, checked in by mhnguyen, 8 years ago

Adding new transformation: Compute_connectivity_domain

Test
+) On Curie
+) Test passes

  • 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: 6.8 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=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
42  INTEGER :: data_n_index
43  INTEGER,ALLOCATABLE :: data_i_index(:)
44  DOUBLE PRECISION,ALLOCATABLE :: field_A_compressed(:,:)
45
46  CALL xios_initialize(id,return_comm=comm)
47  CALL MPI_COMM_RANK(comm,mpi_rank,ierr)
48  CALL MPI_COMM_SIZE(comm,mpi_size,ierr)
49
50  CALL init_wait
51
52  ncell_glo=0
53  DO j=1,nlat
54    n =  NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
55    IF (n<8) n=8
56    ncell_glo=ncell_glo+n
57  ENDDO
58
59  ALLOCATE(lon_glo(ncell_glo))
60  ALLOCATE(lat_glo(ncell_glo))
61  ALLOCATE(bounds_lon_glo(4,ncell_glo))
62  ALLOCATE(bounds_lat_glo(4,ncell_glo))
63  ALLOCATE(i_index_glo(ncell_glo))
64  ALLOCATE(field_A_glo(ncell_glo,llm))
65  ALLOCATE(mask_glo(ncell_glo))
66
67  ind=0
68  DO j=1,nlat
69    n = NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
70    if (j==1) PRINT*,"--- ",n
71    if (j==nlat) PRINT*,"--- ",n
72    IF (n<8) n=8
73
74    DO i=1,n
75      ind=ind+1
76      list_ind(i,j)=ind
77      ilon=i-0.5
78      ilat=j-0.5
79
80      lat_glo(ind)= 90-(ilat*180./nlat)
81      lon_glo(ind)= (ilon*360./n)
82
83
84      bounds_lat_glo(1,ind)= 90-((ilat-0.5)*180./nlat)
85      bounds_lon_glo(1,ind)=((ilon-0.5)*360./n)
86
87      bounds_lat_glo(2,ind)= 90-((ilat-0.5)*180./nlat)
88      bounds_lon_glo(2,ind)=((ilon+0.5)*360./n)
89
90      bounds_lat_glo(3,ind)= 90-((ilat+0.5)*180./nlat)
91      bounds_lon_glo(3,ind)=((ilon+0.5)*360./n)
92
93      bounds_lat_glo(4,ind)= 90-((ilat+0.5)*180./nlat)
94      bounds_lon_glo(4,ind)=((ilon-0.5)*360./n)
95
96    ENDDO
97  ENDDO
98
99!  mpi_size=32
100  rank=(mpi_size-1)/2
101  ncell_x=sqrt(ncell_glo*1./mpi_size)
102
103  j1=nlat/2
104  DO WHILE(rank>=0)
105    j2=MAX(j1-ncell_x+1,1)
106    j=(j1+j2)/2
107    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
108    np = MIN(n/ncell_x,rank+1) ;
109    if (j2==1) np=rank+1
110
111    PRINT *,"domain ",j2,j1,rank,np ;
112    DO j=j2,j1
113      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
114      IF (n<8) n=8
115      DO i=1,n
116        ind=list_ind(i,j)
117        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
118          i_index_glo(ind) = rank - (i-1)/(n/np+1)
119        ELSE
120          i_index_glo(ind) = rank-(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
121        ENDIF
122      ENDDO
123    ENDDO
124    rank=rank-np
125    j1=j2-1
126  ENDDO
127
128  rank=(mpi_size-1)/2+1
129  ncell_x=sqrt(ncell_glo*1./mpi_size)
130
131  j1=nlat/2+1
132  DO WHILE(rank<=mpi_size-1)
133    j2=MIN(j1+ncell_x-1,nlat)
134    j=(j1+j2)/2
135    n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
136    np = MIN(n/ncell_x,mpi_size-rank) ;
137    if (j2==nlat) np=mpi_size-rank
138
139    PRINT *,"domain ",j2,j1,rank,np ;
140    DO j=j1,j2
141      n=NINT(COS(Pi/2-(j-0.5)*PI/nlat)*nlon)
142      IF (n<8) n=8
143      DO i=1,n
144        ind=list_ind(i,j)
145        IF ( (i-1) < MOD(n,np)*(n/np+1)) THEN
146          i_index_glo(ind) = rank + (i-1)/(n/np+1)
147        ELSE
148          i_index_glo(ind) = rank+(MOD(n,np)+ (i-1-MOD(n,np)*(n/np+1))/(n/np))
149        ENDIF
150      ENDDO
151    ENDDO
152    rank=rank+np
153    j1=j2+1
154  ENDDO
155
156  ncell=0
157  DO ind=1,ncell_glo
158    IF (i_index_glo(ind)==mpi_rank) ncell=ncell+1
159  ENDDO
160  ALLOCATE(i_index(ncell))
161  ALLOCATE(lon(ncell))
162  ALLOCATE(lat(ncell))
163  ALLOCATE(bounds_lon(4,ncell))
164  ALLOCATE(bounds_lat(4,ncell))
165  ALLOCATE(field_A_srf(ncell,llm))
166  ALLOCATE(mask(ncell))
167  ALLOCATE(n_local(ncell))
168  ncell=0
169  data_n_index=0
170  DO ind=1,ncell_glo
171    IF (i_index_glo(ind)==mpi_rank) THEN
172      ncell=ncell+1
173      i_index(ncell)=ind-1
174      lon(ncell)=lon_glo(ind)
175      lat(ncell)=lat_glo(ind)
176      bounds_lon(:,ncell)=bounds_lon_glo(:,ind)
177      bounds_lat(:,ncell)=bounds_lat_glo(:,ind)
178      field_A_srf(ncell,:)=i_index_glo(ind)
179      IF (MOD(ind,8)>=0 .AND. MOD(ind,8)<2) THEN
180        mask(ncell)=.FALSE.
181      ELSE
182        mask(ncell)=.TRUE.
183        data_n_index=data_n_index+1
184      ENDIF
185    ENDIF
186  ENDDO
187
188  ALLOCATE(field_A_compressed(data_n_index,llm))
189  ALLOCATE(data_i_index(data_n_index))
190  data_n_index=0
191  DO ind=1,ncell
192    IF (mask(ind)) THEN
193      data_n_index=data_n_index+1
194      data_i_index(data_n_index)=ind-1
195      field_A_compressed(data_n_index,:)=field_A_srf(ind,:)
196    ENDIF
197  ENDDO
198
199  CALL xios_context_initialize("surface",comm)
200  CALL xios_get_handle("surface",ctx_hdl)
201  CALL xios_set_current_context(ctx_hdl)
202
203  CALL xios_set_axis_attr("axis_srf",n_glo=llm ,value=lval) ;
204  CALL xios_set_domain_attr("domain_srf", ni_glo=ncell_glo, ni=ncell, ibegin=1, i_index=i_index)
205  CALL xios_set_domain_attr("domain_srf", type='unstructured', data_dim=1, data_ni=data_n_index, &
206                                          data_i_index=data_i_index)
207  CALL xios_set_domain_attr("domain_srf", lonvalue_1D=lon, latvalue_1D=lat)
208  CALL xios_set_domain_attr("domain_srf", nvertex=4, bounds_lon_1D=bounds_lon, bounds_lat_1D=bounds_lat)
209!  CALL xios_set_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
210
211
212
213  dtime%second=3600
214  CALL xios_set_timestep(dtime)
215  CALL xios_close_context_definition()
216
217  CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor_max=nbMax)
218  ALLOCATE(local_neighbor(nbMax,ncell))
219  CALL xios_get_compute_connectivity_domain_attr("compute", n_neighbor=n_local, local_neighbor=local_neighbor)
220
221   DO ts=1,24*10
222     CALL xios_update_calendar(ts)
223     CALL xios_send_field("field_A_srf",field_A_compressed)
224    ENDDO
225
226    CALL xios_context_finalize()
227
228  DEALLOCATE(lon_glo)
229  DEALLOCATE(lat_glo)
230  DEALLOCATE(bounds_lon_glo)
231  DEALLOCATE(bounds_lat_glo)
232  DEALLOCATE(i_index_glo)
233  DEALLOCATE(field_A_glo)
234  DEALLOCATE(mask_glo)
235  DEALLOCATE(i_index)
236  DEALLOCATE(lon)
237  DEALLOCATE(lat)
238  DEALLOCATE(bounds_lon)
239  DEALLOCATE(bounds_lat)
240  DEALLOCATE(field_A_srf)
241  DEALLOCATE(mask)
242  DEALLOCATE(field_A_compressed)
243  DEALLOCATE(data_i_index)
244
245  CALL MPI_COMM_FREE(comm, ierr)
246
247  CALL xios_finalize()
248
249  END PROGRAM test_unstruct_complete
250
251
252
253
254
Note: See TracBrowser for help on using the repository browser.