2 ||M|| This file is part of HELM, an Hypertextual, Electronic
3 ||A|| Library of Mathematics, developed at the Computer Science
4 ||T|| Department, University of Bologna, Italy.
6 ||T|| HELM is free software; you can redistribute it and/or
7 ||A|| modify it under the terms of the GNU General Public License
8 \ / version 2 or (at your option) any later version.
9 \ / This software is distributed as is, NO WARRANTY.
10 V_______________________________________________________________ *)
12 (* $Id: nCic.ml 9058 2008-10-13 17:42:30Z tassi $ *)
14 exception Error of string lazy_t
15 let fail msg = raise (Error msg)
17 type lowtac_status = {
19 lstatus : LexiconEngine.status
22 type lowtactic = lowtac_status -> int -> lowtac_status
25 gstatus : Continuationals.Stack.t;
26 istatus : lowtac_status;
29 type tactic = tac_status -> tac_status
31 type tactic_term = CicNotationPt.term Disambiguate.disambiguator_input
32 type tactic_pattern = GrafiteAst.npattern Disambiguate.disambiguator_input
34 let pp_tac_status status =
35 prerr_endline (NCicPp.ppobj status.istatus.pstatus)
38 let pp_lowtac_status status =
39 prerr_endline "--------------------------------------------";
40 prerr_endline (NCicPp.ppobj status.pstatus)
43 type cic_term = NCic.conjecture (* name, context, term *)
44 let ctx_of (_,c,_) = c ;;
46 let relocate context (name,ctx,t as term) =
48 let rec aux = function
50 | x::xs, y::ys -> x=y && aux (xs,ys)
53 aux (List.rev l1, List.rev l2)
55 if ctx == context then term else
56 if ctx = context then term else
57 if is_prefix ctx context then
59 NCicSubstitution.lift (List.length context - List.length ctx) t)
65 type ast_term = string * int * CicNotationPt.term
67 let disambiguate (status : lowtac_status) (t : ast_term)
68 (ty : cic_term option) context =
69 let uri,height,metasenv,subst,obj = status.pstatus in
72 | None -> None | Some ty -> let _,_,x = relocate context ty in Some x
74 let metasenv, subst, lexicon_status, t =
75 GrafiteDisambiguate.disambiguate_nterm expty
76 status.lstatus context metasenv subst t
78 let new_pstatus = uri,height,metasenv,subst,obj in
79 { lstatus = lexicon_status; pstatus = new_pstatus }, (None, context, t)
82 let typeof status ctx t =
83 let _,_,metasenv,subst,_ = status.pstatus in
84 let _,_,t = relocate ctx t in
85 let ty = NCicTypeChecker.typeof ~subst ~metasenv ctx t in
89 let whd status ?delta ctx t =
90 let _,_,metasenv,subst,_ = status.pstatus in
91 let name,_,t = relocate ctx t in
92 let t = NCicReduction.whd ~subst ?delta ctx t in
96 let unify status ctx a b =
97 let n,h,metasenv,subst,o = status.pstatus in
98 let _,_,a = relocate ctx a in
99 let _,_,b = relocate ctx b in
100 let metasenv, subst =
101 NCicUnification.unify (NCicUnifHint.db ()) metasenv subst ctx a b
103 { status with pstatus = n,h,metasenv,subst,o }
106 let refine status ctx term expty =
107 let nt,_,term = relocate ctx term in
109 match expty with None -> None, None
110 | Some e -> let n,_, e = relocate ctx e in n, Some e
112 let name,height,metasenv,subst,obj = status.pstatus in
113 let db = NCicUnifHint.db () in (* XXX fixme *)
114 let coercion_db = NCicCoercion.db () in
115 let look_for_coercion = NCicCoercion.look_for_coercion coercion_db in
116 let metasenv, subst, t, ty =
117 NCicRefiner.typeof db ~look_for_coercion metasenv subst ctx term expty
119 { status with pstatus = (name,height,metasenv,subst,obj) },
120 (nt,ctx,t), (ne,ctx,ty)
123 let get_goalty (status : lowtac_status) (g : int) =
124 let _,_,metasenv,_,_ = status.pstatus in
125 List.assoc g metasenv
128 let instantiate status i t =
129 let (gname, context, _ as gty) = get_goalty status i in
130 let status, (_,_,t), (_,_,ty) =
131 refine status (ctx_of gty) t (Some gty)
134 let name,height,metasenv,subst,obj = status.pstatus in
135 let metasenv = List.filter (fun j,_ -> j <> i) metasenv in
136 let subst = (i, (gname, context, t, ty)) :: subst in
137 { status with pstatus = (name,height,metasenv,subst,obj) }
140 let mk_meta status ?name ctx bo_or_ty =
141 let n,h,metasenv,subst,o = status.pstatus in
144 let _,_,ty = relocate ctx ty in
145 let metasenv, _, instance, _ =
146 NCicMetaSubst.mk_meta ?name metasenv ctx (`WithType ty)
148 let status = { status with pstatus = n,h,metasenv,subst,o } in
149 status, (None,ctx,instance)
151 let _,_,bo_ as bo = relocate ctx bo in
152 let _,_,ty = typeof status ctx bo in
153 let metasenv, metano, instance, _ =
154 NCicMetaSubst.mk_meta ?name metasenv ctx (`WithType ty) in
155 let metasenv = List.filter (fun j,_ -> j <> metano) metasenv in
156 let subst = (metano, (name, ctx, bo_, ty)) :: subst in
157 let status = { status with pstatus = n,h,metasenv,subst,o } in
158 status, (None,ctx,instance)
161 let select_term low_status (name,context,term) (wanted,path) =
162 let found status ctx t wanted =
163 (* we could lift wanted step-by-step *)
164 try true, unify status ctx (None, ctx, t) wanted
166 | NCicUnification.UnificationFailure _
167 | NCicUnification.Uncertain _ -> false, status
169 let match_term status ctx (wanted : cic_term) t =
170 let rec aux ctx status t =
171 let b, status = found status ctx t wanted in
173 let status, (_,_,t) =
174 mk_meta status ~name:NCicMetaSubst.in_scope_tag
175 ctx (`Def (None, ctx, t))
178 else NCicUntrusted.map_term_fold_a (fun e c -> e::c) ctx aux status t
182 let rec select status ctx pat cic =
184 | NCic.LetIn (_,t1,s1,b1), NCic.LetIn (n,t2,s2,b2) ->
185 let status, t = select status ctx t1 t2 in
186 let status, s = select status ctx s1 s2 in
187 let ctx = (n, NCic.Def (s2,t2)) :: ctx in
188 let status, b = select status ctx b1 b2 in
189 status, NCic.LetIn (n,t,s,b)
190 | NCic.Lambda (_,s1,t1), NCic.Lambda (n,s2,t2) ->
191 let status, s = select status ctx s1 s2 in
192 let ctx = (n, NCic.Decl s2) :: ctx in
193 let status, t = select status ctx t1 t2 in
194 status, NCic.Lambda (n,s,t)
195 | NCic.Prod (_,s1,t1), NCic.Prod (n,s2,t2) ->
196 let status, s = select status ctx s1 s2 in
197 let ctx = (n, NCic.Decl s2) :: ctx in
198 let status, t = select status ctx t1 t2 in
199 status, NCic.Prod (n,s,t)
200 | NCic.Appl l1, NCic.Appl l2 ->
203 (fun (status,l) x y ->
204 let status, x = select status ctx x y in
208 status, NCic.Appl (List.rev l)
209 | NCic.Match (_,ot1,t1,pl1), NCic.Match (u,ot2,t2,pl2) ->
210 let status, t = select status ctx t1 t2 in
211 let status, ot = select status ctx ot1 ot2 in
214 (fun (status,l) x y ->
215 let status, x = select status ctx x y in
219 status, NCic.Match (u,ot,t,List.rev pl)
220 | NCic.Implicit `Hole, t ->
223 let status, wanted = disambiguate status wanted None ctx in
224 match_term status ctx wanted t
225 | None -> match_term status ctx (None,ctx,t) t)
226 | NCic.Implicit _, t -> status, t
228 fail (lazy ("malformed pattern: " ^ NCicPp.ppterm ~metasenv:[]
229 ~context:[] ~subst:[] pat))
231 let status, term = select low_status context path term in
232 let term = (name, context, term) in
233 mk_meta status ~name:(NCicMetaSubst.out_scope_tag 1) context (`Def term)
236 let analyse_indty status ty =
238 match whd status (ctx_of ty) ty with
239 | _,_,NCic.Const ref -> ref, []
240 | _,_,NCic.Appl (NCic.Const ref :: args) -> ref, args
241 | _,_,_ -> fail (lazy ("not an inductive type")) in
242 let _,lno,tl,_,i = NCicEnvironment.get_checked_indtys ref in
243 let _,_,_,cl = List.nth tl i in
244 let consno = List.length cl in
245 let left, right = HExtlib.split_nth lno args in
246 ref, consno, left, right
249 let mk_cic_term c t = None,c,t ;;