]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic_unification/cicMkImplicit.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_unification / cicMkImplicit.ml
1 (* Copyright (C) 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://cs.unibo.it/helm/.
24  *)
25
26 (* identity_relocation_list_for_metavariable i canonical_context         *)
27 (* returns the identity relocation list, which is the list [1 ; ... ; n] *)
28 (* where n = List.length [canonical_context]                             *)
29 (*CSC: ma mi basta la lunghezza del contesto canonico!!!*)
30 let identity_relocation_list_for_metavariable ?(start = 1) canonical_context =
31   let rec aux =
32    function
33       (_,[]) -> []
34     | (n,None::tl) -> None::(aux ((n+1),tl))
35     | (n,_::tl) -> (Some (Cic.Rel n))::(aux ((n+1),tl))
36   in
37    aux (start,canonical_context)
38
39 (* Returns the first meta whose number is above the *)
40 (* number of the higher meta.                       *)
41 let new_meta metasenv subst =
42   let rec aux =
43    function
44       None, [] -> 1
45     | Some n, [] -> n
46     | None, n::tl -> aux (Some n,tl)
47     | Some m, n::tl -> if n > m then aux (Some n,tl) else aux (Some m,tl)
48   in
49   let indexes = 
50     (List.map (fun (i, _, _) -> i) metasenv) @ (List.map fst subst)
51   in
52   1 + aux (None, indexes)
53
54 (* let apply_subst_context = CicMetaSubst.apply_subst_context;; *)
55 (* questa o la precedente sembrano essere equivalenti come tempi *)
56 let apply_subst_context _ context = context ;;
57
58 let mk_implicit metasenv subst context =
59   let newmeta = new_meta metasenv subst in
60   let newuniv = CicUniv.fresh () in
61   let irl = identity_relocation_list_for_metavariable context in
62     (* in the following mk_* functions we apply substitution to canonical
63     * context since we have the invariant that the metasenv has already been
64     * instantiated with subst *)
65   let context = apply_subst_context subst context in
66   ([ newmeta, [], Cic.Sort (Cic.Type newuniv) ;
67     (* TASSI: ?? *)
68     newmeta + 1, context, Cic.Meta (newmeta, []);
69     newmeta + 2, context, Cic.Meta (newmeta + 1,irl) ] @ metasenv,
70    newmeta + 2)
71
72 let mk_implicit_type metasenv subst context =
73   let newmeta = new_meta metasenv subst in
74   let newuniv = CicUniv.fresh () in
75   let context = apply_subst_context subst context in
76   ([ newmeta, [], Cic.Sort (Cic.Type newuniv);
77     (* TASSI: ?? *)
78     newmeta + 1, context, Cic.Meta (newmeta, []) ] @metasenv,
79    newmeta + 1)
80
81 let mk_implicit_sort metasenv subst =
82   let newmeta = new_meta metasenv subst in
83   let newuniv = CicUniv.fresh () in
84   ([ newmeta, [], Cic.Sort (Cic.Type newuniv)] @ metasenv, newmeta)
85   (* TASSI: ?? *)
86
87 let n_fresh_metas metasenv subst context n = 
88   if n = 0 then metasenv, []
89   else 
90     let irl = identity_relocation_list_for_metavariable context in
91     let context = apply_subst_context subst context in
92     let newmeta = new_meta metasenv subst in
93     let newuniv = CicUniv.fresh () in
94     let rec aux newmeta n = 
95       if n = 0 then metasenv, [] 
96       else
97         let metasenv', l = aux (newmeta + 3) (n-1) in 
98         (* TASSI: ?? *)
99         (newmeta, context, Cic.Sort (Cic.Type newuniv))::
100         (newmeta + 1, context, Cic.Meta (newmeta, irl))::
101         (newmeta + 2, context, Cic.Meta (newmeta + 1,irl))::metasenv',
102         Cic.Meta(newmeta+2,irl)::l in
103     aux newmeta n
104       
105 let fresh_subst metasenv subst context uris = 
106   let irl = identity_relocation_list_for_metavariable context in
107   let context = apply_subst_context subst context in
108   let newmeta = new_meta metasenv subst in
109   let newuniv = CicUniv.fresh () in
110   let rec aux newmeta = function
111       [] -> metasenv, [] 
112     | uri::tl ->
113        let metasenv', l = aux (newmeta + 3) tl in 
114          (* TASSI: ?? *)
115          (newmeta, context, Cic.Sort (Cic.Type newuniv))::
116          (newmeta + 1, context, Cic.Meta (newmeta, irl))::
117          (newmeta + 2, context, Cic.Meta (newmeta + 1,irl))::metasenv',
118           (uri,Cic.Meta(newmeta+2,irl))::l in
119     aux newmeta uris
120