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

Last change on this file since 666 was 666, checked in by mhnguyen, 9 years ago

Change name of several axis attributes and remove some redundant variable of domain

+) Change name of axis attributes to make them consistent with ones of domain
+) Remove zoom_client_* of domain

Test
+) On Curie
+) All tests pass and are correct

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