71adf56e145b28067e06c388fcfc906a95256f3c
[tatoo.git] / src / auto / eval.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                               TAToo                                 *)
4 (*                                                                     *)
5 (*                     Kim Nguyen, LRI UMR8623                         *)
6 (*                   Université Paris-Sud & CNRS                       *)
7 (*                                                                     *)
8 (*  Copyright 2010-2013 Université Paris-Sud and Centre National de la *)
9 (*  Recherche Scientifique. All rights reserved.  This file is         *)
10 (*  distributed under the terms of the GNU Lesser General Public       *)
11 (*  License, with the special exception on linking described in file   *)
12 (*  ../LICENSE.                                                        *)
13 (*                                                                     *)
14 (***********************************************************************)
15
16 (*
17   Time-stamp: <Last modified on 2013-03-14 11:12:24 CET by Kim Nguyen>
18 *)
19
20 INCLUDE "utils.ml"
21 open Format
22 open Utils
23
24 module Make (T : Tree.Sig.S) :
25   sig
26     val eval : Ata.t -> T.t -> T.node -> T.node list
27   end
28  = struct
29
30   type cache = StateSet.t Cache.N1.t
31   let get c t n = Cache.N1.find c (T.preorder t n)
32
33   let set c t n v = Cache.N1.add c (T.preorder t n) v
34
35   module Info = struct
36     type t = { is_left : bool;
37                is_right : bool;
38                has_left : bool;
39                has_right : bool;
40                kind : Tree.Common.NodeKind.t;
41              }
42     let equal a b = a = b
43     let hash  a = Hashtbl.hash a
44   end
45
46   module NodeInfo = Hcons.Make(Info)
47
48   let eval_form phi node_info fcs nss ps ss =
49     let open NodeInfo in
50     let open Info in
51     let rec loop phi =
52       begin match Ata.SFormula.expr phi with
53         Formula.True -> true
54       | Formula.False -> false
55       | Formula.Atom a ->
56           let p, b, q = Ata.Atom.node a in
57           let pos =
58             let open Ata in
59                 match p with
60                 | First_child -> StateSet.mem q fcs
61                 | Next_sibling ->  StateSet.mem q nss
62                 | Parent | Previous_sibling -> StateSet.mem q ps
63                 | Stay -> StateSet.mem q ss
64                 | Is_first_child -> node_info.node.is_left
65                 | Is_next_sibling -> node_info.node.is_right
66                 | Is k -> k == node_info.node.kind
67                 | Has_first_child -> node_info.node.has_left
68                 | Has_next_sibling -> node_info.node.has_right
69             in
70             if Ata.is_move p && (not b) then
71               eprintf "Warning: Invalid negative atom %a" Ata.Atom.print a;
72             b == pos
73       | Formula.And(phi1, phi2) -> loop phi1 && loop phi2
74       | Formula.Or (phi1, phi2) -> loop phi1 || loop phi2
75       end
76     in
77     loop phi
78
79   let eval_trans cache ltrs node_info fcs nss ps ss =
80     let j = (node_info.NodeInfo.id :> int)
81     and k = (fcs.StateSet.id :> int)
82     and l = (nss.StateSet.id :> int)
83     and m = (ps.StateSet.id :> int) in
84   let rec loop ltrs ss =
85     let i = (ltrs.Ata.TransList.id :> int)
86     and n = (ss.StateSet.id :> int) in
87     let (new_ltrs, new_ss) as res =
88       let res = Cache.N6.find cache i j k l m n in
89       if res == Cache.N6.dummy cache then
90         let res =
91           Ata.TransList.fold (fun trs (acct, accs) ->
92             let q, _, phi = Ata.Transition.node trs in
93             if StateSet.mem q accs then (acct, accs) else
94               if eval_form phi node_info fcs nss ps accs then
95                 (acct, StateSet.add q accs)
96               else
97                 (Ata.TransList.cons trs acct, accs)
98           ) ltrs (Ata.TransList.nil, ss)
99         in
100         Cache.N6.add cache i j k l m n res; res
101       else
102         res
103     in
104     if new_ss == ss then res else
105       loop new_ltrs new_ss
106   in
107   loop ltrs ss
108
109   let top_down_run auto tree node cache trans_cache2 trans_cache6  _i =
110     let redo = ref false in
111     let rec loop node =
112       if node != T.nil then begin
113         let parent = T.parent tree node in
114         let fc = T.first_child tree node in
115         let ns = T.next_sibling tree node in
116         let tag = T.tag tree node in
117         let states0 = get cache tree node in
118         let trans0 =
119           let trs =
120             Cache.N2.find trans_cache2
121               (tag.QName.id :> int) (auto.Ata.states.StateSet.id :> int)
122           in
123           if trs == Cache.N2.dummy trans_cache2 then
124             let trs = Ata.get_trans auto auto.Ata.states tag in
125             (Cache.N2.add
126               trans_cache2
127               (tag.QName.id :> int)
128               (auto.Ata.states.StateSet.id :> int) trs; trs)
129           else trs
130         in
131         let ps = get cache tree parent in
132         let fcs = get cache tree fc in
133         let nss = get cache tree ns in
134         let node_info = NodeInfo.make
135           (Info.({ is_left = node == T.first_child tree parent;
136                    is_right = node == T.next_sibling tree parent;
137                    has_left = fc != T.nil;
138                    has_right = ns != T.nil;
139                    kind = T.kind tree node }))
140         in
141         let trans1, states1 =
142           eval_trans trans_cache6 trans0 node_info fcs nss ps states0
143         in
144         if states1 != states0 then set cache tree node states1;
145         let () = loop fc in
146         let fcs1 = get cache tree fc in
147         let trans2, states2 =
148           eval_trans trans_cache6 trans1 node_info fcs1 nss ps states1
149         in
150         if states2 != states1 then set cache tree node states2;
151         let () = loop ns in
152         let _, states3 =
153           eval_trans trans_cache6 trans2 node_info fcs1 (get cache tree ns) ps states2
154         in
155         if states3 != states2 then set cache tree node states3;
156         if states0 != states3 && (not !redo) then redo := true
157       end
158     in
159     loop node;
160     !redo
161
162   let get_results auto tree node cache =
163     let rec loop node acc =
164       if node == T.nil then acc
165       else
166         let acc0 = loop (T.next_sibling tree node) acc in
167         let acc1 = loop (T.first_child tree node) acc0 in
168
169         if StateSet.intersect (get cache tree node) auto.Ata.selection_states then
170           node::acc1
171         else
172           acc1
173     in
174     loop node []
175
176   let eval auto tree node =
177     let cache = Cache.N1.create (T.size tree) StateSet.empty in
178     let redo = ref true in
179     let iter = ref 0 in
180     let dummy2 = Ata.TransList.cons
181       (Ata.Transition.make (State.dummy,QNameSet.empty, Ata.SFormula.false_))
182       Ata.TransList.nil
183     in
184     let dummy6 = (dummy2, StateSet.empty) in
185     let trans_cache6 = Cache.N6.create 17 dummy6 in
186     let trans_cache2 = Cache.N2.create 17 dummy2 in
187     let () = at_exit (fun () ->
188       let num_phi = ref 0 in
189       let num_trans = ref 0 in
190       Cache.N6.iteri (fun _ _ _ _ _ _ _ b  -> if not b then incr num_phi) trans_cache6;
191       Cache.N2.iteri (fun _ _ _ b -> if not b then incr num_trans) trans_cache2;
192       Format.eprintf "PROFILE:materialized %i transitions and %i configurations\n@." !num_trans !num_phi
193     )
194     in
195     while !redo do
196       redo := top_down_run auto tree node cache trans_cache2 trans_cache6 !iter;
197       incr iter;
198     done;
199     get_results auto tree node cache
200
201 end