source: XIOS/trunk/src/test/test_complete.f90 @ 537

Last change on this file since 537 was 537, checked in by rlacroix, 9 years ago

Add a new attribute type for durations and use it for the context's timestep.

Note that the "xios_time" type and the "xios_set_timestep" procedure have been removed from the Fortran interface. Instead, the "xios_duration" type and the "xios_get_context_attr"/"xios_set_context_attr" procedures should now be used to get/set the timestep.

  • 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: 8.4 KB
Line 
1PROGRAM test_complete
2
3  USE xios
4  USE mod_wait
5  IMPLICIT NONE
6  INCLUDE "mpif.h"
7  INTEGER :: rank
8  INTEGER :: size_loc
9  INTEGER :: ierr
10 
11  CHARACTER(len=*),PARAMETER :: id="client"
12  INTEGER :: comm
13  TYPE(xios_date)      :: start_date, time_origin
14  TYPE(xios_duration)  :: dtime
15  TYPE(xios_context) :: ctx_hdl
16  INTEGER,PARAMETER :: ni_glo=100
17  INTEGER,PARAMETER :: nj_glo=100 
18  INTEGER,PARAMETER :: llm=5 
19  DOUBLE PRECISION  :: lval(llm)=1
20  TYPE(xios_field) :: field_hdl
21  TYPE(xios_fieldgroup) :: fieldgroup_hdl
22  TYPE(xios_file) :: file_hdl
23  LOGICAL :: ok
24  CHARACTER(len=256) :: crname
25
26  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
27  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
28  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A_atm(:,:,:), field_A_srf(:,:), lonvalue(:)
29  INTEGER, ALLOCATABLE :: kindex(:)
30  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
31  INTEGER :: i,j,l,ts,n, nb_pt
32
33!!! MPI Initialization
34
35  CALL MPI_INIT(ierr)
36 
37  CALL init_wait
38 
39!!! XIOS Initialization (get the local communicator)
40
41  CALL xios_initialize(id,return_comm=comm)
42
43  CALL MPI_COMM_RANK(comm,rank,ierr)
44  CALL MPI_COMM_SIZE(comm,size_loc,ierr) 
45 
46
47!###########################################################################
48! Contexte ATM
49!###########################################################################
50
51!!! Initialisation des coordonnées globales et locales pour la grille réguliÚre
52
53  DO j=1,nj_glo
54    DO i=1,ni_glo
55      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
56      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
57      DO l=1,llm
58        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
59      ENDDO
60    ENDDO
61  ENDDO
62  ni=ni_glo ; ibegin=1
63
64  jbegin=1
65  DO n=0,size_loc-1
66    nj=nj_glo/size_loc
67    IF (n<MOD(nj_glo,size_loc)) nj=nj+1
68    IF (n==rank) exit
69    jbegin=jbegin+nj
70  ENDDO
71 
72  iend=ibegin+ni-1 ; jend=jbegin+nj-1
73
74  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A_atm(0:ni+1,-1:nj+2,llm),lonvalue(ni*nj))
75  lon(:,:)=lon_glo(ibegin:iend,jbegin:jend)
76  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend)
77  field_A_atm(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:)
78 
79
80!!! Context ATMOSPHERE
81
82  CALL xios_context_initialize("atmosphere",comm)
83  CALL xios_get_handle("atmosphere",ctx_hdl)
84  CALL xios_set_current_context(ctx_hdl)
85 
86  CALL xios_set_context_attr("atmosphere",calendar_type="Gregorian")
87  start_date = xios_date(2000, 01, 01, 00, 00, 00)
88  CALL xios_set_context_attr("atmosphere",start_date=start_date)
89  time_origin = xios_date(1999, 01, 01, 15, 00, 00)
90  CALL xios_set_context_attr("atmosphere",time_origin=time_origin)
91
92  CALL xios_set_axis_attr("axis_atm",size=llm ,value=lval) ;
93
94  CALL xios_set_domain_attr("domain_atm",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
95  CALL xios_set_domain_attr("domain_atm",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
96  CALL xios_set_domain_attr("domain_atm",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
97
98  CALL xios_set_domain_attr("domain_atm_zoom",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
99  CALL xios_set_domain_attr("domain_atm_zoom",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
100  CALL xios_set_domain_attr("domain_atm_zoom",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
101
102!!! Activation du groupe field_definition
103
104  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
105
106!!! Création d un nouveau champ
107
108  CALL xios_get_handle("field_definition",fieldgroup_hdl)
109  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_atm")
110
111!!! Heritage des attributs d un autre champ
112
113  CALL xios_set_attr(field_hdl,field_ref="field_A_atm",name="field_B_atm")
114 
115!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
116
117  CALL xios_get_handle("output_atmosphere",file_hdl)
118  CALL xios_add_child(file_hdl,field_hdl)
119  CALL xios_set_attr(field_hdl,field_ref="field_B_atm",name="field_C_atm")
120   
121!!! Definition du timestep
122
123  dtime%second=3600
124  CALL xios_set_context_attr("atmosphere", timestep=dtime)
125   
126!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
127
128  ni=0 ; lonvalue(:)=0
129  CALL xios_get_domain_attr("domain_atm",ni=ni,lonvalue=lonvalue)
130   
131  PRINT *,"ni",ni
132  PRINT *,"lonvalue",lonvalue ;
133
134!!! Fin de la definition du contexte
135
136  CALL xios_close_context_definition()
137
138!!! Test des valeurs des champs/fichiers
139 
140  !!! Attribut defini ?
141
142  CALL xios_is_defined_field_attr("field_A_atm",enabled=ok)
143  PRINT *,"field_A_atm : attribute enabled is defined ? ",ok
144
145  !!! Recuperer la valeur d un attribut
146 
147  CALL xios_get_field_attr("field_A_atm",name=crname)
148  PRINT *,"field_A_atm : attribute name is : ",TRIM(crname)
149
150  !!! Champ actif (besoin de fournir la valeur) ?
151
152    PRINT*,"field field_A_atm is active ? ",xios_field_is_active("field_A_atm")
153
154  !!! Champ defini ?
155
156    PRINT*,"field field_A_atm is valid ?",xios_is_valid_field("field_A_atm")
157
158
159!###########################################################################
160! Contexte SRF
161!###########################################################################
162
163!!! Initialisation des coordonnées globales et locales pour la grille indexee (1 point sur 2)
164
165    nb_pt=ni*nj/2
166    ALLOCATE(kindex(nb_pt),field_A_srf(nb_pt,llm))
167    DO i=1,nb_pt
168      kindex(i)=2*i-1
169    ENDDO
170    field_A_srf(1:nb_pt,:)=RESHAPE(field_A_glo(ibegin:iend:2,jbegin:jend,:),(/ nb_pt,llm /))
171
172  CALL xios_context_initialize("surface",comm)
173  CALL xios_get_handle("surface",ctx_hdl)
174  CALL xios_set_current_context(ctx_hdl)
175 
176  CALL xios_set_context_attr("surface",calendar_type="Gregorian")
177  start_date = xios_date(2000, 01, 01, 00, 00, 00)
178  CALL xios_set_context_attr("surface",start_date=start_date)
179  time_origin = xios_date(1999, 01, 01, 15, 00, 00)
180  CALL xios_set_context_attr("surface",time_origin=time_origin)
181
182  CALL xios_set_axis_attr("axis_srf",size=llm ,value=lval) ;
183  CALL xios_set_domain_attr("domain_srf",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
184  CALL xios_set_domain_attr("domain_srf",data_dim=1, data_ibegin=0, data_ni=nb_pt)
185  CALL xios_set_domain_attr("domain_srf",data_n_index=nb_pt, data_i_index=kindex)
186  CALL xios_set_domain_attr("domain_srf",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
187
188!!! Création d un nouveau champ
189
190  CALL xios_get_handle("field_definition",fieldgroup_hdl)
191  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B_srf")
192
193!!! Heritage des attributs d un autre champ
194
195  CALL xios_set_attr(field_hdl,field_ref="field_A_srf",name="field_B_srf")
196 
197!!! Affectation de ce nouveau champ au fichier avec un nouveau nom
198
199  CALL xios_get_handle("output_surface",file_hdl)
200  CALL xios_add_child(file_hdl,field_hdl)
201  CALL xios_set_attr(field_hdl,field_ref="field_B_srf",name="field_C_srf")
202   
203!!! Definition du timestep
204
205  dtime%second=1800
206  CALL xios_set_context_attr("surface", timestep=dtime)
207   
208!!! Recupration des valeurs des longitudes et de taille des domaines locaux (pour test de fonctionnalité)
209
210  ni=0 ; lonvalue(:)=0
211  CALL xios_get_domain_attr("domain_srf",ni=ni,lonvalue=lonvalue)
212   
213  PRINT *,"ni",ni
214  PRINT *,"lonvalue",lonvalue ;
215
216!!! Fin de la definition du contexte SRF
217
218  CALL xios_close_context_definition()
219
220
221!####################################################################################
222!!! Boucle temporelle
223!####################################################################################
224
225    DO ts=1,24*10
226
227      CALL xios_get_handle("atmosphere",ctx_hdl)
228      CALL xios_set_current_context(ctx_hdl)   
229
230!!! Mise a jour du pas de temps
231
232      CALL xios_update_calendar(ts)
233
234!!! On donne la valeur du champ atm
235
236      CALL xios_send_field("field_A_atm",field_A_atm)
237
238!!! On change de contexte
239
240      CALL xios_get_handle("surface",ctx_hdl)
241      CALL xios_set_current_context(ctx_hdl)   
242
243!!! Mise a jour du pas de temps
244
245      CALL xios_update_calendar(ts)
246
247!!! On donne la valeur du champ srf
248
249      CALL xios_send_field("field_A_srf",field_A_srf)
250
251      CALL wait_us(5000) ;
252    ENDDO
253
254!####################################################################################
255!!! Finalisation
256!####################################################################################
257
258!!! Fin des contextes
259   
260    CALL xios_context_finalize()
261    CALL xios_get_handle("atmosphere",ctx_hdl)
262    CALL xios_set_current_context(ctx_hdl)   
263    CALL xios_context_finalize()
264   
265!!! Fin de XIOS
266
267    CALL xios_finalize()
268 
269    CALL MPI_FINALIZE(ierr)
270 
271  END PROGRAM test_complete
272
273
274
275 
276
277 
Note: See TracBrowser for help on using the repository browser.