X-Git-Url: http://git.nguyen.vg/gitweb/?a=blobdiff_plain;f=src%2Fruntime.ml;h=7d1e79f7eac8e9e97706741aa8c020ba7786731a;hb=cb728132e1c5cb0a171ee09e9b3ced16da08f796;hp=c355f5e35edbec206adfd2fa0c76aafe0735b5b3;hpb=4b52da1a20a4fe031930bb96d2ca46bec06dc529;p=SXSI%2Fxpathcomp.git diff --git a/src/runtime.ml b/src/runtime.ml index c355f5e..7d1e79f 100644 --- a/src/runtime.ml +++ b/src/runtime.ml @@ -1,4 +1,5 @@ INCLUDE "debug.ml" +INCLUDE "log.ml" INCLUDE "utils.ml" open Format @@ -7,6 +8,8 @@ module type S = sig type result_set val top_down_run : Ata.t -> Tree.t -> Tree.node -> result_set val bottom_up_run : Ata.t -> Tree.t -> Compile.text_query * string -> result_set + val naive_top_down_run : Ata.t -> Tree.t -> Tree.node -> result_set + val twopass_top_down_run : Ata.t -> Tree.t -> Tree.node -> result_set end module Make (U : ResJIT.S) : S with type result_set = U.NS.t = @@ -16,178 +19,150 @@ module Make (U : ResJIT.S) : S with type result_set = U.NS.t = let eval_form auto s1 s2 f = let rec loop f = - match Formula.expr f with - | Formula.False | Formula.True | Formula.Pred _ -> f, [] - | Formula.Atom(`Left, b, q) -> - Formula.of_bool (b == (StateSet.mem q s1)), - if b && StateSet.mem q auto.topdown_marking_states then [ResJIT.LEFT q] else [] - | Formula.Atom (`Right, b, q) -> - Formula.of_bool(b == (StateSet.mem q s2)), - if b && StateSet.mem q auto.topdown_marking_states then [ResJIT.RIGHT q] else [] - - | Formula.Or(f1, f2) -> - let b1, i1 = loop f1 in - let b2, i2 = loop f2 in - Formula.or_pred b1 b2, i1 @ i2 - | Formula.And(f1, f2) -> - let b1, i1 = loop f1 in - let b2, i2 = loop f2 in - Formula.and_pred b1 b2, i1 @ i2 + match Formula.expr f with + | Formula.False | Formula.True | Formula.Pred _ -> f, [] + | Formula.Atom(`Left, b, q) -> + Formula.of_bool (b == (StateSet.mem q s1)), + if b && StateSet.mem q auto.topdown_marking_states then [ResJIT.LEFT q] else [] + | Formula.Atom (`Right, b, q) -> + Formula.of_bool(b == (StateSet.mem q s2)), + if b && StateSet.mem q auto.topdown_marking_states then [ResJIT.RIGHT q] else [] + | Formula.Atom (`Epsilon, _, _) -> assert false + + | Formula.Or(f1, f2) -> + let b1, i1 = loop f1 in + let b2, i2 = loop f2 in + Formula.or_pred b1 b2, i1 @ i2 + | Formula.And(f1, f2) -> + let b1, i1 = loop f1 in + let b2, i2 = loop f2 in + Formula.and_pred b1 b2, i1 @ i2 in loop f let eval_trans auto s1 s2 trans = + LOG(__ "top-down-run" 3 "Evaluating transition list:@\n%a" Translist.print trans); Translist.fold - (fun t ((a_st, a_op, a_todo) as acc)-> - let q, _, m, f = Transition.node t in - let form, ops = eval_form auto s1 s2 f in - match Formula.expr form with - | Formula.True -> - StateSet.add q a_st, - (q, (if m then (ResJIT.SELF() :: ops) else ops)):: a_op, - a_todo - | Formula.False -> acc - | Formula.Pred p -> a_st, a_op, - (p.Tree.Predicate.node, q, [(q,(if m then (ResJIT.SELF() :: ops) else ops))]) :: a_todo - | _ -> assert false - ) trans (StateSet.empty, [], []) + (fun t ((a_st, a_op, a_todo) as acc)-> + let q, _, m, f = Transition.node t in + let form, ops = eval_form auto s1 s2 f in + match Formula.expr form with + | Formula.True -> + StateSet.add q a_st, + (q, (if m then (ResJIT.SELF() :: ops) else ops)):: a_op, + a_todo + | Formula.False -> acc + | Formula.Pred p -> a_st, a_op, + (p.Tree.Predicate.node, q, [(q,(if m then (ResJIT.SELF() :: ops) else ops))]) :: a_todo + | _ -> assert false + ) trans (StateSet.empty, [], []) module L3JIT = struct - type opcode = (t -> t -> t -> Tree.t -> Tree.node -> StateSet.t * t) - - type t = opcode Cache.t Cache.t Cache.t - - let dummy _ _ _ _ _ = failwith "Uninitialized L3JIT" - - let create () = Cache.Lvl3.create 1024 dummy - - let stats fmt d = - let d = Cache.Lvl3.to_array d in - let len = Array.fold_left - (fun acc a -> - Array.fold_left (fun acc2 a2 -> Array.length a2 + acc2) acc a) 0 d - in - - let lvl1 = - Array.fold_left - (fun acc a -> if Array.length a == 0 then acc else acc+1) 0 d in - let lvl2 = Array.fold_left - (fun acc a -> - Array.fold_left (fun acc2 a2 -> if Array.length a2 == 0 then acc2 else acc2+1) - acc a) 0 d - in - let lvl3 = Array.fold_left - (fun acc a -> - Array.fold_left (fun acc2 a2 -> - Array.fold_left - (fun acc3 a3 -> if a3 == dummy then acc3 else acc3+1) acc2 a2) - acc a) 0 d - in - fprintf fmt "L3JIT Statistics: -\t%i entries -\t%i used L1 lines -\t%i used L2 lines -\t%i used L3 lines -\ttable size: %ikb\n" - len lvl1 lvl2 lvl3 (Ocaml.size_kb d) - - let find t tlist s1 s2 = - Cache.Lvl3.find t - (Uid.to_int tlist.Translist.Node.id) - (Uid.to_int s1.StateSet.Node.id) - (Uid.to_int s2.StateSet.Node.id) - - let add t tlist s1 s2 v = - Cache.Lvl3.add t - (Uid.to_int tlist.Translist.Node.id) - (Uid.to_int s1.StateSet.Node.id) - (Uid.to_int s2.StateSet.Node.id) - v - - let compile auto trl s1 s2 = - let orig_s1, orig_s2 = - Translist.fold (fun t (a1, a2) -> - let _, _, _, f = Transition.node t in - let (_, _, fs1), (_, _, fs2) = Formula.st f in - (StateSet.union s1 fs1, StateSet.union s2 fs2) - ) trl (StateSet.empty, StateSet.empty) - in - let ns1 = StateSet.inter s1 orig_s1 - and ns2 = StateSet.inter s2 orig_s2 in - let res, ops, todo = eval_trans auto ns1 ns2 trl in - let code, not_marking = ResJIT.compile ops in - let todo_code, todo_notmarking = - List.fold_left (fun (l, b) (p, q, o) -> let c, b' = ResJIT.compile o in - (p, q, c)::l, b && b') - ([], not_marking) todo - in - let opcode = res, code, todo_notmarking, todo_code in - opcode - - let gen_code auto tlist s1 s2 = - let res, code, not_marking, todo_code = compile auto tlist s1 s2 in - let f = - if todo_code == [] then - if not_marking then begin fun empty_slot sl1 sl2 _ node -> - let slot1_empty = sl1 == empty_slot - and slot2_empty = sl2 == empty_slot in - if slot1_empty && slot2_empty then res,sl2 - else - let sl = - if slot2_empty then - if slot1_empty then - Array.copy empty_slot - else sl1 - else sl2 - in - U.exec sl sl1 sl2 node code; - res, sl - end - else (* marking *) begin fun empty_slot sl1 sl2 _ node -> - let sl = - if sl2 == empty_slot then - if sl1 == empty_slot then - Array.copy empty_slot - else sl1 - else sl2 - in - U.exec sl sl1 sl2 node code; - res, sl - end - else (* todo != [] *) - begin fun empty_slot sl1 sl2 tree node -> - let sl = - if sl2 == empty_slot then - if sl1 == empty_slot then - Array.copy empty_slot - else sl1 - else sl2 - in - U.exec sl sl1 sl2 node code; - List.fold_left - (fun ares (p, q, code) -> - if !p tree node then begin - if code != ResJIT.Nil then U.exec sl sl1 sl2 node code; - StateSet.add q ares - end - else ares) res todo_code, sl - + type opcode = (t -> t -> t -> Tree.t -> Tree.node -> StateSet.t * t) + + type t = opcode Cache.Lvl3.t + + let dummy _ _ _ _ _ = failwith "Uninitialized L3JIT" + + + let show_stats a = + let count = ref 0 in + Cache.Lvl3.iteri (fun _ _ _ _ b -> if not b then incr count) a; + Logger.print err_formatter "@?L3JIT: %i used entries@\n@?" !count + let create () = + let v = Cache.Lvl3.create 1024 dummy in + if !Config.verbose then at_exit (fun () -> show_stats v); + v + + let find t tlist s1 s2 = + Cache.Lvl3.find t + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int tlist.Translist.Node.id) + + let add t tlist s1 s2 v = + Cache.Lvl3.add t + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int tlist.Translist.Node.id) + v + + let compile auto trl s1 s2 = + let orig_s1, orig_s2 = + Translist.fold (fun t (a1, a2) -> + let _, _, _, f = Transition.node t in + let fs1, fs2 = Formula.st f in + (StateSet.union a1 fs1, StateSet.union a2 fs2) + ) trl (StateSet.empty, StateSet.empty) + in + let ns1 = StateSet.inter s1 orig_s1 + and ns2 = StateSet.inter s2 orig_s2 in + let res, ops, todo = eval_trans auto ns1 ns2 trl in + let code, not_marking = ResJIT.compile ops in + let todo_code, todo_notmarking = + List.fold_left (fun (l, b) (p, q, o) -> let c, b' = ResJIT.compile o in + (p, q, c)::l, b && b') + ([], not_marking) todo + in + let opcode = res, code, todo_notmarking, todo_code in + opcode + + let choose_slot empty sl1 sl2 = + if sl1 != empty then sl1 + else if sl2 != empty then sl2 + else Array.copy empty + + let gen_code auto tlist s1 s2 = + let res, code, not_marking, todo_code = compile auto tlist s1 s2 in + let f = + if todo_code == [] then begin + if not_marking then begin fun empty_slot sl1 sl2 _ node -> + if sl1 == empty_slot && sl2 == empty_slot then res, empty_slot + else + let sl = choose_slot empty_slot sl1 sl2 in + U.exec sl sl1 sl2 node code; + res, sl + end else (* marking *) begin fun empty_slot sl1 sl2 _ node -> + let sl = choose_slot empty_slot sl1 sl2 in + U.exec sl sl1 sl2 node code; + res, sl end - in + end else (* todo_code *) begin fun empty_slot sl1 sl2 tree node -> + let sl = choose_slot empty_slot sl1 sl2 in + LOG( __ "bottom-up" 3 "Has todo code\n"); + U.exec sl sl1 sl2 node code; + List.fold_left + (fun ares (p, q, code) -> + if !p tree node then begin + if code != ResJIT.Nil then U.exec sl sl1 sl2 node code; + StateSet.add q ares + end + else ares) res todo_code, sl + end + in + f + + let cache_apply cache auto tlist s1 s2 = + let f = gen_code auto tlist s1 s2 in + LOG(__ "top-down-run" 2 "Inserting: %i, %a, %a\n%!" + (Uid.to_int tlist.Translist.Node.id) StateSet.print s1 StateSet.print s2); + if not !Config.no_cache then add cache tlist s1 s2 f; f - - let cache_apply cache auto tlist s1 s2 = - let f = gen_code auto tlist s1 s2 in - add cache tlist s1 s2 f; f end DEFINE LOOP (t, states, ctx) = ( - let _t = (t) in + let _t = t in + LOG(__ "top-down-run" 3 + "Entering node %i with loop (tag %s, context %i) with states %a" + (Node.to_int _t) + (Tag.to_string (Tree.tag tree _t)) + (Node.to_int (ctx)) + (StateSet.print) (states)); if _t == Tree.nil then nil_res else let tag = Tree.tag tree _t in @@ -197,208 +172,434 @@ DEFINE LOOP (t, states, ctx) = ( DEFINE LOOP_TAG (t, states, tag, ctx) = ( let _t = (t) in (* to avoid duplicating expression t *) + LOG(__ "top-down-run" 3 + "Entering node %i with loop_tag (tag %s, context %i) with states %a" + (Node.to_int _t) + (Tag.to_string (tag)) + (Node.to_int (ctx)) + (StateSet.print) (states)); if _t == Tree.nil then nil_res else l2jit_dispatch _t (tag) (states) (ctx) (L2JIT.find cache2 (tag) (states))) + let top_down_run auto tree root states ctx = - let res_len = (StateSet.max_elt auto.states) + 1 in + let res_len = StateSet.max_elt auto.states + 1 in let empty_slot = Array.create res_len U.NS.empty in let nil_res = auto.bottom_states, empty_slot in - let cache3 = L3JIT.create () in + let mark_subtree s subtree = + if subtree != U.NS.empty then + let r = Array.copy empty_slot in + r.(auto.last) <- subtree; + s, r + else + s, empty_slot + in + let cache3 = L3JIT.create () in let l3jit_dispatch trl s1 s2 t sl1 sl2 = - let f = L3JIT.find cache3 trl s1 s2 in - if f == L3JIT.dummy then (L3JIT.cache_apply cache3 auto trl s1 s2) empty_slot sl1 sl2 tree t - else f empty_slot sl1 sl2 tree t - + let f = L3JIT.find cache3 trl s1 s2 in + if f == L3JIT.dummy then (L3JIT.cache_apply cache3 auto trl s1 s2) empty_slot sl1 sl2 tree t + else f empty_slot sl1 sl2 tree t in let cache2 = L2JIT.create () in + let rec loop t states ctx = + if t == Tree.nil then nil_res + else + let tag = Tree.tag tree t in + l2jit_dispatch + t tag (states) (ctx) (L2JIT.find cache2 tag (states)) + and loop_tag t states ctx tag = + if t == Tree.nil then nil_res + else + l2jit_dispatch + t (tag) (states) (ctx) (L2JIT.find cache2 (tag) (states)) + + and l2jit_dispatch t tag states ctx opcode = + match opcode with + | L2JIT.RETURN () -> nil_res + | L2JIT.LEFT (tr_list, instr) -> + let res1, slot1 = + l2jit_dispatch_instr t (Tree.closing tree t) instr + in + l3jit_dispatch tr_list res1 auto.bottom_states t slot1 empty_slot + + | L2JIT.RIGHT (tr_list, instr) -> + let res2, slot2 = + l2jit_dispatch_instr t ctx instr + in + l3jit_dispatch tr_list auto.bottom_states res2 t empty_slot slot2 + + | L2JIT.BOTH (tr_list, instr1, instr2) -> + let res1, slot1 = + l2jit_dispatch_instr t (Tree.closing tree t) instr1 + in + let res2, slot2 = + l2jit_dispatch_instr t ctx instr2 + in + l3jit_dispatch tr_list res1 res2 t slot1 slot2 + | L2JIT.CACHE () -> + LOG(__ "top-down-run" 3 + "Top-down cache miss for configuration %s %a" + (Tag.to_string tag) StateSet.print states); + l2jit_dispatch t tag states ctx + (L2JIT.compile cache2 auto tree tag states) + + and l2jit_dispatch_instr t ctx instr = + LOG(__ "top-down-run" 3 "Dispatching instr: %a on node %i (context=%i)" + L2JIT.print_jump instr (Node.to_int t) (Node.to_int ctx)); + match instr with + | L2JIT.NOP _ -> nil_res + | L2JIT.FIRST_CHILD s -> loop (Tree.first_child tree t) s ctx + | L2JIT.NEXT_SIBLING s -> loop (Tree.next_sibling tree t) s ctx + + | L2JIT.FIRST_ELEMENT s -> loop (Tree.first_element tree t) s ctx + | L2JIT.NEXT_ELEMENT s -> loop (Tree.next_element tree t) s ctx + + | L2JIT.TAGGED_DESCENDANT (s, tag) -> + loop_tag (Tree.tagged_descendant tree t tag) s ctx tag + + | L2JIT.TAGGED_FOLLOWING (s, tag) -> + loop_tag (Tree.tagged_following_before tree t tag ctx) s ctx tag + + | L2JIT.SELECT_DESCENDANT (s, _, us) -> + loop (Tree.select_descendant tree t us) s ctx + + | L2JIT.SELECT_FOLLOWING (s, pt, us) -> + loop (Tree.select_following_before tree t us ctx) s ctx + + | L2JIT.TAGGED_CHILD (s, tag) -> + loop_tag (Tree.tagged_child tree t tag) s ctx tag + + | L2JIT.TAGGED_SIBLING (s, tag) -> + loop_tag (Tree.tagged_sibling tree t tag) s ctx tag + + | L2JIT.SELECT_CHILD (s, _, us) -> + loop (Tree.select_child tree t us) s ctx + + | L2JIT.SELECT_SIBLING (s, _, us) -> + loop (Tree.select_sibling tree t us) s ctx + + | L2JIT.TAGGED_SUBTREE(s, tag) -> + mark_subtree s (U.NS.subtree_tags tree t tag) + + | L2JIT.ELEMENT_SUBTREE(s) -> + mark_subtree s (U.NS.subtree_elements tree t) + in + let r = loop root states ctx in + r - let () = D_TRACE_(at_exit (fun () -> L2JIT.stats Format.err_formatter cache2)) in - - let rec l2jit_dispatch t tag states ctx opcode = - match opcode with - | L2JIT.RETURN () -> nil_res - | L2JIT.CACHE () -> - let opcode = L2JIT.compile cache2 auto tree tag states in - l2jit_dispatch t tag states ctx opcode - - | L2JIT.LEFT (tr_list, instr) -> - let res1, slot1 = - l2jit_dispatch_instr t tag states (Tree.closing tree t) instr true - in - l3jit_dispatch tr_list res1 auto.bottom_states t slot1 empty_slot + let full_top_down_run auto states tree root = + top_down_run auto tree root states (Tree.closing tree root) - | L2JIT.RIGHT (tr_list, instr) -> - let res2, slot2 = l2jit_dispatch_instr t tag states ctx instr false in - l3jit_dispatch tr_list auto.bottom_states res2 t empty_slot slot2 + let top_down_run auto tree root = + Ata.init (); + L2JIT.init(); + let res, slot = full_top_down_run auto auto.init tree root in + slot.(StateSet.min_elt auto.topdown_marking_states) - | L2JIT.BOTH (tr_list, instr1, instr2) -> - let res1, slot1 = - l2jit_dispatch_instr t tag states (Tree.closing tree t) instr1 true - in - let res2, slot2 = l2jit_dispatch_instr t tag states ctx instr2 false in - l3jit_dispatch tr_list res1 res2 t slot1 slot2 - and l2jit_dispatch_instr t tag states ctx instr _left = - match instr with - | L2JIT.NOP () -> nil_res - | L2JIT.FIRST_CHILD s -> LOOP ((Tree.first_child tree t), s, ctx) - | L2JIT.NEXT_SIBLING s -> LOOP ((Tree.next_sibling tree t), s, ctx) + (*** Bottom-up evaluation function **) - | L2JIT.FIRST_ELEMENT s -> LOOP ((Tree.first_element tree t), s, ctx) - | L2JIT.NEXT_ELEMENT s -> LOOP ((Tree.next_element tree t), s, ctx) + let eval_trans auto tree parent res1 res2 = assert false - | L2JIT.TAGGED_DESCENDANT (s, tag) -> - LOOP_TAG ((Tree.tagged_descendant tree t tag), s, tag, ctx) + let rec uniq = function + | ([] | [ _ ]) as l -> l + | e1 :: ((e2 :: ll) as l) -> if e1 == e2 then uniq l + else e1 :: e2 :: (uniq ll);; - | L2JIT.TAGGED_FOLLOWING (s, tag) -> - LOOP_TAG((Tree.tagged_following_before tree t tag ctx), s, tag, ctx) +DEFINE BOTTOM_UP_NEXT(node, rest, stop) = + (let ___fs = Tree.first_child tree node in + let ___res1 = + if ___fs == Tree.nil then nil_res + else full_top_down_run auto states tree ___fs + in + move_up node ___res1 true rest stop) - | L2JIT.SELECT_DESCENDANT (s, _, us) -> - LOOP((Tree.select_descendant tree t us), s, ctx) - | L2JIT.SELECT_FOLLOWING (s, pt, us) -> - LOOP ((Tree.select_following_before tree t us ctx), s, ctx) + let bottom_up_run auto tree (query, pat) = + let array = time ~msg:"Timing text query" (Tree.full_text_query query tree) pat in + let leaves = Array.to_list array in + let states = auto.states in + let res_len = (StateSet.max_elt states) + 1 in + let empty_slot = Array.create res_len U.NS.empty in + let nil_res = auto.bottom_states, empty_slot in + let cache = Cache.Lvl3.create 0 L3JIT.dummy in + let rec move_up node res is_left rest stop = + LOG(__ "bottom-up" 2 "move_up: node %i is_left %b stop %i\n" + (Node.to_int node) is_left (Node.to_int stop)); + if node == stop then res, rest + else + (*let prev_sibling = Tree.prev_sibling tree node in *) + let is_left' = Tree.is_first_child tree node (*prev_sibling == Tree.nil*) in + (*TODO: unsound in case of following-sibling moves + should replace the else by previous_sibling and walk up the sequence of + right child moves *) + let parent = if is_left' then Tree.parent tree node else + let p = Tree.first_child tree (Tree.parent tree node) in + if p < stop then stop else p + in + let (s1, sl1), (s2, sl2), rest' = + if is_left then match rest with + [] -> res, nil_res, rest + | next :: rest' -> + if Tree.is_right_descendant tree node next + then + let res2, rest' = (*bottom_up_next*) BOTTOM_UP_NEXT(next, rest', node) in + res, res2, rest' + else res, nil_res, rest + else + nil_res, res, rest + in + let tag = Tree.tag tree node in + let id1 = Uid.to_int s1.StateSet.Node.id in + let id2 = Uid.to_int s2.StateSet.Node.id in + let code = + let code = Cache.Lvl3.find cache id2 id1 tag in + if code == L3JIT.dummy then + let trl = + StateSet.fold + (fun q acc -> + List.fold_left (fun acc' (labels, tr) -> + if TagSet.mem tag labels + then Translist.cons tr acc' else acc') + acc + (Hashtbl.find auto.trans q) + ) + states + Translist.nil + in + LOG( __ "bottom-up" 3 "Transition list for %s, %a, %a is %a\n" + (Tag.to_string tag) + StateSet.print s1 + StateSet.print s2 + Translist.print trl + ); + let code = L3JIT.gen_code auto trl s1 s2 in + Cache.Lvl3.add cache id2 id1 tag code; code + else code + in + let res' = code empty_slot sl1 sl2 tree node in + move_up parent res' is_left' rest' stop + in + let loop_leaves l = + match l with + [] -> nil_res + | node :: ll -> + let res, lll = BOTTOM_UP_NEXT( (*bottom_up_next*) node, ll, Tree.nil) in + if lll <> [] then + Logger.print err_formatter "WARNING: Leftover nodes: %i\n" (List.length lll); + res + in + let _, slot = loop_leaves leaves in + slot.(StateSet.min_elt auto.topdown_marking_states) - | L2JIT.TAGGED_CHILD (s, tag) -> - LOOP_TAG((Tree.tagged_child tree t tag), s, tag, ctx) - | L2JIT.TAGGED_FOLLOWING_SIBLING (s, tag) -> - LOOP_TAG((Tree.tagged_following_sibling tree t tag), s, tag, ctx) - | L2JIT.SELECT_CHILD (s, _, us) -> - LOOP ((Tree.select_child tree t us), s, ctx) + (* Slow reference top-down implementation *) + let naive_top_down auto tree root states ctx = + let res_len = StateSet.max_elt auto.states + 1 in + let empty_slot = Array.create res_len U.NS.empty in + let nil_res = auto.bottom_states, empty_slot in + let cache3 = L3JIT.create () in + let l3jit_dispatch trl s1 s2 t sl1 sl2 = + let f = L3JIT.find cache3 trl s1 s2 in + if f == L3JIT.dummy then (L3JIT.cache_apply cache3 auto trl s1 s2) empty_slot sl1 sl2 tree t + else f empty_slot sl1 sl2 tree t + in + let dummy = Translist.nil, StateSet.singleton State.dummy, StateSet.singleton State.dummy in + let cache2 = Cache.Lvl2.create 512 dummy in + let rec loop t states ctx = + if states == StateSet.empty then nil_res + else if t == Tree.nil then (*StateSet.inter states auto.bottom_states, empty_slot *) nil_res + else + let tag = Tree.tag tree t in + + let trans, lstates, rstates = + let c = Cache.Lvl2.find cache2 (Uid.to_int states.StateSet.Node.id) tag in + if c == dummy then + let c = Ata.get_trans auto states tag in + Cache.Lvl2.add cache2 (Uid.to_int states.StateSet.Node.id) tag c; + c + else c + in + let s1, res1 = loop (Tree.first_child tree t) lstates ctx + and s2, res2 = loop (Tree.next_sibling tree t) rstates ctx in + l3jit_dispatch trans s1 s2 t res1 res2 + in + loop root states ctx - | L2JIT.SELECT_FOLLOWING_SIBLING (s, _, us) -> - LOOP ((Tree.select_following_sibling tree t us), s, ctx) - | L2JIT.TAGGED_SUBTREE(s, tag) -> - let count = U.NS.subtree_tags tree t tag in - if count != U.NS.empty then - let r = Array.copy empty_slot in - r.(auto.last) <- count; - s,r - else - s,empty_slot - | L2JIT.ELEMENT_SUBTREE(s) -> + let naive_top_down_run auto tree root = + let res, slot = naive_top_down auto tree root auto.init (Tree.closing tree root) in + slot.(StateSet.min_elt auto.topdown_marking_states) - let count = U.NS.subtree_elements tree t in - if count != U.NS.empty then - let r = Array.copy empty_slot in - r.(auto.last) <- count; - s,r - else - s,empty_slot - in - LOOP (root, states, ctx) - let full_top_down_run auto states tree root = - (*Ata.init (); *) - top_down_run auto tree root states (Tree.closing tree root) + let eval_form auto s1 s2 f = + let rec loop f = + match Formula.expr f with + | Formula.False | Formula.True | Formula.Pred _ -> f + | Formula.Atom(`Left, b, q) -> + Formula.of_bool (b == (StateSet.mem q s1)) + | Formula.Atom (`Right, b, q) -> + Formula.of_bool(b == (StateSet.mem q s2)) + | Formula.Atom (`Epsilon, _, _) -> assert false + + | Formula.Or(f1, f2) -> + let b1 = loop f1 in + let b2 = loop f2 in + Formula.or_pred b1 b2 + | Formula.And(f1, f2) -> + let b1 = loop f1 in + let b2 = loop f2 in + Formula.and_pred b1 b2 + in + loop f - let top_down_run auto tree root = - (*Ata.init (); *) - let res, slot = full_top_down_run auto auto.init tree root in - slot.(StateSet.min_elt auto.topdown_marking_states) + let eval_trans auto s1 s2 trans = + Translist.fold + (fun t ((a_st, mark) as acc)-> + let q, _, m, f = Transition.node t in + let form = eval_form auto s1 s2 f in + match Formula.expr form with + | Formula.True -> StateSet.add q a_st, mark || m + | Formula.False -> acc + | _ -> assert false + ) trans (StateSet.empty, false) + + + let set a i v = + LOG(__ "twopass" 2 "Setting node %i to state %a\n%!" + i StateSet.print v); + a.(i) <- v + + let twopass_top_down states_array auto tree root states ctx = + let dummy3 = StateSet.singleton State.dummy in + let cache3 = Cache.Lvl3.create 512 dummy3 in + let dummy2 = Translist.nil, StateSet.singleton State.dummy, StateSet.singleton State.dummy in + let cache2 = Cache.Lvl2.create 512 dummy2 in + let attributes = TagSet.inj_positive (Tree.attribute_tags tree) in + let rec loop t states ctx = + if t == Tree.nil then auto.bottom_states + else if states == StateSet.empty then + let () = set states_array (Node.to_int t) auto.bottom_states in + auto.bottom_states + else + let tag = Tree.tag tree t in + LOG(__ "twopass" 2 "Traversing node %i (tag %s) in states %a\n%!" (Node.to_int t) (Tag.to_string tag) + StateSet.print states + ); + let trans, lstates, rstates = + let c = Cache.Lvl2.find cache2 (Uid.to_int states.StateSet.Node.id) tag in + if c == dummy2 then + let c = Ata.get_trans ~attributes:attributes auto states tag in + Cache.Lvl2.add cache2 (Uid.to_int states.StateSet.Node.id) tag c; + c + else c + in + LOG(__ "twopass" 2 "\nTransitions are:\n%!"); + LOG(__ "twopass" 2"\nTransitions are:\n%a\n%!" + Translist.print trans + ); + let s1 = loop (Tree.first_child tree t) lstates ctx + and s2 = loop (Tree.next_sibling tree t) rstates ctx in + let st = + let c = Cache.Lvl3.find cache3 + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int trans.Translist.Node.id) + in + if c == dummy3 then + let c, _ = eval_trans auto s1 s2 trans in + Cache.Lvl3.add cache3 + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int trans.Translist.Node.id) c;c + else c + in + set states_array (Node.to_int t) st; + st + in + loop root states ctx, (dummy2, cache2) + + + type action = Nop | Mark | Dummy + + let twopass_top_down_scan states_array (dummy2, cache2) auto tree root states ctx = + let attributes = TagSet.inj_positive (Tree.attribute_tags tree) in + let cache3 = Cache.Lvl3.create 512 Dummy in + let rec loop t states acc = + if states == StateSet.empty || t = Tree.nil then acc + else + let tag = Tree.tag tree t in + let trans, _, _ = + let c = Cache.Lvl2.find cache2 (Uid.to_int states.StateSet.Node.id) tag in + if c == dummy2 then + let c = Ata.get_trans ~attributes:attributes auto states tag in + Cache.Lvl2.add cache2 (Uid.to_int states.StateSet.Node.id) tag c; + c + else c + in + let fs = Tree.first_child tree t in + let ns = Tree.next_sibling tree t in + let s1 = if fs != Tree.nil then states_array.(Node.to_int fs) else auto.bottom_states + and s2 = if ns != Tree.nil then states_array.(Node.to_int ns) else auto.bottom_states + in + let mark = + let c = Cache.Lvl3.find cache3 + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int trans.Translist.Node.id) + in + if c == Dummy then + let _, c = eval_trans auto s1 s2 trans in + let c = if c then Mark else Nop in + Cache.Lvl3.add cache3 + (Uid.to_int s1.StateSet.Node.id) + (Uid.to_int s2.StateSet.Node.id) + (Uid.to_int trans.Translist.Node.id) c;c + else c + in + LOG(__ "twopass" 2 "Evaluating node %i (tag %s).\n%!States=%a\n%!" + (Node.to_int t) + (Tag.to_string tag) + StateSet.print states + ); + LOG(__ "twopass" 2 "Translist=%a\nLeft=%a\nRight=%a\nMark=%s\n\n%!" + Translist.print trans + StateSet.print s1 + StateSet.print s2 + (match mark with + Dummy -> "Dummy" + | Mark -> "Mark" + | Nop -> "Nop")); + if mark == Mark then + loop ns s2 (loop fs s1 (U.NS.snoc acc t)) + else + loop ns s2 (loop fs s1 acc) + in + loop root states U.NS.empty + + let twopass_top_down_run auto tree root = + let len = Node.to_int (Tree.closing tree root) + 1 in + LOG(__ "twopass" 2 "Creating array of size: %i\n%!" len); + let states_array = Array.make len StateSet.empty in + let _, cache = + twopass_top_down states_array auto tree root auto.init Tree.nil + in + twopass_top_down_scan states_array cache auto tree root auto.init Tree.nil - (*** Bottom-up evaluation function **) - let ns_print fmt t = - Format.fprintf fmt "{ "; - U.NS.iter begin fun node -> - Format.fprintf fmt "%a " Node.print node; - end t; - Format.fprintf fmt "}" - let slot_print fmt t = - Array.iteri begin fun state ns -> - Format.eprintf "%a -> %a\n" State.print state ns_print ns; - end t - let eval_trans auto tree parent res1 res2 = assert false - let bottom_up_run auto tree (query, pat) = - let leaves = Array.to_list (Tree.full_text_query query tree pat) in - let states = auto.states in - let res_len = (StateSet.max_elt states) + 1 in - let empty_slot = Array.create res_len U.NS.empty in - let nil_res = auto.bottom_states, empty_slot in - let cache = Cache.Lvl3.create 1024 L3JIT.dummy in - let rec loop_leaves l acc = - match l with - [] -> acc - | node :: ll -> - let res, lll = bottom_up_next node ll Tree.nil in - if (lll <> []) then Printf.eprintf "Leftover elements\n%!"; - res - - and bottom_up_next node rest stop = - let fs = Tree.first_child tree node in - let res1 = - if fs == Tree.nil then nil_res - else full_top_down_run auto states tree fs - in - move_up node res1 true rest stop - - and move_up node res is_left rest stop = - if node == stop then res, rest - else - let prev_sibling = Tree.prev_sibling tree node in - let is_left' = prev_sibling == Tree.nil in - let real_parent = Tree.parent tree node in - let parent = - if is_left' then real_parent else max (Tree.first_child tree real_parent) stop - in - (* let parent = if is_left' then Tree.parent tree node else prev_sibling in *) - let (s1, sl1), (s2, sl2), rest' = - if is_left then match rest with - [] -> res, nil_res, rest - | next :: rest' -> - if Tree.is_right_descendant tree node next - then - let res2, rest' = bottom_up_next next rest' node in - res, res2, rest' - else res, nil_res, rest - else - nil_res, res, rest - in - let tag = Tree.tag tree node in - let id1 = Uid.to_int s1.StateSet.Node.id in - let id2 = Uid.to_int s2.StateSet.Node.id in - let code = - let code = Cache.Lvl3.find cache tag id1 id2 in - if code == L3JIT.dummy then - let trl = - StateSet.fold - (fun q acc -> - List.fold_left (fun acc' (labels, tr) -> - if labels == TagSet.any || TagSet.mem tag labels - then Translist.cons tr acc' else acc') - acc - (Hashtbl.find auto.trans q) - ) - states - Translist.nil - in - let code = L3JIT.gen_code auto trl s1 s2 in - Cache.Lvl3.add cache tag id1 id2 code; code - else code - in - let res' = code empty_slot sl1 sl2 tree node in - move_up parent res' is_left' rest' stop - in - let _, slot = loop_leaves leaves (nil_res) in - slot.(StateSet.min_elt auto.topdown_marking_states) end -