976914a331a2869dde110272dd614c543c446c04
[bpt/coccinelle.git] / parsing_cocci / unitary_ast0.ml
1 (*
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
27 # 0 "./unitary_ast0.ml"
28 (* find unitary metavariables *)
29 module Ast0 = Ast0_cocci
30 module Ast = Ast_cocci
31 module V0 = Visitor_ast0
32 module VT0 = Visitor_ast0_types
33
34 let set_minus s minus = List.filter (function n -> not (List.mem n minus)) s
35
36 let rec nub = function
37 [] -> []
38 | (x::xs) when (List.mem x xs) -> nub xs
39 | (x::xs) -> x::(nub xs)
40
41 (* ----------------------------------------------------------------------- *)
42 (* Find the variables that occur free and occur free in a unitary way *)
43
44 (* take everything *)
45 let minus_checker name = let id = Ast0.unwrap_mcode name in [id]
46
47 (* take only what is in the plus code *)
48 let plus_checker (nm,_,_,mc,_,_) =
49 match mc with Ast0.PLUS _ -> [nm] | _ -> []
50
51 let get_free checker t =
52 let bind x y = x @ y in
53 let option_default = [] in
54
55 (* considers a single list *)
56 let collect_unitary_nonunitary free_usage =
57 let free_usage = List.sort compare free_usage in
58 let rec loop1 todrop = function
59 [] -> []
60 | (x::xs) as all -> if x = todrop then loop1 todrop xs else all in
61 let rec loop2 = function
62 [] -> ([],[])
63 | [x] -> ([x],[])
64 | x::y::xs ->
65 if x = y
66 then
67 let (unitary,non_unitary) = loop2(loop1 x xs) in
68 (unitary,x::non_unitary)
69 else
70 let (unitary,non_unitary) = loop2 (y::xs) in
71 (x::unitary,non_unitary) in
72 loop2 free_usage in
73
74 (* considers a list of lists *)
75 let detect_unitary_frees l =
76 let (unitary,nonunitary) =
77 List.split (List.map collect_unitary_nonunitary l) in
78 let unitary = nub (List.concat unitary) in
79 let nonunitary = nub (List.concat nonunitary) in
80 let unitary =
81 List.filter (function x -> not (List.mem x nonunitary)) unitary in
82 unitary@nonunitary@nonunitary in
83
84 let whencode afn bfn expression = function
85 Ast0.WhenNot(a) -> afn a
86 | Ast0.WhenAlways(b) -> bfn b
87 | Ast0.WhenModifier(_) -> option_default
88 | Ast0.WhenNotTrue(a) -> expression a
89 | Ast0.WhenNotFalse(a) -> expression a in
90
91 let ident r k i =
92 match Ast0.unwrap i with
93 Ast0.MetaId(name,_,_,_) | Ast0.MetaFunc(name,_,_)
94 | Ast0.MetaLocalFunc(name,_,_) -> checker name
95 | Ast0.DisjId(starter,id_list,mids,ender) ->
96 detect_unitary_frees(List.map r.VT0.combiner_rec_ident id_list)
97 | _ -> k i in
98
99 let expression r k e =
100 match Ast0.unwrap e with
101 Ast0.MetaErr(name,_,_) | Ast0.MetaExpr(name,_,_,_,_)
102 | Ast0.MetaExprList(name,_,_) -> checker name
103 | Ast0.DisjExpr(starter,expr_list,mids,ender) ->
104 detect_unitary_frees(List.map r.VT0.combiner_rec_expression expr_list)
105 | _ -> k e in
106
107 let typeC r k t =
108 match Ast0.unwrap t with
109 Ast0.MetaType(name,_) -> checker name
110 | Ast0.DisjType(starter,types,mids,ender) ->
111 detect_unitary_frees(List.map r.VT0.combiner_rec_typeC types)
112 | _ -> k t in
113
114 let parameter r k p =
115 match Ast0.unwrap p with
116 Ast0.MetaParam(name,_) | Ast0.MetaParamList(name,_,_) -> checker name
117 | _ -> k p in
118
119 let declaration r k d =
120 match Ast0.unwrap d with
121 Ast0.MetaDecl(name,_) | Ast0.MetaField(name,_)
122 | Ast0.MetaFieldList(name,_,_) -> checker name
123 | Ast0.DisjDecl(starter,decls,mids,ender) ->
124 detect_unitary_frees(List.map r.VT0.combiner_rec_declaration decls)
125 | _ -> k d in
126
127 let case_line r k c =
128 match Ast0.unwrap c with
129 Ast0.DisjCase(starter,case_lines,mids,ender) ->
130 detect_unitary_frees(List.map r.VT0.combiner_rec_case_line case_lines)
131 | _ -> k c in
132
133 let statement r k s =
134 match Ast0.unwrap s with
135 Ast0.MetaStmt(name,_) | Ast0.MetaStmtList(name,_) -> checker name
136 | Ast0.Disj(starter,stmt_list,mids,ender) ->
137 detect_unitary_frees
138 (List.map r.VT0.combiner_rec_statement_dots stmt_list)
139 | Ast0.Nest(starter,stmt_dots,ender,whn,multi) ->
140 bind (r.VT0.combiner_rec_statement_dots stmt_dots)
141 (detect_unitary_frees
142 (List.map
143 (whencode
144 r.VT0.combiner_rec_statement_dots
145 r.VT0.combiner_rec_statement
146 r.VT0.combiner_rec_expression)
147 whn))
148 | Ast0.Dots(d,whn) | Ast0.Circles(d,whn) | Ast0.Stars(d,whn) ->
149 detect_unitary_frees
150 (List.map
151 (whencode
152 r.VT0.combiner_rec_statement_dots r.VT0.combiner_rec_statement
153 r.VT0.combiner_rec_expression)
154 whn)
155 | _ -> k s in
156
157 let res = V0.combiner bind option_default
158 {V0.combiner_functions with
159 VT0.combiner_identfn = ident;
160 VT0.combiner_exprfn = expression;
161 VT0.combiner_tyfn = typeC;
162 VT0.combiner_paramfn = parameter;
163 VT0.combiner_declfn = declaration;
164 VT0.combiner_stmtfn = statement;
165 VT0.combiner_casefn = case_line} in
166
167 collect_unitary_nonunitary
168 (List.concat (List.map res.VT0.combiner_rec_top_level t))
169
170 (* ----------------------------------------------------------------------- *)
171 (* update the variables that are unitary *)
172
173 let update_unitary unitary =
174 let is_unitary name =
175 match (List.mem (Ast0.unwrap_mcode name) unitary,
176 !Flag.sgrep_mode2, Ast0.get_mcode_mcodekind name) with
177 (true,true,_) | (true,_,Ast0.CONTEXT(_)) -> Ast0.PureContext
178 | (true,_,_) -> Ast0.Pure
179 | (false,true,_) | (false,_,Ast0.CONTEXT(_)) -> Ast0.Context
180 | (false,_,_) -> Ast0.Impure in
181
182 let ident r k i =
183 match Ast0.unwrap i with
184 Ast0.MetaId(name,constraints,seed,_) ->
185 Ast0.rewrap i (Ast0.MetaId(name,constraints,seed,is_unitary name))
186 | Ast0.MetaFunc(name,constraints,_) ->
187 Ast0.rewrap i (Ast0.MetaFunc(name,constraints,is_unitary name))
188 | Ast0.MetaLocalFunc(name,constraints,_) ->
189 Ast0.rewrap i (Ast0.MetaLocalFunc(name,constraints,is_unitary name))
190 | _ -> k i in
191
192 let expression r k e =
193 match Ast0.unwrap e with
194 Ast0.MetaErr(name,constraints,_) ->
195 Ast0.rewrap e (Ast0.MetaErr(name,constraints,is_unitary name))
196 | Ast0.MetaExpr(name,constraints,ty,form,_) ->
197 Ast0.rewrap e (Ast0.MetaExpr(name,constraints,ty,form,is_unitary name))
198 | Ast0.MetaExprList(name,lenname,_) ->
199 Ast0.rewrap e (Ast0.MetaExprList(name,lenname,is_unitary name))
200 | _ -> k e in
201
202 let typeC r k t =
203 match Ast0.unwrap t with
204 Ast0.MetaType(name,_) ->
205 Ast0.rewrap t (Ast0.MetaType(name,is_unitary name))
206 | _ -> k t in
207
208 let parameter r k p =
209 match Ast0.unwrap p with
210 Ast0.MetaParam(name,_) ->
211 Ast0.rewrap p (Ast0.MetaParam(name,is_unitary name))
212 | Ast0.MetaParamList(name,lenname,_) ->
213 Ast0.rewrap p (Ast0.MetaParamList(name,lenname,is_unitary name))
214 | _ -> k p in
215
216 let statement r k s =
217 match Ast0.unwrap s with
218 Ast0.MetaStmt(name,_) ->
219 Ast0.rewrap s (Ast0.MetaStmt(name,is_unitary name))
220 | Ast0.MetaStmtList(name,_) ->
221 Ast0.rewrap s (Ast0.MetaStmtList(name,is_unitary name))
222 | _ -> k s in
223
224 let res = V0.rebuilder
225 {V0.rebuilder_functions with
226 VT0.rebuilder_identfn = ident;
227 VT0.rebuilder_exprfn = expression;
228 VT0.rebuilder_tyfn = typeC;
229 VT0.rebuilder_paramfn = parameter;
230 VT0.rebuilder_stmtfn = statement} in
231
232 List.map res.VT0.rebuilder_rec_top_level
233
234 (* ----------------------------------------------------------------------- *)
235
236 let rec split3 = function
237 [] -> ([],[],[])
238 | (a,b,c)::xs -> let (l1,l2,l3) = split3 xs in (a::l1,b::l2,c::l3)
239
240 let rec combine3 = function
241 ([],[],[]) -> []
242 | (a::l1,b::l2,c::l3) -> (a,b,c) :: combine3 (l1,l2,l3)
243 | _ -> failwith "not possible"
244
245 (* ----------------------------------------------------------------------- *)
246 (* process all rules *)
247
248 let do_unitary rules =
249 let rec loop = function
250 [] -> ([],[])
251 | (r::rules) ->
252 match r with
253 Ast0.ScriptRule (_,_,_,_,_,_)
254 | Ast0.InitialScriptRule (_,_,_,_) | Ast0.FinalScriptRule (_,_,_,_) ->
255 let (x,rules) = loop rules in
256 (x, r::rules)
257 | Ast0.CocciRule ((minus,metavars,chosen_isos),((plus,_) as plusz),rt) ->
258 let mm1 = List.map Ast.get_meta_name metavars in
259 let (used_after, rest) = loop rules in
260 let (m_unitary, m_nonunitary) = get_free minus_checker minus in
261 let (p_unitary, p_nonunitary) = get_free plus_checker plus in
262 let p_free =
263 if !Flag.sgrep_mode2 then []
264 else p_unitary @ p_nonunitary in
265 let (in_p, m_unitary) =
266 List.partition (function x -> List.mem x p_free) m_unitary in
267 let m_nonunitary = in_p @ m_nonunitary in
268 let (m_unitary, not_local) =
269 List.partition (function x -> List.mem x mm1) m_unitary in
270 let m_unitary =
271 List.filter (function x -> not (List.mem x used_after))
272 m_unitary in
273 let rebuilt = update_unitary m_unitary minus in
274 (set_minus (m_nonunitary @ used_after) mm1,
275 (Ast0.CocciRule
276 ((rebuilt, metavars, chosen_isos),plusz,rt))::rest) in
277 let (_,rules) = loop rules in
278 rules
279
280 (*
281 let do_unitary minus plus =
282 let (minus,metavars,chosen_isos) = split3 minus in
283 let (plus,_) = List.split plus in
284 let rec loop = function
285 ([],[],[]) -> ([],[])
286 | (mm1::metavars,m1::minus,p1::plus) ->
287 let mm1 = List.map Ast.get_meta_name mm1 in
288 let (used_after,rest) = loop (metavars,minus,plus) in
289 let (m_unitary,m_nonunitary) = get_free minus_checker m1 in
290 let (p_unitary,p_nonunitary) = get_free plus_checker p1 in
291 let p_free =
292 if !Flag.sgrep_mode2
293 then []
294 else p_unitary @ p_nonunitary in
295 let (in_p,m_unitary) =
296 List.partition (function x -> List.mem x p_free) m_unitary in
297 let m_nonunitary = in_p@m_nonunitary in
298 let (m_unitary,not_local) =
299 List.partition (function x -> List.mem x mm1) m_unitary in
300 let m_unitary =
301 List.filter (function x -> not(List.mem x used_after)) m_unitary in
302 let rebuilt = update_unitary m_unitary m1 in
303 (set_minus (m_nonunitary @ used_after) mm1,
304 rebuilt::rest)
305 | _ -> failwith "not possible" in
306 let (_,rules) = loop (metavars,minus,plus) in
307 combine3 (rules,metavars,chosen_isos)
308 *)