X-Git-Url: http://matita.cs.unibo.it/gitweb/?a=blobdiff_plain;f=helm%2Fsoftware%2Flambda-delta%2Fbasic_rg%2FbrgReduction.ml;h=3b4820abf5fdc0eaf6e9fbc0b78d1f6b0d00df14;hb=5780dca4cfcee57e680213186cf3eaae402b6c88;hp=aced1a22ec6a7673845d0357ff0fa0c003665bb2;hpb=f3b4d265268a43ca98e6843b733109fdfe3f6b0b;p=helm.git diff --git a/helm/software/lambda-delta/basic_rg/brgReduction.ml b/helm/software/lambda-delta/basic_rg/brgReduction.ml index aced1a22e..3b4820abf 100644 --- a/helm/software/lambda-delta/basic_rg/brgReduction.ml +++ b/helm/software/lambda-delta/basic_rg/brgReduction.ml @@ -11,184 +11,209 @@ module U = NUri module C = Cps -module S = Share +module L = Log +module P = Output module B = Brg +module O = BrgOutput module E = BrgEnvironment +module S = BrgSubstitution -exception LRefNotFound of string Lazy.t +exception TypeError of B.message -type bind = Void_ - | Abst_ of B.term - | Abbr_ of B.term +type machine = { + c: B.context; + s: (B.term * int) list +} -type environment = int * bind list +(* Internal functions *******************************************************) -type stack = B.term list +let level = 5 -type context = { - g: environment; - l: environment; - s: stack -} +let log1 s c t = + let sc, st = s ^ " in the context", "the term" in + L.log O.specs level (L.ct_items1 sc c st t) -type whd_result = - | Sort_ of int - | LRef_ of int * B.term option - | GRef_ of int * B.bind * B.term - | Bind_ of B.term * B.term +let log2 s cu u ct t = + let s1, s2, s3 = s ^ " in the context", "the term", "and in the context" in + L.log O.specs level (L.ct_items2 s1 cu s2 u s3 ct s2 t) -type ho_whd_result = - | Sort of int - | Abst of B.term +let error0 i = + let s = Printf.sprintf "local reference not found %u" i in + raise (TypeError (L.items1 s)) -(* Internal functions *******************************************************) +let error1 st c t = + let sc = "In the context" in + raise (TypeError (L.ct_items1 sc c st t)) -let empty_e = 0, [] +let error3 c t1 t2 t3 = + let sc, st1, st2, st3 = + "In the context", "the term", "is of type", "but must be of type" + in + raise (TypeError (L.ct_items3 sc c st1 t1 st2 t2 st3 t3)) -let push_e f b (l, e) = - f (succ l, b :: e) +let empty_machine c = { + c = c; s = [] +} -let get_e f c i = - let (gl, ge), (ll, le) = c.g, c.l in - if i >= gl + ll then raise (LRefNotFound (lazy (string_of_int i))); - let b = - if i < gl then List.nth ge (gl - (succ i)) - else List.nth le (gl + ll - (succ i)) +let get f m i = + let f e = function + | Some (_, b) -> f e b + | None -> error0 i in - f b - -let rec lref_map f map t = match t with - | B.LRef i -> f (B.LRef (map i)) - | B.GRef _ -> f t - | B.Sort _ -> f t - | B.Cast (w, u) -> - let f w' u' = f (S.sh2 w w' u u' t B.cast) in - let f w' = lref_map (f w') map u in - lref_map f map w - | B.Appl (w, u) -> - let f w' u' = f (S.sh2 w w' u u' t B.appl) in - let f w' = lref_map (f w') map u in - lref_map f map w - | B.Bind (id, b, w, u) -> - let f w' u' = f (S.sh2 w w' u u' t (B.bind id b)) in - let f w' = lref_map (f w') map u in - lref_map f map w + B.get f m.c i -(* to share *) -let lift f c = - let (gl, _), (ll, le) = c.g, c.l in - let map i = if i >= gl then succ i else i in - let map f = function - | Abbr_ t -> let f t' = f (Abbr_ t') in lref_map f map t - | _ -> assert false - in - let f le' = f {c with l = (ll, le')} in - C.list_map f map le - -let xchg f c t = - let (gl, _), (ll, _) = c.g, c.l in - let map i = - if i < gl || i > gl + ll then i else - if i >= gl && i < gl + ll then succ i else gl - in - lref_map (f c) map t +let lift_stack f s = + let map f (v, i) = f (v, succ i) in + Cps.list_map f map s + +let push f m a b = + assert (m.s = []); + f {m with c = (a, b) :: m.c} (* to share *) -let rec whd f c t = match t with - | B.Sort h -> f c (Sort_ h) - | B.GRef uri -> - let f (i, _, b, t) = f c (GRef_ (i, b, t)) in - E.get_obj f uri - | B.LRef i -> +let rec step f ?(delta=false) ?(rt=false) m x = +(* L.warn "entering R.step"; *) + match x with + | B.Sort _ -> f m x + | B.GRef (a, uri) -> let f = function - | Void_ -> f c (LRef_ (i, None)) - | Abst_ t -> f c (LRef_ (i, Some t)) - | Abbr_ t -> whd f c t + | _, _, B.Abbr v when delta -> + P.add ~gdelta:1 (); + step f ~delta ~rt m v + | _, _, B.Abst w when rt -> + P.add ~grt:1 (); + step f ~delta ~rt m w + | e, _, b -> + f m (B.GRef (B.Entry (e, b) :: a, uri)) + in + E.get_obj f uri + | B.LRef (a, i) -> + let f e = function + | B.Abbr v -> + P.add ~ldelta:1 (); + step f ~delta ~rt m v + | B.Abst w when rt -> + P.add ~lrt:1 (); + step f ~delta ~rt m w + | b -> + f m (B.LRef (B.Entry (e, b) :: a, i)) in - get_e f c i - | B.Appl (v, t) -> whd f {c with s = v :: c.s} t - | B.Bind (_, B.Abbr, v, t) -> - let f l = whd f {c with l = l} t in - push_e f (Abbr_ v) c.l - | B.Bind (_, B.Abst, w, t) -> - begin match c.s with - | [] -> f c (Bind_ (w, t)) - | v :: tl -> - let f tl l = whd f {c with l = l; s = tl} t in - push_e (f tl) (Abbr_ v) c.l + let f e = S.lift_bind (f e) (succ i) (0) in + get f m i + | B.Cast (_, _, t) -> + P.add ~tau:1 (); + step f ~delta ~rt m t + | B.Appl (_, v, t) -> + step f ~delta ~rt {m with s = (v, 0) :: m.s} t + | B.Bind (a, B.Abst w, t) -> + begin match m.s with + | [] -> f m x + | (v, h) :: tl -> + P.add ~beta:1 ~upsilon:(List.length tl) (); + let f c s = step f ~delta ~rt {c = c; s = s} t in + let f c = lift_stack (f c) tl in + let f v = B.push f m.c a (B.Abbr v (* (B.Cast ([], w, v)) *) ) in + S.lift f h (0) v end - | B.Cast (_, t) -> whd f c t - -let push f c t = - assert (c.s = []); - let f c g = xchg f {c with g = g} t in - let f c = push_e (f c) Void_ c.g in - lift f c + | B.Bind (a, b, t) -> + P.add ~upsilon:(List.length m.s) (); + let f s c = step f ~delta ~rt {c = c; s = s} t in + let f s = B.push (f s) m.c a b in + lift_stack f m.s (* Interface functions ******************************************************) -let rec are_convertible f c1 t1 c2 t2 = - let rec aux c1' r1 c2' r2 = match r1, r2 with - | Sort_ h1, Sort_ h2 -> f (h1 = h2) - | LRef_ (i1, _), LRef_ (i2, _) -> - if i1 = i2 then are_convertible_stacks f c1' c2' else f false - | GRef_ (a1, B.Abst, _), GRef_ (a2, B.Abst, _) -> - if a1 = a2 then are_convertible_stacks f c1' c2' else f false - | GRef_ (a1, B.Abbr, v1), GRef_ (a2, B.Abbr, v2) -> - if a1 = a2 then are_convertible_stacks f c1' c2' else - if a1 < a2 then whd (aux c1' r1) c2' v2 else - whd (aux_rev c2' r2) c1' v1 - | _, GRef_ (_, B.Abbr, v2) -> - whd (aux c1' r1) c2' v2 - | GRef_ (_, B.Abbr, v1), _ -> - whd (aux_rev c2' r2) c1' v1 - | Bind_ (w1, t1), Bind_ (w2, t2) -> - let f b = - if b then - let f c1'' t1' = push (are_convertible f c1'' t1') c2' t2 in - push f c1' t1 - else f false - in - are_convertible f c1' w1 c2' w2 - | _ -> f false - and aux_rev c2 r2 c1 r1 = aux c1 r1 c2 r2 in - let f c1' r1 = whd (aux c1' r1) c2 t2 in - whd f c1 t1 - -and are_convertible_stacks f c1 c2 = - let map f v1 v2 = are_convertible f c1 v1 c2 v2 in - if List.length c1.s <> List.length c2.s then f false else - C.forall2 f map c1.s c2.s - -let are_convertible f c t1 t2 = are_convertible f c t1 c t2 - -let rec ho_whd f c t = - let aux c' = function - | Sort_ h -> f c' (Sort h) - | Bind_ (w, t) -> f c' (Abst w) - | LRef_ (_, Some w) -> ho_whd f c w - | GRef_ (_, _, u) -> ho_whd f c u - | LRef_ (_, None) -> assert false +let domain f m t = + let f r = L.unbox level; f r in + let f m = function + | B.Bind (_, B.Abst w, _) -> f m w + | _ -> error1 "not a function" m.c t in - whd aux c t - -let push f c b t = - assert (c.l = empty_e && c.s = []); - let f g = f {c with g = g} in - let b = match b with - | B.Abbr -> Abbr_ t - | B.Abst -> Abst_ t + L.box level; log1 "Now scanning" m.c t; + step f ~delta:true ~rt:true m t + +let rec ac_nfs f ~si r m1 u m2 t = + log2 "Now converting nfs" m1.c u m2.c t; + match u, t with + | B.Sort (_, h1), B.Sort (_, h2) -> + if h1 = h2 then f r else f false + | B.LRef (B.Entry (e1, B.Abst _) :: _, i1), + B.LRef (B.Entry (e2, B.Abst _) :: _, i2) -> + P.add ~zeta:(i1+i2-e1-e2) (); + if e1 = e2 then ac_stacks f ~si r m1 m2 else f false + | B.GRef (B.Entry (e1, B.Abst _) :: _, _), + B.GRef (B.Entry (e2, B.Abst _) :: _, _) -> + if e1 = e2 then ac_stacks f ~si r m1 m2 else f false + | B.GRef (B.Entry (e1, B.Abbr v1) :: _, _), + B.GRef (B.Entry (e2, B.Abbr v2) :: _, _) -> + if e1 = e2 then + let f r = + if r then f r + else begin + P.add ~gdelta:2 (); + ac f ~si true m1 v1 m2 v2 + end + in + ac_stacks f ~si r m1 m2 + else if e1 < e2 then begin + P.add ~gdelta:1 (); + step (ac_nfs f ~si r m1 u) m2 v2 + end else begin + P.add ~gdelta:1 (); + step (ac_nfs_rev f ~si r m2 t) m1 v1 + end + | _, B.GRef (B.Entry (_, B.Abbr v2) :: _, _) -> + P.add ~gdelta:1 (); + step (ac_nfs f ~si r m1 u) m2 v2 + | B.GRef (B.Entry (_, B.Abbr v1) :: _, _), _ -> + P.add ~gdelta:1 (); + step (ac_nfs_rev f ~si r m2 t) m1 v1 + | B.Bind (a1, (B.Abst w1 as b1), t1), + B.Bind (a2, (B.Abst w2 as b2), t2) -> + let g m1 m2 = ac f ~si r m1 t1 m2 t2 in + let g m1 = push (g m1) m2 a2 b2 in + let f r = if r then push g m1 a1 b1 else f false in + ac f ~si r m1 w1 m2 w2 + | B.Sort _, B.Bind (a, b, t) when si -> + P.add ~si:1 (); + let f m1 m2 = ac f ~si r m1 u m2 t in + let f m1 = push (f m1) m2 a b in + push f m1 a b + | _ -> f false + +and ac_nfs_rev f ~si r m2 t m1 u = ac_nfs f ~si r m1 u m2 t + +and ac f ~si r m1 t1 m2 t2 = +(* L.warn "entering R.are_convertible"; *) + let g m1 t1 = step (ac_nfs f ~si r m1 t1) m2 t2 in + if r = false then f false else step g m1 t1 + +and ac_stacks f ~si r m1 m2 = +(* L.warn "entering R.are_convertible_stacks"; *) + let mm1, mm2 = {m1 with s = []}, {m2 with s = []} in + let map f r (v1, h1) (v2, h2) = + let f v1 = S.lift (ac f ~si r mm1 v1 mm2) h2 (0) v2 in + S.lift f h1 (0) v1 in - push_e f b c.g - -let get f c i = - let gl, ge = c.g in - if i >= gl then raise (LRefNotFound (lazy (string_of_int i))); - match List.nth ge (gl - (succ i)) with - | Abbr_ v -> f (B.Abbr, v) - | Abst_ w -> f (B.Abst, w) - | Void_ -> assert false - -let empty_context = { - g = empty_e; l = empty_e; s = [] -} + if List.length m1.s <> List.length m2.s then + begin +(* L.warn (Printf.sprintf "Different lengths: %u %u" + (List.length m1.s) (List.length m2.s) + ); *) + f false + end + else + C.list_fold_left2 f map r m1.s m2.s + +let assert_conversion f ?(si=false) ?(rt=false) c u w v = + let f b = L.unbox level; f b in + let mw = empty_machine c in + let f mu u = + let f = function + | true -> f () + | false -> error3 c v w u + in + L.box level; log2 "Now converting" c u c w; + ac f ~si true mu u mw w + in + if rt then domain f mw u else f mw u