]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_transformations/cic2Xml.ml
b3467ad9e013ae0b378f7ba081883d6d1c938200
[helm.git] / helm / ocaml / cic_transformations / cic2Xml.ml
1 (* Copyright (C) 2000-2004, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 (*CSC codice cut & paste da cicPp e xmlcommand *)
27
28 exception ImpossiblePossible;;
29 exception NotImplemented;;
30
31 let dtdname ~ask_dtd_to_the_getter dtd =
32  if ask_dtd_to_the_getter then
33   Helm_registry.get "getter.url" ^ "getdtd?uri=" ^ dtd
34  else
35   "http://mowgli.cs.unibo.it/dtd/" ^ dtd
36 ;;
37
38 let param_attribute_of_params params =
39  String.concat " " (List.map UriManager.string_of_uri params)
40 ;;
41
42 (*CSC ottimizzazione: al posto di curi cdepth (vedi codice) *)
43 let print_term ~ids_to_inner_sorts =
44  let rec aux =
45   let module C = Cic in
46   let module X = Xml in
47   let module U = UriManager in
48     function
49        C.ARel (id,idref,n,b) ->
50         let sort = Hashtbl.find ids_to_inner_sorts id in
51          X.xml_empty "REL"
52           [None,"value",(string_of_int n) ; None,"binder",b ; None,"id",id ;
53            None,"idref",idref ; None,"sort",sort]
54      | C.AVar (id,uri,exp_named_subst) ->
55         let sort = Hashtbl.find ids_to_inner_sorts id in
56          aux_subst uri
57           (X.xml_empty "VAR"
58             [None,"uri",U.string_of_uri uri;None,"id",id;None,"sort",sort])
59           exp_named_subst
60      | C.AMeta (id,n,l) ->
61         let sort = Hashtbl.find ids_to_inner_sorts id in
62          X.xml_nempty "META"
63           [None,"no",(string_of_int n) ; None,"id",id ; None,"sort",sort]
64           (List.fold_left
65             (fun i t ->
66               match t with
67                  Some t' ->
68                   [< i ; X.xml_nempty "substitution" [] (aux t') >]
69                | None ->
70                   [< i ; X.xml_empty "substitution" [] >]
71             ) [< >] l)
72      | C.ASort (id,s) ->
73         let string_of_sort =
74          function
75             C.Prop  -> "Prop"
76           | C.Set   -> "Set"
77           | C.Type _ -> "Type" (* TASSI *)
78           | C.CProp -> "CProp"
79         in
80          X.xml_empty "SORT" [None,"value",(string_of_sort s) ; None,"id",id]
81      | C.AImplicit _ -> raise NotImplemented
82      | C.AProd (last_id,_,_,_) as prods ->
83         let rec eat_prods =
84          function
85             C.AProd (id,n,s,t) ->
86              let prods,t' = eat_prods t in
87               (id,n,s)::prods,t'
88           | t -> [],t
89         in
90          let prods,t = eat_prods prods in
91           let sort = Hashtbl.find ids_to_inner_sorts last_id in
92            X.xml_nempty "PROD" [None,"type",sort]
93             [< List.fold_left
94                 (fun i (id,binder,s) ->
95                   let sort =
96                    Hashtbl.find ids_to_inner_sorts (Cic2acic.source_id_of_id id)
97                   in
98                    let attrs =
99                     (None,"id",id)::(None,"type",sort)::
100                     match binder with
101                        C.Anonymous -> []
102                      | C.Name b -> [None,"binder",b]
103                    in
104                     [< i ; X.xml_nempty "decl" attrs (aux s) >]
105                 ) [< >] prods ;
106                X.xml_nempty "target" [] (aux t)
107             >]
108      | C.ACast (id,v,t) ->
109         let sort = Hashtbl.find ids_to_inner_sorts id in
110          X.xml_nempty "CAST" [None,"id",id ; None,"sort",sort]
111           [< X.xml_nempty "term" [] (aux v) ;
112              X.xml_nempty "type" [] (aux t)
113           >]
114      | C.ALambda (last_id,_,_,_) as lambdas ->
115         let rec eat_lambdas =
116          function
117             C.ALambda (id,n,s,t) ->
118              let lambdas,t' = eat_lambdas t in
119               (id,n,s)::lambdas,t'
120           | t -> [],t
121         in
122          let lambdas,t = eat_lambdas lambdas in
123           let sort = Hashtbl.find ids_to_inner_sorts last_id in
124            X.xml_nempty "LAMBDA" [None,"sort",sort]
125             [< List.fold_left
126                 (fun i (id,binder,s) ->
127                   let sort =
128                    Hashtbl.find ids_to_inner_sorts (Cic2acic.source_id_of_id id)
129                   in
130                    let attrs =
131                     (None,"id",id)::(None,"type",sort)::
132                     match binder with
133                        C.Anonymous -> []
134                      | C.Name b -> [None,"binder",b]
135                    in
136                     [< i ; X.xml_nempty "decl" attrs (aux s) >]
137                 ) [< >] lambdas ;
138                X.xml_nempty "target" [] (aux t)
139             >]
140      | C.ALetIn (xid,C.Anonymous,s,t) ->
141        assert false
142      | C.ALetIn (last_id,C.Name _,_,_) as letins ->
143         let rec eat_letins =
144          function
145             C.ALetIn (id,n,s,t) ->
146              let letins,t' = eat_letins t in
147               (id,n,s)::letins,t'
148           | t -> [],t
149         in
150          let letins,t = eat_letins letins in
151           let sort = Hashtbl.find ids_to_inner_sorts last_id in
152            X.xml_nempty "LETIN" [None,"sort",sort]
153             [< List.fold_left
154                 (fun i (id,binder,s) ->
155                   let sort = Hashtbl.find ids_to_inner_sorts id in
156                    let attrs =
157                     (None,"id",id)::(None,"sort",sort)::
158                     match binder with
159                        C.Anonymous -> []
160                      | C.Name b -> [None,"binder",b]
161                    in
162                     [< i ; X.xml_nempty "def" attrs (aux s) >]
163                 ) [< >] letins ;
164                X.xml_nempty "target" [] (aux t)
165             >]
166      | C.AAppl (id,li) ->
167         let sort = Hashtbl.find ids_to_inner_sorts id in
168          X.xml_nempty "APPLY" [None,"id",id ; None,"sort",sort]
169           [< (List.fold_right (fun x i -> [< (aux x) ; i >]) li [<>])
170           >]
171      | C.AConst (id,uri,exp_named_subst) ->
172         let sort = Hashtbl.find ids_to_inner_sorts id in
173          aux_subst uri
174           (X.xml_empty "CONST"
175             [None,"uri",(U.string_of_uri uri) ; None,"id",id ; None,"sort",sort]
176           ) exp_named_subst
177      | C.AMutInd (id,uri,i,exp_named_subst) ->
178         aux_subst uri
179          (X.xml_empty "MUTIND"
180            [None, "uri", (U.string_of_uri uri) ;
181             None, "noType", (string_of_int i) ;
182             None, "id", id]
183          ) exp_named_subst
184      | C.AMutConstruct (id,uri,i,j,exp_named_subst) ->
185         let sort = Hashtbl.find ids_to_inner_sorts id in
186          aux_subst uri
187           (X.xml_empty "MUTCONSTRUCT"
188             [None,"uri", (U.string_of_uri uri) ;
189              None,"noType",(string_of_int i) ;
190              None,"noConstr",(string_of_int j) ;
191              None,"id",id ; None,"sort",sort]
192           ) exp_named_subst
193      | C.AMutCase (id,uri,typeno,ty,te,patterns) ->
194         let sort = Hashtbl.find ids_to_inner_sorts id in
195          X.xml_nempty "MUTCASE"
196           [None,"uriType",(U.string_of_uri uri) ;
197            None,"noType", (string_of_int typeno) ;
198            None,"id", id ; None,"sort",sort]
199           [< X.xml_nempty "patternsType" [] [< (aux ty) >] ;
200              X.xml_nempty "inductiveTerm" [] [< (aux te) >] ;
201              List.fold_right
202               (fun x i -> [< X.xml_nempty "pattern" [] [< aux x >] ; i>])
203               patterns [<>]
204           >]
205      | C.AFix (id, no, funs) ->
206         let sort = Hashtbl.find ids_to_inner_sorts id in
207          X.xml_nempty "FIX"
208           [None,"noFun", (string_of_int no) ; None,"id",id ; None,"sort",sort]
209           [< List.fold_right
210               (fun (id,fi,ai,ti,bi) i ->
211                 [< X.xml_nempty "FixFunction"
212                     [None,"id",id ; None,"name", fi ;
213                      None,"recIndex", (string_of_int ai)]
214                     [< X.xml_nempty "type" [] [< aux ti >] ;
215                        X.xml_nempty "body" [] [< aux bi >]
216                     >] ;
217                    i
218                 >]
219               ) funs [<>]
220           >]
221      | C.ACoFix (id,no,funs) ->
222         let sort = Hashtbl.find ids_to_inner_sorts id in
223          X.xml_nempty "COFIX"
224           [None,"noFun", (string_of_int no) ; None,"id",id ; None,"sort",sort]
225           [< List.fold_right
226               (fun (id,fi,ti,bi) i ->
227                 [< X.xml_nempty "CofixFunction" [None,"id",id ; None,"name", fi]
228                     [< X.xml_nempty "type" [] [< aux ti >] ;
229                        X.xml_nempty "body" [] [< aux bi >]
230                     >] ;
231                    i
232                 >]
233               ) funs [<>]
234           >]
235  and aux_subst buri target subst =
236 (*CSC: I have now no way to assign an ID to the explicit named substitution *)
237   let id = None in
238    if subst = [] then
239     target
240    else
241     Xml.xml_nempty "instantiate"
242      (match id with None -> [] | Some id -> [None,"id",id])
243      [< target ;
244         List.fold_left
245          (fun i (uri,arg) ->
246            let relUri =
247             let buri_frags =
248              Str.split (Str.regexp "/") (UriManager.string_of_uri buri) in
249             let uri_frags = 
250              Str.split (Str.regexp "/") (UriManager.string_of_uri uri)  in
251              let rec find_relUri buri_frags uri_frags =
252               match buri_frags,uri_frags with
253                  [_], _ -> String.concat "/" uri_frags
254                | he1::tl1, he2::tl2 ->
255                   assert (he1 = he2) ;
256                   find_relUri tl1 tl2
257                | _,_ -> assert false (* uri is not relative to buri *)
258              in
259               find_relUri buri_frags uri_frags
260            in
261             [< i ; Xml.xml_nempty "arg" [None,"relUri", relUri] (aux arg) >]
262          ) [<>] subst
263      >]
264   in
265    aux
266 ;;
267
268 let print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter obj =
269  let module C = Cic in
270  let module X = Xml in
271  let module U = UriManager in
272   let dtdname = dtdname ~ask_dtd_to_the_getter "cic.dtd" in
273    match obj with
274        C.ACurrentProof (id,idbody,n,conjectures,bo,ty,params) ->
275         let params' = param_attribute_of_params params in
276         let xml_for_current_proof_body =
277 (*CSC: Should the CurrentProof also have the list of variables it depends on? *)
278 (*CSC: I think so. Not implemented yet.                                       *)
279          X.xml_nempty "CurrentProof"
280           [None,"of",UriManager.string_of_uri uri ; None,"id", id]
281           [< List.fold_left
282               (fun i (cid,n,canonical_context,t) ->
283                 [< i ;
284                    X.xml_nempty "Conjecture"
285                     [None,"id",cid ; None,"no",(string_of_int n)]
286                     [< List.fold_left
287                         (fun i (hid,t) ->
288                           [< (match t with
289                                  Some (n,C.ADecl t) ->
290                                   X.xml_nempty "Decl"
291                                    (match n with
292                                        C.Name n' ->
293                                         [None,"id",hid;None,"name",n']
294                                      | C.Anonymous -> [None,"id",hid])
295                                    (print_term ids_to_inner_sorts t)
296                                | Some (n,C.ADef t) ->
297                                   X.xml_nempty "Def"
298                                    (match n with
299                                        C.Name n' ->
300                                         [None,"id",hid;None,"name",n']
301                                      | C.Anonymous -> [None,"id",hid])
302                                    (print_term ids_to_inner_sorts t)
303                               | None -> X.xml_empty "Hidden" [None,"id",hid]
304                              ) ;
305                              i
306                           >]
307                         ) [< >] canonical_context ;
308                        X.xml_nempty "Goal" []
309                         (print_term ids_to_inner_sorts t)
310                     >]
311                 >])
312               [<>] conjectures ;
313              X.xml_nempty "body" [] (print_term ids_to_inner_sorts bo) >]
314         in
315         let xml_for_current_proof_type =
316          X.xml_nempty "ConstantType"
317           [None,"name",n ; None,"params",params' ; None,"id", id]
318           (print_term ids_to_inner_sorts ty)
319         in
320         let xmlbo =
321          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
322             X.xml_cdata ("<!DOCTYPE CurrentProof SYSTEM \""^ dtdname ^ "\">\n");
323             xml_for_current_proof_body
324          >] in
325         let xmlty =
326          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
327             X.xml_cdata ("<!DOCTYPE ConstantType SYSTEM \""^ dtdname ^ "\">\n");
328             xml_for_current_proof_type
329          >]
330         in
331          xmlty, Some xmlbo
332      | C.AConstant (id,idbody,n,bo,ty,params) ->
333         let params' = param_attribute_of_params params in
334         let xmlbo =
335          match bo with
336             None -> None
337           | Some bo ->
338              Some
339               [< X.xml_cdata
340                   "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
341                  X.xml_cdata
342                   ("<!DOCTYPE ConstantBody SYSTEM \"" ^ dtdname ^ "\">\n") ;
343                  X.xml_nempty "ConstantBody"
344                   [None,"for",UriManager.string_of_uri uri ;
345                    None,"params",params' ; None,"id", id]
346                   [< print_term ids_to_inner_sorts bo >]
347               >]
348         in
349         let xmlty =
350          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
351             X.xml_cdata ("<!DOCTYPE ConstantType SYSTEM \""^ dtdname ^ "\">\n");
352              X.xml_nempty "ConstantType"
353               [None,"name",n ; None,"params",params' ; None,"id", id]
354               [< print_term ids_to_inner_sorts ty >]
355          >]
356         in
357          xmlty, xmlbo
358      | C.AVariable (id,n,bo,ty,params) ->
359         let params' = param_attribute_of_params params in
360         let xmlbo =
361          match bo with
362             None -> [< >]
363           | Some bo ->
364              X.xml_nempty "body" [] [< print_term ids_to_inner_sorts bo >]
365         in
366         let aobj =
367          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
368             X.xml_cdata ("<!DOCTYPE Variable SYSTEM \"" ^ dtdname ^ "\">\n");
369              X.xml_nempty "Variable"
370               [None,"name",n ; None,"params",params' ; None,"id", id]
371               [< xmlbo ;
372                  X.xml_nempty "type" [] (print_term ids_to_inner_sorts ty)
373               >]
374          >]
375         in
376          aobj, None
377      | C.AInductiveDefinition (id,tys,params,nparams) ->
378         let params' = param_attribute_of_params params in
379          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
380             X.xml_cdata
381              ("<!DOCTYPE InductiveDefinition SYSTEM \"" ^ dtdname ^ "\">\n") ;
382             X.xml_nempty "InductiveDefinition"
383              [None,"noParams",string_of_int nparams ;
384               None,"id",id ;
385               None,"params",params']
386              [< (List.fold_left
387                   (fun i (id,typename,finite,arity,cons) ->
388                     [< i ;
389                        X.xml_nempty "InductiveType"
390                         [None,"id",id ; None,"name",typename ;
391                          None,"inductive",(string_of_bool finite)
392                         ]
393                         [< X.xml_nempty "arity" []
394                             (print_term ids_to_inner_sorts arity) ;
395                            (List.fold_left
396                             (fun i (name,lc) ->
397                               [< i ;
398                                  X.xml_nempty "Constructor"
399                                   [None,"name",name]
400                                   (print_term ids_to_inner_sorts lc)
401                               >]) [<>] cons
402                            )
403                         >]
404                     >]
405                   ) [< >] tys
406                 )
407              >]
408          >], None
409 ;;
410
411 let
412  print_inner_types curi ~ids_to_inner_sorts ~ids_to_inner_types
413   ~ask_dtd_to_the_getter
414 =
415  let module C2A = Cic2acic in
416  let module X = Xml in
417   let dtdname = dtdname ~ask_dtd_to_the_getter "cictypes.dtd" in
418    [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
419       X.xml_cdata
420        ("<!DOCTYPE InnerTypes SYSTEM \"" ^ dtdname ^ "\">\n") ;
421       X.xml_nempty "InnerTypes" [None,"of",UriManager.string_of_uri curi]
422        (Hashtbl.fold
423          (fun id {C2A.annsynthesized = synty ; C2A.annexpected = expty} x ->
424            [< x ;
425               X.xml_nempty "TYPE" [None,"of",id]
426                [< X.xml_nempty "synthesized" []
427                  [< print_term ids_to_inner_sorts synty >] ;
428                  match expty with
429                    None -> [<>]
430                  | Some expty' -> X.xml_nempty "expected" [] [< print_term ids_to_inner_sorts expty' >]
431                >]
432            >]
433          ) ids_to_inner_types [<>]
434        )
435    >]
436 ;;