]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/cic2Xml.ml
* update (ask claudio for details)
[helm.git] / helm / gTopLevel / cic2Xml.ml
1 (* Copyright (C) 2000, 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://cs.unibo.it/helm/.
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   Configuration.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           ["value",(string_of_int n) ; "binder",b ; "id",id ; "idref",idref ;
53            "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" ["uri",U.string_of_uri uri;"id",id;"sort",sort])
58           exp_named_subst
59      | C.AMeta (id,n,l) ->
60         let sort = Hashtbl.find ids_to_inner_sorts id in
61          X.xml_nempty "META" ["no",(string_of_int n) ; "id",id ; "sort",sort]
62           (List.fold_left
63             (fun i t ->
64               match t with
65                  Some t' ->
66                   [< i ; X.xml_nempty "substitution" [] (aux t') >]
67                | None ->
68                   [< i ; X.xml_empty "substitution" [] >]
69             ) [< >] l)
70      | C.ASort (id,s) ->
71         let string_of_sort =
72          function
73             C.Prop -> "Prop"
74           | C.Set  -> "Set"
75           | C.Type -> "Type"
76         in
77          X.xml_empty "SORT" ["value",(string_of_sort s) ; "id",id]
78      | C.AImplicit _ -> raise NotImplemented
79      | C.AProd (last_id,_,_,_) as prods ->
80         let rec eat_prods =
81          function
82             C.AProd (id,n,s,t) ->
83              let prods,t' = eat_prods t in
84               (id,n,s)::prods,t'
85           | t -> [],t
86         in
87          let prods,t = eat_prods prods in
88           let sort = Hashtbl.find ids_to_inner_sorts last_id in
89            X.xml_nempty "PROD" ["type",sort]
90             [< List.fold_left
91                 (fun i (id,binder,s) ->
92                   let sort = Hashtbl.find ids_to_inner_sorts id in
93                    let attrs =
94                     ("id",id)::("type",sort)::
95                     match binder with
96                        C.Anonymous -> []
97                      | C.Name b -> ["binder",b]
98                    in
99                     [< i ; X.xml_nempty "decl" attrs (aux s) >]
100                 ) [< >] prods ;
101                X.xml_nempty "target" [] (aux t)
102             >]
103      | C.ACast (id,v,t) ->
104         let sort = Hashtbl.find ids_to_inner_sorts id in
105          X.xml_nempty "CAST" ["id",id ; "sort",sort]
106           [< X.xml_nempty "term" [] (aux v) ;
107              X.xml_nempty "type" [] (aux t)
108           >]
109      | C.ALambda (last_id,_,_,_) as lambdas ->
110         let rec eat_lambdas =
111          function
112             C.ALambda (id,n,s,t) ->
113              let lambdas,t' = eat_lambdas t in
114               (id,n,s)::lambdas,t'
115           | t -> [],t
116         in
117          let lambdas,t = eat_lambdas lambdas in
118           let sort = Hashtbl.find ids_to_inner_sorts last_id in
119            X.xml_nempty "LAMBDA" ["sort",sort]
120             [< List.fold_left
121                 (fun i (id,binder,s) ->
122                   let sort = Hashtbl.find ids_to_inner_sorts (Cic2acic.source_id_of_id id) in
123                   let _ = prerr_endline ("AHHHHHHHHHHHHHHHHH" ^ sort) in
124                    let attrs =
125                     ("id",id)::("type",sort)::
126                     match binder with
127                        C.Anonymous -> []
128                      | C.Name b -> ["binder",b]
129                    in
130                     [< i ; X.xml_nempty "decl" attrs (aux s) >]
131                 ) [< >] lambdas ;
132                X.xml_nempty "target" [] (aux t)
133             >]
134      | C.ALetIn (xid,C.Anonymous,s,t) ->
135        assert false
136      | C.ALetIn (last_id,C.Name _,_,_) as letins ->
137         let rec eat_letins =
138          function
139             C.ALetIn (id,n,s,t) ->
140              let letins,t' = eat_letins t in
141               (id,n,s)::letins,t'
142           | t -> [],t
143         in
144          let letins,t = eat_letins letins in
145           let sort = Hashtbl.find ids_to_inner_sorts last_id in
146            X.xml_nempty "LETIN" ["sort",sort]
147             [< List.fold_left
148                 (fun i (id,binder,s) ->
149                   let sort = Hashtbl.find ids_to_inner_sorts id in
150                    let attrs =
151                     ("id",id)::("sort",sort)::
152                     match binder with
153                        C.Anonymous -> []
154                      | C.Name b -> ["binder",b]
155                    in
156                     [< i ; X.xml_nempty "def" attrs (aux s) >]
157                 ) [< >] letins ;
158                X.xml_nempty "target" [] (aux t)
159             >]
160      | C.AAppl (id,li) ->
161         let sort = Hashtbl.find ids_to_inner_sorts id in
162          X.xml_nempty "APPLY" ["id",id ; "sort",sort]
163           [< (List.fold_right (fun x i -> [< (aux x) ; i >]) li [<>])
164           >]
165      | C.AConst (id,uri,exp_named_subst) ->
166         let sort = Hashtbl.find ids_to_inner_sorts id in
167          aux_subst uri
168           (X.xml_empty "CONST"
169             ["uri", (U.string_of_uri uri) ; "id",id ; "sort",sort]
170           ) exp_named_subst
171      | C.AMutInd (id,uri,i,exp_named_subst) ->
172         aux_subst uri
173          (X.xml_empty "MUTIND"
174            ["uri", (U.string_of_uri uri) ;
175             "noType",(string_of_int i) ;
176             "id",id]
177          ) exp_named_subst
178      | C.AMutConstruct (id,uri,i,j,exp_named_subst) ->
179         let sort = Hashtbl.find ids_to_inner_sorts id in
180          aux_subst uri
181           (X.xml_empty "MUTCONSTRUCT"
182             ["uri", (U.string_of_uri uri) ;
183              "noType",(string_of_int i) ; "noConstr",(string_of_int j) ;
184              "id",id ; "sort",sort]
185           ) exp_named_subst
186      | C.AMutCase (id,uri,typeno,ty,te,patterns) ->
187         let sort = Hashtbl.find ids_to_inner_sorts id in
188          X.xml_nempty "MUTCASE"
189           ["uriType",(U.string_of_uri uri) ;
190            "noType", (string_of_int typeno) ;
191            "id", id ; "sort",sort]
192           [< X.xml_nempty "patternsType" [] [< (aux ty) >] ;
193              X.xml_nempty "inductiveTerm" [] [< (aux te) >] ;
194              List.fold_right
195               (fun x i -> [< X.xml_nempty "pattern" [] [< aux x >] ; i>])
196               patterns [<>]
197           >]
198      | C.AFix (id, no, funs) ->
199         let sort = Hashtbl.find ids_to_inner_sorts id in
200          X.xml_nempty "FIX"
201           ["noFun", (string_of_int no) ; "id",id ; "sort",sort]
202           [< List.fold_right
203               (fun (id,fi,ai,ti,bi) i ->
204                 [< X.xml_nempty "FixFunction"
205                     ["id",id ; "name", fi ; "recIndex", (string_of_int ai)]
206                     [< X.xml_nempty "type" [] [< aux ti >] ;
207                        X.xml_nempty "body" [] [< aux bi >]
208                     >] ;
209                    i
210                 >]
211               ) funs [<>]
212           >]
213      | C.ACoFix (id,no,funs) ->
214         let sort = Hashtbl.find ids_to_inner_sorts id in
215          X.xml_nempty "COFIX"
216           ["noFun", (string_of_int no) ; "id",id ; "sort",sort]
217           [< List.fold_right
218               (fun (id,fi,ti,bi) i ->
219                 [< X.xml_nempty "CofixFunction" ["id",id ; "name", fi]
220                     [< X.xml_nempty "type" [] [< aux ti >] ;
221                        X.xml_nempty "body" [] [< aux bi >]
222                     >] ;
223                    i
224                 >]
225               ) funs [<>]
226           >]
227  and aux_subst buri target subst =
228 (*CSC: I have now no way to assign an ID to the explicit named substitution *)
229   let id = None in
230    if subst = [] then
231     target
232    else
233     Xml.xml_nempty "instantiate"
234      (match id with None -> [] | Some id -> ["id",id])
235      [< target ;
236         List.fold_left
237          (fun i (uri,arg) ->
238            let relUri =
239             let buri_frags =
240              Str.split (Str.regexp "/") (UriManager.string_of_uri buri) in
241             let uri_frags = 
242              Str.split (Str.regexp "/") (UriManager.string_of_uri uri)  in
243              let rec find_relUri buri_frags uri_frags =
244               match buri_frags,uri_frags with
245                  [_], _ -> String.concat "/" uri_frags
246                | he1::tl1, he2::tl2 ->
247                   assert (he1 = he2) ;
248                   find_relUri tl1 tl2
249                | _,_ -> assert false (* uri is not relative to buri *)
250              in
251               find_relUri buri_frags uri_frags
252            in
253             [< i ; Xml.xml_nempty "arg" ["relUri", relUri] (aux arg) >]
254          ) [<>] subst
255      >]
256   in
257    aux
258 ;;
259
260 let print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter obj =
261  let module C = Cic in
262  let module X = Xml in
263  let module U = UriManager in
264   let dtdname = dtdname ~ask_dtd_to_the_getter "cic.dtd" in
265    match obj with
266        C.ACurrentProof (id,idbody,n,conjectures,bo,ty,params) ->
267         let params' = param_attribute_of_params params in
268         let xml_for_current_proof_body =
269 (*CSC: Should the CurrentProof also have the list of variables it depends on? *)
270 (*CSC: I think so. Not implemented yet.                                       *)
271          X.xml_nempty "CurrentProof"
272           ["of",UriManager.string_of_uri uri ; "id", id]
273           [< List.fold_left
274               (fun i (cid,n,canonical_context,t) ->
275                 [< i ;
276                    X.xml_nempty "Conjecture"
277                     ["id", cid ; "no",(string_of_int n)]
278                     [< List.fold_left
279                         (fun i (hid,t) ->
280                           [< (match t with
281                                  Some (n,C.ADecl t) ->
282                                   X.xml_nempty "Decl"
283                                    (match n with
284                                        C.Name n' -> ["id",hid;"name",n']
285                                      | C.Anonymous -> ["id",hid])
286                                    (print_term ids_to_inner_sorts t)
287                                | Some (n,C.ADef t) ->
288                                   X.xml_nempty "Def"
289                                    (match n with
290                                        C.Name n' -> ["id",hid;"name",n']
291                                      | C.Anonymous -> ["id",hid])
292                                    (print_term ids_to_inner_sorts t)
293                               | None -> X.xml_empty "Hidden" ["id",hid]
294                              ) ;
295                              i
296                           >]
297                         ) [< >] canonical_context ;
298                        X.xml_nempty "Goal" []
299                         (print_term ids_to_inner_sorts t)
300                     >]
301                 >])
302               [<>] conjectures ;
303              X.xml_nempty "body" [] (print_term ids_to_inner_sorts bo) >]
304         in
305         let xml_for_current_proof_type =
306          X.xml_nempty "ConstantType" ["name",n ; "params",params' ; "id", id]
307           (print_term ids_to_inner_sorts ty)
308         in
309         let xmlbo =
310          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
311             X.xml_cdata ("<!DOCTYPE CurrentProof SYSTEM \""^ dtdname ^ "\">\n");
312             xml_for_current_proof_body
313          >] in
314         let xmlty =
315          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
316             X.xml_cdata ("<!DOCTYPE ConstantType SYSTEM \""^ dtdname ^ "\">\n");
317             xml_for_current_proof_type
318          >]
319         in
320          xmlty, Some xmlbo
321      | C.AConstant (id,idbody,n,bo,ty,params) ->
322         let params' = param_attribute_of_params params in
323         let xmlbo =
324          match bo with
325             None -> None
326           | Some bo ->
327              Some
328               [< X.xml_cdata
329                   "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
330                  X.xml_cdata
331                   ("<!DOCTYPE ConstantBody SYSTEM \"" ^ dtdname ^ "\">\n") ;
332                  X.xml_nempty "ConstantBody"
333                   ["for",UriManager.string_of_uri uri ; "params",params' ;
334                    "id", id]
335                   [< print_term ids_to_inner_sorts bo >]
336               >]
337         in
338         let xmlty =
339          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
340             X.xml_cdata ("<!DOCTYPE ConstantType SYSTEM \""^ dtdname ^ "\">\n");
341              X.xml_nempty "ConstantType"
342               ["name",n ; "params",params' ; "id", id]
343               [< print_term ids_to_inner_sorts ty >]
344          >]
345         in
346          xmlty, xmlbo
347      | C.AVariable (id,n,bo,ty,params) ->
348         let params' = param_attribute_of_params params in
349         let xmlbo =
350          match bo with
351             None -> [< >]
352           | Some bo ->
353              X.xml_nempty "body" [] [< print_term ids_to_inner_sorts bo >]
354         in
355         let aobj =
356          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
357             X.xml_cdata ("<!DOCTYPE Variable SYSTEM \"" ^ dtdname ^ "\">\n");
358              X.xml_nempty "Variable"
359               ["name",n ; "params",params' ; "id", id]
360               [< xmlbo ;
361                  X.xml_nempty "type" [] (print_term ids_to_inner_sorts ty)
362               >]
363          >]
364         in
365          aobj, None
366      | C.AInductiveDefinition (id,tys,params,nparams) ->
367         let params' = param_attribute_of_params params in
368          [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
369             X.xml_cdata
370              ("<!DOCTYPE InductiveDefinition SYSTEM \"" ^ dtdname ^ "\">\n") ;
371             X.xml_nempty "InductiveDefinition"
372              ["noParams",string_of_int nparams ;
373               "id",id ;
374               "params",params']
375              [< (List.fold_left
376                   (fun i (id,typename,finite,arity,cons) ->
377                     [< i ;
378                        X.xml_nempty "InductiveType"
379                         ["id",id ; "name",typename ;
380                          "inductive",(string_of_bool finite)
381                         ]
382                         [< X.xml_nempty "arity" []
383                             (print_term ids_to_inner_sorts arity) ;
384                            (List.fold_left
385                             (fun i (name,lc) ->
386                               [< i ;
387                                  X.xml_nempty "Constructor"
388                                   ["name",name]
389                                   (print_term ids_to_inner_sorts lc)
390                               >]) [<>] cons
391                            )
392                         >]
393                     >]
394                   ) [< >] tys
395                 )
396              >]
397          >], None
398 ;;
399
400 let
401  print_inner_types curi ~ids_to_inner_sorts ~ids_to_inner_types
402   ~ask_dtd_to_the_getter
403 =
404  let module C2A = Cic2acic in
405  let module X = Xml in
406   let dtdname = dtdname ~ask_dtd_to_the_getter "cictypes.dtd" in
407    [< X.xml_cdata "<?xml version=\"1.0\" encoding=\"ISO-8859-1\"?>\n" ;
408       X.xml_cdata
409        ("<!DOCTYPE InnerTypes SYSTEM \"" ^ dtdname ^ "\">\n") ;
410       X.xml_nempty "InnerTypes" ["of",UriManager.string_of_uri curi]
411        (Hashtbl.fold
412          (fun id {C2A.annsynthesized = synty ; C2A.annexpected = expty} x ->
413            [< x ;
414               X.xml_nempty "TYPE" ["of",id]
415                [< X.xml_nempty "synthesized" []
416                  [< print_term ids_to_inner_sorts synty >] ;
417                  match expty with
418                    None -> [<>]
419                  | Some expty' -> X.xml_nempty "expected" [] [< print_term ids_to_inner_sorts expty' >]
420                >]
421            >]
422          ) ids_to_inner_types [<>]
423        )
424    >]
425 ;;