source: XMLIO_V2/dev/dev_rv/src/XMLIO/main.f90 @ 138

Last change on this file since 138 was 138, checked in by hozdoba, 14 years ago

Mise à jour

File size: 10.5 KB
Line 
1! --------------------------------------------------- !
2!               XMLIO SERVER MAIN TEST                !
3! --------------------------------------------------- !
4
5PROGRAM MAIN
6
7   USE IXHANDLE
8   USE IXML
9   USE IXMLTREE
10   USE ICONTEXT
11   USE ICALENDAR
12   USE IEXTENDED
13   USE IDATATREATMENT
14
15   INTEGER       :: compt = 0
16   TYPE(XHandle) :: nemo_style_ctxt     = NULLHANDLE, &
17                    orchidee_style_ctxt = NULLHANDLE, &
18                    lmdz_style_ctxt     = NULLHANDLE
19   TYPE(XHandle) :: temp_mod  = NULLHANDLE, &
20                    temp_mod_ = NULLHANDLE
21   ! Les axes verticaux
22   REAL(kind = 8), DIMENSION(10) :: vaxis  = (/(i, i=1, 10)/)
23                                    !vvaxis = (/(i, i=1, 5)/)
24   ! Les domaines horizontaux
25   REAL(kind = 8), DIMENSION(20)    :: lonrect_orch0  = (/(i, i=11, 30)/),&
26                                       latrect_orch0  = (/(i, i=11, 30)/)
27   REAL(kind = 8), DIMENSION(10,10) :: loncurv_nemo0  = 1, &
28                                       latcurv_nemo0  = 1
29   ! Les durées
30   TYPE(XDuration) :: timestep_1h = XDuration(0., 0., 0., 1., 0., 0.)
31                      !timestep_2h = XDuration(0., 0., 0., 2., 0., 0.)
32   ! Les dates
33   TYPE(XDate) :: init_date_orchidee = XDate(1985, 03, 15, 17, 35, 00)
34   ! Les masques
35   LOGICAL(kind = 1), DIMENSION(20, 20) :: mask0  = .TRUE._1
36
37   ! Les données
38   REAL(kind = 8), DIMENSION(400, 10)    :: orchdata  = 2.0
39   REAL(kind = 8), DIMENSION(10, 10, 20) :: nemodata  = 3.0
40
41   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
42
43   ! Parsing du document xml depuis un fichier situé sur le disque.
44   CALL xml_Parse_File("/local/XMLIOSERVER_DEV/dev_rv/test/iodef_simple_test.xml")
45
46   ! Création de handle sur les contextes exstants dans lequels on souhaite travailler.
47   CALL handle_create(nemo_style_ctxt, ECONTEXT, "nemo_style")
48   CALL context_set_current(nemo_style_ctxt)
49
50   CALL handle_create(temp_mod, EDOMAIN,  "domaine0")
51      CALL xml_domain_addAttribut(domain_hdl    = temp_mod,      &
52                                  lonvalue_curv = loncurv_nemo0, &
53                                  latvalue_curv = latcurv_nemo0, &
54                                  domtype       = "curvilinear")
55
56   CALL handle_create(lmdz_style_ctxt, ECONTEXT, "lmdz_style")
57   CALL context_set_current(lmdz_style_ctxt)
58
59   !!!!!!!!!!!!!!!!!!!! EXEMPLE RECONSTRUCTION !!!!!!!!!!!!!!!!!!!!!
60   ! On crée un nouveau context et on lui associe un handle.
61   CALL context_create(context_hdl   = orchidee_style_ctxt, &
62                       context_id    = "orchidee_style",    &
63                       calendar_type = GREGORIAN,           &
64                       init_date     = init_date_orchidee)
65
66   ! ---------> field_definition
67   CALL handle_create(temp_mod, GFIELD,  "field_definition")
68      CALL xml_tree_add(parent_hdl = temp_mod,        &
69                        child_hdl  = temp_mod_,       &
70                        child_type = GFIELD,          &
71                        child_id   = "ss_fieldgroup")
72      CALL xml_group_field_addAttribut(gfield_hdl = temp_mod_, &
73                                       flevel     = 1,         &
74                                       fprec      = 4,         &
75                                       fenabled   = .TRUE._1)
76         CALL xml_tree_add(parent_hdl = temp_mod_,    &
77                           child_hdl  = temp_mod ,    &
78                           child_type = EFIELD,       &
79                           child_id   = "field0")
80         CALL xml_field_addAttribut(field_hdl      = temp_mod,       &
81                                    fname          = "field0_name",  &
82                                    fstandard_name = "field0_sname", &
83                                    flong_name     = "field0_lname", &
84                                    funit          = "Pa",           &
85                                    foperation     = "inst",         &
86                                    ffreq_op       = timestep_1h,    &
87                                    fgrid_ref      = "grid0")
88
89   ! ---------> axis_definition
90   CALL handle_create(temp_mod, GAXIS,   "axis_definition")
91      CALL xml_tree_add(parent_hdl = temp_mod,        &
92                        child_hdl  = temp_mod_,       &
93                        child_type = GAXIS,           &
94                        child_id   = "ss_axisgroup")
95      CALL xml_group_axis_addAttribut(gaxis_hdl = temp_mod_, &
96                                      aunit     = "SI")
97         CALL xml_tree_add(parent_hdl = temp_mod_,    &
98                           child_hdl  = temp_mod ,    &
99                           child_type = EAXIS,        &
100                           child_id   = "axis0")
101         CALL xml_axis_addAttribut(axis_hdl       = temp_mod,             &
102                                   aname          = "saxev",              &
103                                   astandard_name = "saxev",              &
104                                   along_name     = "Simple axe vertical",&
105                                   avalue         = vaxis)
106
107   ! ---------> domain_definition
108   CALL handle_create(temp_mod, GDOMAIN, "domain_definition")
109      CALL xml_tree_add(parent_hdl = temp_mod,        &
110                        child_hdl  = temp_mod_,       &
111                        child_type = GDOMAIN,         &
112                        child_id   = "ss_domaingroup")
113      CALL xml_group_domain_addAttribut(gdomain_hdl = temp_mod_, &
114                                        ni_glo      = 40,        &
115                                        nj_glo      = 40)
116         CALL xml_tree_add(parent_hdl = temp_mod_,    &
117                           child_hdl  = temp_mod ,    &
118                           child_type = EDOMAIN,      &
119                           child_id   = "domain0")
120         CALL xml_domain_addAttribut(domain_hdl     = temp_mod,             &
121                                     dname          = "Compressee",         &
122                                     dstandard_name = "DomOrchTest",        &
123                                     dlong_name     = "Test type orchidee", &
124                                     ibegin         = 10,                   &
125                                     iend           = 31,                   &
126                                     jbegin         = 10,                   &
127                                     jend           = 31,                   &
128                                     mask           = mask0,                &
129                                     data_dim       = 1,                    &
130                                     data_ni        = 400,                  &
131                                     data_ibegin    = 1,                    &
132                                     lonvalue_rect  = lonrect_orch0,        &
133                                     latvalue_rect  = latrect_orch0,        &
134                                     domtype        = "rectilinear")
135
136   ! ---------> file_definition
137   CALL handle_create(temp_mod, GFILE,   "file_definition")
138      CALL xml_tree_add(parent_hdl = temp_mod,        &
139                        child_hdl  = temp_mod_,       &
140                        child_type = GFILE)
141      CALL xml_group_file_addAttribut(gfile_hdl = temp_mod_,   &
142                                      fofreq   = timestep_1h,  &
143                                      folevel   = 2,           &
144                                      fenabled  = .TRUE._1)
145         CALL xml_tree_add(parent_hdl = temp_mod_,    &
146                           child_hdl  = temp_mod ,    &
147                           child_type = EFILE,        &
148                           child_id   = "file0")
149         CALL xml_file_addAttribut(file_hdl     = temp_mod,                      &
150                                   fname        = "data/orchidee_test.nc",       &
151                                   fdescription = "Test sur grille type orchidee")
152            CALL xml_tree_add(parent_hdl = temp_mod , &
153                              child_hdl  = temp_mod_, &
154                              child_type = EFIELD)
155            CALL xml_field_addAttribut(field_hdl  = temp_mod_, &
156                                       ffield_ref = "field0")
157
158   ! ---------> grid_définition
159   CALL handle_create(temp_mod, GGRID,   "grid_definition")
160      CALL xml_tree_add(parent_hdl = temp_mod,        &
161                        child_hdl  = temp_mod_,       &
162                        child_type = GGRID,           &
163                        child_id   = "ss_gridgroup")
164      CALL xml_group_grid_addAttribut(ggrid_hdl    = temp_mod_, &
165                                      gdomain_ref  = "domain0", &
166                                      gaxis_ref    = "axis0");
167         CALL xml_tree_add(parent_hdl = temp_mod_,    &
168                           child_hdl  = temp_mod ,    &
169                           child_type = EGRID,        &
170                           child_id   = "grid0")
171         CALL xml_grid_addAttribut(grid_hdl     = temp_mod,           &
172                                   gname        = "GRectiCompressee", &
173                                   gdescription = "Grille orchidee");
174
175   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
176
177   ! Affichage de l'arbre xml au niveau de la sortie.
178   CALL xml_tree_show("xmlio_tree_prev.log")
179   ! CALL xml_tree_show()
180
181   ! ----------- Début du traitement ----------- !
182
183   ! <<<------------- orchidée
184   PRINT *, "Style Orchydée"
185   ! On choisit le context dans lequel on va travailler
186   ! et on commence le traitement des données.
187   CALL dtreatment_start(orchidee_style_ctxt, NETCDF4)
188   CALL set_timestep(XDuration(0., 0., 0., 1., 0., 0.)) ! UNE heure
189
190   ! Exécution de la boucle de calcul-écriture.
191   DO compt = 1, 9
192      CALL update_calendar(compt)
193         CALL write_data("field0", data2d_k8 = orchdata)
194   END DO
195   CALL dtreatment_end(orchidee_style_ctxt)
196
197   ! <<<------------- lmdz
198   PRINT *, "Style Lmdz"
199   CALL dtreatment_start(lmdz_style_ctxt, NETCDF4)
200   CALL set_timestep(XDuration(0., 0., 0., 1., 0., 0.)) ! UNE heure
201
202   ! Exécution de la boucle de calcul-écriture.
203   DO compt = 1, 9
204      CALL update_calendar(compt)
205
206   END DO
207   CALL dtreatment_end(lmdz_style_ctxt)
208
209   ! <<<------------- nemo
210   PRINT *, "Style Nemo"
211   CALL dtreatment_start(nemo_style_ctxt, NETCDF4)
212   CALL set_timestep(XDuration(0., 0., 0., 1., 0., 0.)) ! UNE heure
213
214   ! Exécution de la boucle de calcul-écriture.
215   DO compt = 1, 9
216      CALL update_calendar(compt)
217      CALL write_data("champ0",  data3d_k8 = nemodata)
218   END DO
219   CALL dtreatment_end(nemo_style_ctxt)
220
221   ! Affichage de l'arbre xml au niveau de la sortie.
222   CALL xml_tree_show("xmlio_tree_next.log")
223
224END PROGRAM MAIN
Note: See TracBrowser for help on using the repository browser.