source: XMLIO_V2/dev/dev_rv/src/xmlio/fake_client/fake_nemo.f90 @ 177

Last change on this file since 177 was 177, checked in by hozdoba, 13 years ago
File size: 17.8 KB
Line 
1! --------------------------------------------------- !
2!          XMLIO SERVER MAIN TEST (NEMO)              !
3! --------------------------------------------------- !
4
5MODULE NEMO_FAKE
6
7   ! Modules de la bibliothÚque xmlioserver
8   USE IXMLIOSERVER
9   USE ISO_C_BINDING
10
11include 'mpif.h'
12
13   CONTAINS
14
15   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
16
17   SUBROUTINE NEMO_FAKE_ENTRY(comm_client, comm_client_grp, comm_client_server) BIND(C)
18      INTEGER(kind = C_INT), INTENT(IN), VALUE :: comm_client,       & ! communicateur des clients
19                                                  comm_client_grp,   & ! communicateur du groupe de clients
20                                                  comm_client_server   ! communicateur client-serveur
21      REAL(kind = 8), DIMENSION(10000)   :: real_array
22      INTEGER                           :: rankGrp, error
23      INTEGER                           :: ibegin, iend, jbegin, jend
24      TYPE(XDate)                       :: init_date_nemo  = XDate(1985, 03, 15, 17, 35, 00)
25      TYPE(XHandle)                     :: nemo_style_ctxt = NULLHANDLE
26      TYPE(XHandle)                     :: temp_mod   = NULLHANDLE, &
27                                           temp_mod_  = NULLHANDLE, &
28                                           temp_mod__ = NULLHANDLE
29
30      CALL MPI_COMM_RANK(comm_client, rankGrp, error)
31
32      IF (rankGrp .EQ. 0) THEN
33          PRINT*," Starting NEMO Client Tests ..."
34      END IF
35
36      ! Parsing du document xml de définition à partir d'une faire de caractÚre.
37      CALL xml_parse_string ("<? xml version=1.0 ?><simulation></simulation>")
38
39      !!!!!!!!!!!!!!!!!!!! EXEMPLE RECONSTRUCTION !!!!!!!!!!!!!!!!!!!!!
40
41      ! On crée un nouveau context et on lui associe un handle.
42      CALL context_create(context_hdl   = nemo_style_ctxt, &
43                          context_id    = "nemo_style",    &
44                          calendar_type = GREGORIAN,       &
45                          init_date     = init_date_nemo)
46
47      ! ---------> field_definition
48      CALL handle_create(temp_mod, GFIELD,  "field_definition")
49
50      ! Ajout d'un groupe de champ anomyme
51      CALL xml_tree_add(parent_hdl  = temp_mod,        &
52                        parent_type = GFIELD,          &
53                        child_hdl   = temp_mod_,       &
54                        child_type  = GFIELD)
55
56      CALL set_field_attributes(field_hdl = temp_mod_, &
57                                ftype     = GFIELD,    &
58                                unit_     = "SI",      &
59                                prec_     = 8)
60
61      CALL xml_tree_add(parent_hdl  = temp_mod_,       &
62                        parent_type = GFIELD,          &
63                        child_hdl   = temp_mod,        &
64                        child_type  = GFIELD,          &
65                        child_id    = "field_enabled")
66
67      CALL set_field_attributes(field_hdl      = temp_mod,     &
68                                ftype          = GFIELD,       &
69                                operation_     = "instant",    &
70                                enabled_       = .TRUE._1)
71
72      CALL xml_tree_add(parent_hdl  = temp_mod,        &
73                        parent_type = GFIELD,          &
74                        child_hdl   = temp_mod__,      &
75                        child_type  = EFIELD,          &
76                        child_id    = "champ_2D_k8_inst")
77
78      CALL set_field_attributes(field_hdl      = temp_mod__,   &
79                                ftype          = EFIELD,       &
80                                name_          = "champ1",     &
81                                standard_name_ = "lechamp1",   &
82                                long_name_     = "le champ 1", &
83                                domain_ref_    = "simple_domaine0")
84
85      CALL xml_tree_add(parent_hdl  = temp_mod,        &
86                        parent_type = GFIELD,          &
87                        child_hdl   = temp_mod__,      &
88                        child_type  = EFIELD,          &
89                        child_id    = "champ_2D_k4_once_dis")
90
91      CALL set_field_attributes(field_hdl      = temp_mod__,   &
92                                ftype          = EFIELD,       &
93                                prec_          = 4,            &
94                                operation_     = "once",       &
95                                enabled_       = .FALSE._1,    &
96                                name_          = "champ2",     &
97                                standard_name_ = "lechamp2",   &
98                                long_name_     = "le champ 2", &
99                                domain_ref_    = "simple_domaine1")
100
101      CALL xml_tree_add(parent_hdl  = temp_mod,        &
102                        parent_type = GFIELD,          &
103                        child_hdl   = temp_mod__,      &
104                        child_type  = EFIELD,          &
105                        child_id    = "champ_3D_k4_once")
106
107      CALL set_field_attributes(field_hdl      = temp_mod__,   &
108                                ftype          = EFIELD,       &
109                                prec_          = 4,            &
110                                operation_     = "once",       &
111                                name_          = "champ3",     &
112                                standard_name_ = "lechamp3",   &
113                                long_name_     = "le champ 3", &
114                                grid_ref_   = "simple_grille")
115
116      CALL xml_tree_add(parent_hdl  = temp_mod,        &
117                        parent_type = GFIELD,          &
118                        child_hdl   = temp_mod__,      &
119                        child_type  = EFIELD,          &
120                        child_id    = "champ_3D_k8_average")
121
122      CALL set_field_attributes(field_hdl      = temp_mod__,   &
123                                ftype          = EFIELD,       &
124                                prec_          = 8,            &
125                                operation_     = "average",    &
126                                name_          = "champ4",     &
127                                standard_name_ = "lechamp4",   &
128                                long_name_     = "le champ 4", &
129                                grid_ref_   = "simple_grille")
130
131      CALL xml_tree_add(parent_hdl  = temp_mod_,       &
132                        parent_type = GFIELD,          &
133                        child_hdl   = temp_mod,        &
134                        child_type  = GFIELD,          &
135                        child_id    = "field_disabled")
136
137      CALL set_field_attributes(field_hdl  = temp_mod,  &
138                                ftype          = GFIELD,    &
139                                operation_     = "instant", &
140                                enabled_   = .FALSE._1)
141
142      CALL xml_tree_add(parent_hdl  = temp_mod,        &
143                        parent_type = GFIELD,          &
144                        child_hdl   = temp_mod__,      &
145                        child_type  = EFIELD,          &
146                        child_id    = "champ_3D_k8_inst")
147
148      CALL set_field_attributes(field_hdl      = temp_mod__,       &
149                                ftype          = EFIELD,           &
150                                prec_          = 8,                &
151                                name_          = "champ5",         &
152                                standard_name_ = "lechamp5",       &
153                                long_name_     = "le champ 5",     &
154                                domain_ref_    = "simple_domaine", &
155                                axis_ref_      = "simple_axe")
156
157      ! ---------> axis_definition
158      CALL handle_create(temp_mod, GAXIS,  "axis_definition")
159      CALL xml_tree_add(parent_hdl  = temp_mod,   &
160                        parent_type = GAXIS,      &
161                        child_hdl   = temp_mod_,  &
162                        child_type  = GAXIS,      &
163                        child_id    = "all_axis")
164
165      CALL set_axis_attributes(axis_hdl = temp_mod_, &
166                               ftype    = GAXIS,     &
167                               unit_    = "km")
168
169      CALL xml_tree_add(parent_hdl     = temp_mod_,       &
170                        parent_type    = GAXIS,           &
171                        child_hdl      = temp_mod,        &
172                        child_type     = EAXIS,           &
173                        child_id       = "simple_axe")
174
175      CALL set_axis_attributes(axis_hdl       = temp_mod, &
176                               ftype          = EAXIS,    &
177                               name_          = "axe1",   &
178                               standard_name_ = "laxe1",  &
179                               long_name_     = "l axe1", &
180                               size_          = 30,       &
181                               zvalue_        = real_array(1:30))
182
183      ! ---------> domain_definition
184      CALL handle_create(temp_mod, GDOMAIN,  "domain_definition")
185      CALL xml_tree_add(parent_hdl  = temp_mod,   &
186                        parent_type = GDOMAIN,    &
187                        child_hdl   = temp_mod_,  &
188                        child_type  = GDOMAIN,    &
189                        child_id    = "all_domain")
190
191      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
192                        parent_type = GDOMAIN,    &
193                        child_hdl   = temp_mod,   &
194                        child_type  = EDOMAIN,    &
195                        child_id    = "simple_domaine0")
196
197      IF (rankGrp .EQ. 0) THEN
198         ibegin = 1
199         iend   = 50
200         jbegin = 1
201         jend   = 50
202      ELSE IF (rankGrp .EQ. 1) THEN
203         ibegin = 51
204         iend   = 100
205         jbegin = 1
206         jend   = 50
207      END IF
208
209      CALL set_domain_attributes(domain_hdl     = temp_mod,       &
210                                 ftype          = EDOMAIN,        &
211                                 name_          = "domaine0",     &
212                                 standard_name_ = "ledomaine0",   &
213                                 long_name_     = "le domaine 0", &
214                                 lonvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), &
215                                 latvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), &
216                                 data_dim_      = 2,              &
217                                 ni_glo_        = 100,            &
218                                 nj_glo_        = 50,             &
219                                 ibegin_        = ibegin,         &
220                                 iend_          = iend,           &
221                                 jbegin_        = jbegin,         &
222                                 jend_          = jend)
223
224      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
225                        parent_type = GDOMAIN,    &
226                        child_hdl   = temp_mod,   &
227                        child_type  = EDOMAIN,    &
228                        child_id    = "simple_domaine1")
229
230      IF (rankGrp .EQ. 0) THEN
231         ibegin = 1
232         iend   = 90
233         jbegin = 1
234         jend   = 10
235      ELSE IF (rankGrp .EQ. 1) THEN
236         ibegin = 1
237         iend   = 90
238         jbegin = 11
239         jend   = 20
240      END IF
241
242      CALL set_domain_attributes(domain_hdl     = temp_mod,       &
243                                 ftype          = EDOMAIN,        &
244                                 name_          = "domaine1",     &
245                                 standard_name_ = "ledomaine0",   &
246                                 long_name_     = "le domaine 1", &
247                                 lonvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), &
248                                 latvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), &
249                                 data_dim_      = 2,              &
250                                 ni_glo_        = 90,             &
251                                 nj_glo_        = 40,             &
252                                 ibegin_        = ibegin,         &
253                                 iend_          = iend,           &
254                                 jbegin_        = jbegin,         &
255                                 jend_          = jend)
256
257      ! ---------> grid_definition
258      CALL handle_create(temp_mod, GGRID, "grid_definition")
259      CALL xml_tree_add(parent_hdl  = temp_mod,   &
260                        parent_type = GGRID,      &
261                        child_hdl   = temp_mod_,  &
262                        child_type  = EGRID,      &
263                        child_id    = "simple_grille")
264
265      CALL set_grid_attributes(grid_hdl     = temp_mod_,         &
266                               ftype        = EGRID,             &
267                               name_        = "grille1",         &
268                               description_ = "la grille 1",     &
269                               domain_ref_  = "simple_domaine1", &
270                               axis_ref_    = "simple_axe")
271
272      ! ---------> file_definition
273      CALL handle_create(temp_mod, GFILE, "file_definition")
274
275      CALL xml_tree_add(parent_hdl  = temp_mod,   &
276                        parent_type = GFILE,      &
277                        child_hdl   = temp_mod_,  &
278                        child_type  = EFILE,      &
279                        child_id    = "simple_fichier1")
280
281      CALL set_file_attributes(file_hdl      = temp_mod_,        &
282                               ftype         = EFILE,            &
283                               name_         = "fichier1",       &
284                               description_  = "mon fichier 1 ", &
285                               output_freq_  = "12h",            &
286                               output_level_ = 3,                &
287                               enabled_      =  .TRUE._1)
288
289      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
290                        parent_type = EFILE,      &
291                        child_hdl   = temp_mod__, &
292                        child_type  = EFIELD)
293
294      CALL set_field_attributes(field_hdl      = temp_mod__,       &
295                                ftype          = EFIELD,           &
296                                field_ref_     = "champ_2D_k8_inst")
297
298      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
299                        parent_type = EFILE,      &
300                        child_hdl   = temp_mod__, &
301                        child_type  = EFIELD)
302
303      CALL set_field_attributes(field_hdl      = temp_mod__,       &
304                                ftype          = EFIELD,           &
305                                field_ref_     = "champ_2D_k4_once_dis")
306
307      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
308                        parent_type = EFILE,      &
309                        child_hdl   = temp_mod__, &
310                        child_type  = EFIELD)
311
312      CALL set_field_attributes(field_hdl      = temp_mod__,       &
313                                ftype          = EFIELD,           &
314                                field_ref_     = "champ_3D_k4_once")
315
316      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
317                        parent_type = EFILE,      &
318                        child_hdl   = temp_mod__, &
319                        child_type  = EFIELD)
320
321      CALL set_field_attributes(field_hdl      = temp_mod__,       &
322                                ftype          = EFIELD,           &
323                                field_ref_     = "champ_3D_k8_average")
324
325      CALL xml_tree_add(parent_hdl  = temp_mod,   &
326                        parent_type = GFILE,      &
327                        child_hdl   = temp_mod_,  &
328                        child_type  = EFILE,      &
329                        child_id    = "simple_fichier2")
330
331      CALL set_file_attributes(file_hdl      = temp_mod_,        &
332                               ftype         = EFILE,            &
333                               name_         = "fichier2",       &
334                               description_  = "mon fichier 2 ", &
335                               output_freq_  = "1d",             &
336                               output_level_ = 3,                &
337                               enabled_      =  .TRUE._1)
338
339      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
340                        parent_type = EFILE,      &
341                        child_hdl   = temp_mod__, &
342                        child_type  = EFIELD)
343
344      CALL set_field_attributes(field_hdl      = temp_mod__,       &
345                                ftype          = EFIELD,           &
346                                field_ref_     = "champ_2D_k8_inst")
347
348      CALL xml_tree_add(parent_hdl  = temp_mod,   &
349                        parent_type = GFILE,      &
350                        child_hdl   = temp_mod_,  &
351                        child_type  = EFILE,      &
352                        child_id    = "simple_fichier3")
353
354      CALL set_file_attributes(file_hdl      = temp_mod_,        &
355                               ftype         = EFILE,            &
356                               name_         = "fichier3",       &
357                               description_  = "mon fichier 3 ", &
358                               output_freq_  = "18h",            &
359                               output_level_ = 5,                &
360                               enabled_      =  .FALSE._1)
361
362      CALL xml_tree_add(parent_hdl  = temp_mod_,  &
363                        parent_type = EFILE,      &
364                        child_hdl   = temp_mod__, &
365                        child_type  = EFIELD)
366
367      CALL set_field_attributes(field_hdl      = temp_mod__,       &
368                                ftype          = EFIELD,           &
369                                field_ref_     = "champ_2D_k8_inst")
370
371      !!!!!!!!!!!!!!!!!!!!!!! Début du traitement !!!!!!!!!!!!!!!!!!!!!
372
373      ! On choisit le context dans lequel on va travailler
374      ! et on commence le traitement des données.
375      CALL dtreatment_start(nemo_style_ctxt, NETCDF4)
376
377   END SUBROUTINE NEMO_FAKE_ENTRY
378
379   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
380
381END MODULE NEMO_FAKE
Note: See TracBrowser for help on using the repository browser.