]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/ng_kernel/oCic2NCic.ml
...
[helm.git] / helm / software / components / ng_kernel / oCic2NCic.ml
1 let convert_term = Obj.magic;;
2
3 let cn_to_s = function
4   | Cic.Anonymous -> "_"
5   | Cic.Name s -> s
6 ;;
7
8 type ctx = Ce of NCic.hypothesis | Fix of int * int
9
10 let splat mk_pi ctx t =
11   List.fold_left
12     (fun t c -> 
13       match c with
14       | Ce (name, NCic.Def (bo,ty)) -> NCic.LetIn (name, ty, bo, t)
15       | Ce (name, NCic.Decl ty) when mk_pi -> NCic.Prod (name, ty, t)
16       | Ce (name, NCic.Decl ty) -> NCic.Lambda (name, ty, t)
17       | Fix _ -> t)
18     t ctx
19 ;;
20
21 let splat_args ctx t = 
22   let n_args =  
23     List.length (List.filter (function Ce _ -> true | _ -> false) ctx)
24   in  
25   if n_args = 0 then t 
26   else
27     let rec aux = function
28       | 0 -> []
29       | n -> aux (n-1) @ [NCic.Rel n]
30     in
31     NCic.Appl (t:: aux n_args)
32 ;;
33
34 let convert_term uri t = 
35   let rec aux octx (ctx : ctx list) n_fix uri = function
36     | Cic.CoFix (k, fl) ->
37         let idx = ref ~-1 in
38         let bctx = 
39           List.map (fun (_,_,_) -> 
40             incr idx; Fix (~-1,!idx)) fl @ ctx 
41         in
42         let buri = 
43           UriManager.uri_of_string 
44            (UriManager.string_of_uri uri^string_of_int (List.length ctx)^".con")
45         in
46         let n_fl = List.length fl in
47         let boctx,_ =
48          List.fold_left
49           (fun (types,len) (n,ty,_) ->
50              (Some (Cic.Name n,(Cic.Decl (CicSubstitution.lift len ty)))::types,
51               len+1)) (octx,0) fl
52         in
53         let fl, fixpoints =
54           List.fold_right 
55             (fun (name,ty,bo) (l,fixpoints) -> 
56                let ty, fixpoints_ty = aux octx ctx n_fix uri ty in
57                let bo, fixpoints_bo = aux boctx bctx (n_fix + n_fl) buri bo in
58                (([],name,~-1,splat true ctx ty, splat false ctx bo)::l),
59                fixpoints_ty @ fixpoints_bo @ fixpoints)
60             fl ([],[])
61         in
62         let obj = 
63           NUri.nuri_of_ouri uri,0,[],[],
64             NCic.Fixpoint (false, fl, (`Generated, `Definition)) 
65         in
66         NCic.Const (NReference.reference_of_ouri uri (NReference.CoFix (k))),
67         obj::fixpoints
68     | Cic.Fix (k, fl) ->
69         let idx = ref ~-1 in
70         let rno = ref 0 in
71         let bctx = 
72           List.map (fun (_,recno,_,_) -> 
73             incr idx; if !idx = k then rno := recno;Fix (recno,!idx)) fl @ ctx 
74         in
75         let buri = 
76           UriManager.uri_of_string 
77            (UriManager.string_of_uri uri^string_of_int (List.length ctx)^".con")
78         in
79         let n_fl = List.length fl in
80         let boctx,_ =
81          List.fold_left
82           (fun (types,len) (n,_,ty,_) ->
83              (Some (Cic.Name n,(Cic.Decl (CicSubstitution.lift len ty)))::types,
84               len+1)) (octx,0) fl
85         in
86         let fl, fixpoints =
87           List.fold_right 
88             (fun (name,rno,ty,bo) (l,fixpoints) -> 
89                let ty, fixpoints_ty = aux octx ctx n_fix uri ty in
90                let bo, fixpoints_bo = aux boctx bctx (n_fix + n_fl) buri bo in
91                let rno = rno + List.length ctx - n_fix in
92                (([],name,rno,splat true ctx ty, splat false ctx bo)::l),
93                fixpoints_ty @ fixpoints_bo @ fixpoints)
94             fl ([],[])
95         in
96         let obj = 
97           NUri.nuri_of_ouri uri,0,[],[],
98             NCic.Fixpoint (true, fl, (`Generated, `Definition)) 
99         in
100         NCic.Const (NReference.reference_of_ouri uri (NReference.Fix (k,!rno))),
101         obj::fixpoints
102     | Cic.Rel n ->
103         (match List.nth ctx n with
104         | Ce _ -> NCic.Rel (n-n_fix), []
105         | Fix (recno, fixno) -> 
106            (* uri should be in the context, since the inner 
107             * fix may refer to the outer one *)
108            splat_args ctx  (* this function must lift the args wrt len(octx) *)
109            (NCic.Const 
110             (NReference.reference_of_ouri uri (NReference.Fix (fixno,recno)))),
111            [])
112     | Cic.Lambda (name, (s as old_s), t) ->
113         let s, fixpoints_s = aux octx ctx n_fix uri s in
114         let ctx = Ce (cn_to_s name, NCic.Decl s) :: ctx in
115         let octx = Some (name, Cic.Decl old_s) :: octx in
116         let t, fixpoints_t = aux octx ctx n_fix uri t in
117         NCic.Lambda (cn_to_s name, s, t), fixpoints_s @ fixpoints_t
118     | Cic.Prod (name, (s as old_s), t) ->
119         let s, fixpoints_s = aux octx ctx n_fix uri s in
120         let ctx = Ce (cn_to_s name, NCic.Decl s) :: ctx in
121         let octx = Some (name, Cic.Decl old_s) :: octx in
122         let t, fixpoints_t = aux octx ctx n_fix uri t in
123         NCic.Prod (cn_to_s name, s, t), fixpoints_s @ fixpoints_t
124     | Cic.LetIn (name, (s as old_s), t) ->
125         let s, fixpoints_s = aux octx ctx n_fix uri s in
126         let old_ty,_ = 
127           CicTypeChecker.type_of_aux' [] octx old_s CicUniv.oblivion_ugraph 
128         in
129         let ty, fixpoints_ty = aux octx ctx n_fix uri old_ty in
130         let ctx = Ce (cn_to_s name, NCic.Def (s, ty)) :: ctx in
131         let octx = Some (name, Cic.Def (old_s, Some old_ty)) :: octx in
132         let t, fixpoints_t = aux octx ctx n_fix uri t in
133         NCic.LetIn (cn_to_s name, ty, s, t), 
134         fixpoints_s @ fixpoints_t @ fixpoints_ty
135     | Cic.Cast (t,ty) ->
136         let t, fixpoints_t = aux octx ctx n_fix uri t in
137         let ty, fixpoints_ty = aux octx ctx n_fix uri ty in
138         NCic.LetIn ("cast", ty, t, NCic.Rel 1), fixpoints_t @ fixpoints_ty
139     | Cic.Sort Cic.Prop -> NCic.Sort NCic.Prop,[]
140     | Cic.Sort Cic.Set -> NCic.Sort NCic.Set,[]
141     | Cic.Sort Cic.CProp -> NCic.Sort NCic.CProp,[]
142     | Cic.Sort (Cic.Type _) -> NCic.Sort (NCic.Type 0),[] 
143        (* calculate depth in the univ_graph*)
144     | Cic.Appl l -> 
145         let l, fixpoints =
146           List.fold_right 
147              (fun t (l,acc) -> 
148                let t, fixpoints = aux octx ctx n_fix uri t in 
149                (t::l,fixpoints@acc))
150              l ([],[])
151         in
152         NCic.Appl l, fixpoints
153     | Cic.Const (curi, _) -> 
154         NCic.Const (NReference.reference_of_ouri curi NReference.Def),[]
155     | Cic.MutInd (curi, tyno, _) -> 
156         NCic.Const (NReference.reference_of_ouri curi (NReference.Ind tyno)),[]
157     | Cic.MutConstruct (curi, tyno, consno, _) -> 
158         NCic.Const (NReference.reference_of_ouri curi 
159         (NReference.Con (tyno,consno))),[]
160     | Cic.MutCase (curi, tyno, oty, t, branches) ->
161         let r = NReference.reference_of_ouri curi (NReference.Ind tyno) in
162         let oty, fixpoints_oty = aux octx ctx n_fix uri oty in
163         let t, fixpoints_t = aux octx ctx n_fix uri t in
164         let branches, fixpoints =
165           List.fold_right 
166              (fun t (l,acc) -> 
167                let t, fixpoints = aux octx ctx n_fix uri t in 
168                (t::l,fixpoints@acc))
169              branches ([],[])
170         in
171         NCic.Match (r,oty,t,branches), fixpoints_oty @ fixpoints_t @ fixpoints
172     | Cic.Implicit _ | Cic.Meta _ | Cic.Var _ -> assert false
173   in
174    aux [] [] 0 uri t
175 ;;
176
177 let convert_obj_aux uri = function
178  | Cic.Constant (name, None, ty, _, _) ->
179      let nty, fixpoints = convert_term uri ty in
180      assert(fixpoints = []);
181      NCic.Constant ([], name, None, nty, (`Provided,`Theorem,`Regular)),
182      fixpoints
183  | Cic.Constant (name, Some bo, ty, _, _) ->
184      let nbo, fixpoints_bo = convert_term uri bo in
185      let nty, fixpoints_ty = convert_term uri ty in
186      assert(fixpoints_ty = []);
187      NCic.Constant ([], name, Some nbo, nty, (`Provided,`Theorem,`Regular)),
188      fixpoints_bo @ fixpoints_ty
189  | Cic.InductiveDefinition (_,_,_,_) -> assert false (*
190      let ind = let _,x,_,_ = List.hd itl in x in
191      let itl = 
192        List.map 
193          (fun name, _, ty, cl ->
194             [], name, convert_term ty, 
195               List.map (fun name, ty -> [], name, convert_term ty) cl) 
196          itl        
197      in
198      NCic.Inductive (ind, leftno, itl, (`Provided, `Regular)) *)
199  | Cic.Variable _ 
200  | Cic.CurrentProof _ -> assert false
201 ;;
202
203 let convert_obj uri obj = 
204   let o, fixpoints = convert_obj_aux uri obj in
205   let obj = NUri.nuri_of_ouri uri,0, [], [], o in
206   obj, fixpoints
207 ;;