source: XIOS/dev/branch_yushan/src/test/test_regular.f90 @ 1037

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

initialize the branch

File size: 5.0 KB
Line 
1PROGRAM test_regular
2
3  USE xios
4  IMPLICIT NONE
5  INCLUDE "mpif.h"
6
7  INTEGER, PARAMETER :: ntime=1
8
9  CHARACTER(len=*),PARAMETER :: id="client"
10  TYPE(xios_duration)  :: dtime
11  TYPE(xios_context) :: ctx_hdl
12  TYPE(xios_field) :: field_hdl
13  TYPE(xios_fieldgroup) :: fieldgroup_hdl
14  TYPE(xios_file) :: file_hdl
15  LOGICAL :: ok
16  CHARACTER(len=256) :: crname
17  INTEGER :: ts
18  INTEGER :: comm 
19  INTEGER :: ierr
20  INTEGER :: size, rank
21
22  INTEGER :: nlon = 100 
23  INTEGER :: nlat = 100
24  INTEGER :: ncell 
25  INTEGER :: ilat, ilon, ind
26  DOUBLE PRECISION :: lon1, lon2, lat1, lat2
27  INTEGER :: ni, ibegin
28
29  DOUBLE PRECISION,ALLOCATABLE :: lon_glo(:)
30  DOUBLE PRECISION,ALLOCATABLE :: lat_glo(:)
31  DOUBLE PRECISION,ALLOCATABLE :: bounds_lon_glo(:,:)
32  DOUBLE PRECISION,ALLOCATABLE :: bounds_lat_glo(:,:)
33  DOUBLE PRECISION,ALLOCATABLE :: field_temp_glo(:,:)
34  DOUBLE PRECISION,ALLOCATABLE :: lon(:)
35  DOUBLE PRECISION,ALLOCATABLE :: lat(:)
36  DOUBLE PRECISION,ALLOCATABLE :: bounds_lon(:,:)
37  DOUBLE PRECISION,ALLOCATABLE :: bounds_lat(:,:)
38  DOUBLE PRECISION,ALLOCATABLE :: field_temp(:,:)
39
40!!! MPI Initialization
41  CALL MPI_INIT(ierr)
42
43!!! XIOS Initialization (get the local communicator)
44  CALL xios_initialize(id,return_comm=comm)
45
46!###########################################################################
47! Contexte ATM
48!###########################################################################
49
50!!! Initialisation des coordonnées globales et locales pour la grille réguliÚre
51
52! Regions around the poles are not included into the grid
53! The whole grid is rectangular (nvertex=4)
54
55  ncell = nlon * (nlat-1)
56  ALLOCATE(lon_glo(ncell))
57  ALLOCATE(lat_glo(ncell))
58  ALLOCATE(bounds_lon_glo(4,ncell))
59  ALLOCATE(bounds_lat_glo(4,ncell))
60  ALLOCATE(field_temp_glo(ncell,ntime))
61
62
63  ind = 0
64  DO ilat = 1, nlat-1
65   DO ilon = 1, nlon
66
67      ind=ind+1
68
69      lon1 = 360./DBLE(nlon) * DBLE(ilon-1)
70      lon2 = lon1 + 360./DBLE(nlon)
71
72      lat1 = (90. + 90./DBLE(nlat)) - 180./DBLE(nlat)*DBLE(ilat)
73      lat2 = lat1 - 180./DBLE(nlat)
74
75      lon_glo(ind) = (lon1+lon2)*0.5
76      lat_glo(ind) = (lat1+lat2)*0.5 
77
78      bounds_lon_glo(1,ind) = lon1
79      bounds_lon_glo(2,ind) = lon2
80      bounds_lon_glo(3,ind) = lon2
81      bounds_lon_glo(4,ind) = lon1
82
83      bounds_lat_glo(1,ind) = lat1
84      bounds_lat_glo(2,ind) = lat1
85      bounds_lat_glo(3,ind) = lat2     
86      bounds_lat_glo(4,ind) = lat2     
87
88      field_temp_glo(ind,1) = DBLE(ind)
89
90    ENDDO
91  ENDDO
92
93! Initialization of local variables
94
95  CALL MPI_COMM_RANK(comm,rank,ierr)
96  CALL MPI_COMM_SIZE(comm,size,ierr)
97
98  IF (MOD(ncell, size) == 0) THEN
99    ni = ncell/size
100    ibegin = rank*ni
101  ELSE
102    IF (rank < MOD(ncell, size)) THEN
103      ni = ncell/size + 1
104      ibegin = rank*(ncell/size + 1)
105    ELSE
106      ni = ncell/size
107      IF (rank == MOD(ncell, size)) THEN
108        ibegin = rank*(ncell/size + 1)
109      ELSE
110        ibegin = MOD(ncell,size)*(ncell/size + 1) + (rank-MOD(ncell,size))*ncell/size
111      END IF
112    END IF
113  END IF
114
115  ALLOCATE(lon(ni))
116  ALLOCATE(lat(ni))
117  ALLOCATE(bounds_lon(4,ni))
118  ALLOCATE(bounds_lat(4,ni))
119  ALLOCATE(field_temp(ni,ntime)) 
120  lon = lon_glo(1+ibegin:1+ibegin+ni)
121  lat = lat_glo(1+ibegin:1+ibegin+ni)
122  bounds_lon(:,:) = bounds_lon_glo(:,1+ibegin:1+ibegin+ni)
123  bounds_lat(:,:) = bounds_lat_glo(:,1+ibegin:1+ibegin+ni)
124  field_temp(:,:) = rank
125
126
127!!! Context ATMOSPHERE
128
129  CALL xios_context_initialize("atmosphere",comm)
130  CALL xios_get_handle("atmosphere",ctx_hdl)
131  CALL xios_set_current_context(ctx_hdl)
132
133  CALL xios_define_calendar(type="Gregorian", &
134                            start_date=xios_date(2000, 01, 01, 00, 00, 00), &
135                            time_origin=xios_date(1999, 01, 01, 15, 00, 00))
136
137  CALL xios_set_domain_attr("face", ni_glo=ncell, ibegin=ibegin, ni=ni, type='unstructured')
138  CALL xios_set_domain_attr("face", lonvalue_1d=lon, latvalue_1d=lat)
139  CALL xios_set_domain_attr("face", bounds_lon_1d=bounds_lon, bounds_lat_1d=bounds_lat)
140
141   
142!!! Definition du timestep
143
144  dtime%second=3600
145  CALL xios_set_timestep(timestep=dtime)
146
147!!! Fin de la definition du contexte
148
149  CALL xios_close_context_definition()
150
151
152!####################################################################################
153!!! Boucle temporelle
154!####################################################################################
155   
156    DO ts=1,1
157
158!!! Mise a jour du pas de temps
159      CALL xios_update_calendar(ts)
160
161!!! On donne la valeur du champ atm
162     CALL xios_send_field("temp",field_temp(:,1))
163
164    ENDDO
165
166!####################################################################################
167!!! Finalisation
168!####################################################################################
169
170!!! Fin des contextes
171
172    CALL xios_context_finalize()
173
174    DEALLOCATE(lon_glo, lat_glo)
175    DEALLOCATE(bounds_lon_glo, bounds_lat_glo)
176    DEALLOCATE(field_temp_glo)
177    DEALLOCATE(lon, lat)
178    DEALLOCATE(bounds_lon, bounds_lat)
179    DEALLOCATE(field_temp)
180
181!!! Fin de XIOS
182
183    CALL MPI_COMM_FREE(comm, ierr)
184
185    CALL xios_finalize()
186
187    CALL MPI_FINALIZE(ierr)
188
189  END PROGRAM test_regular
190
191
192
193
194
195
Note: See TracBrowser for help on using the repository browser.