** Language:
[bpt/coccinelle.git] / ocaml / yes_prepare_ocamlcocci.ml
CommitLineData
174d1640
C
1module Ast = Ast_cocci
2
3exception CompileFailure of string
4exception LinkFailure of string
5
aba5c457 6let ext = if Dynlink.is_native then ".cmxs" else ".cma"
174d1640 7
8babbc8f 8let sysdir () =
1eddfd50
C
9 let sysdircmd = !Flag.ocamlfind ^ " printconf stdlib" in
10 match Common.cmd_to_list sysdircmd with
11 [sysdir] -> sysdir
12 | _ -> raise (CompileFailure (sysdircmd ^" has failed"))
13
174d1640 14let check_cmd cmd =
c491d8ee
C
15 let (_,stat) = Common.cmd_to_list_and_status cmd in
16 match stat with
17 Unix.WEXITED 0 -> true
174d1640
C
18 | _ -> false
19
20let check_runtime () =
21 let has_opt = check_cmd (!Flag.ocamlc ^".opt -version 2>&1 > /dev/null") in
22 let has_c = check_cmd (!Flag.ocamlc ^" -version 2>&1 > /dev/null") in
174d1640
C
23 if has_opt then
24 begin
25 Flag.ocamlc := !Flag.ocamlc ^ ".opt";
26 Flag.ocamlopt := !Flag.ocamlopt ^ ".opt";
27 Flag.ocamldep := !Flag.ocamldep ^ ".opt";
28 Common.pr2 "Using native version of ocamlc/ocamlopt/ocamldep"
29 end
30 else
31 if has_c then
32 Common.pr2 "Using bytecode version of ocamlc/ocamlopt/ocamldep"
33 else
34 if Dynlink.is_native then
35 failwith
36 "No OCaml compiler found! Install either ocamlopt or ocamlopt.opt"
37 else
38 failwith
39 "No OCaml compiler found! Install either ocamlc or ocamlc.opt"
40
41let init_ocamlcocci _ =
42 "open Coccilib\n"
43
aba5c457
C
44let print_match ctr nm kind =
45 let endlet = "| _ -> failwith \"bad value\" in\n" in
46 let index = !ctr in
47 ctr := !ctr + 1;
48 Printf.sprintf
49 "let %s = match List.nth args %d with Coccilib.%s x -> x %s"
50 nm index kind endlet
51
52let string_rep_binding ctr = function
53 (Some nm,Ast.MetaPosDecl _) -> print_match ctr nm "Pos"
54 | (Some nm,Ast.MetaListlenDecl _) -> print_match ctr nm "Int"
55 | (Some nm,_) (* strings for everything else *) ->
56 print_match ctr nm "Str"
57 | (None,_) -> ""
58
59let ast_rep_binding ctr = function
60 (Some nm,Ast.MetaPosDecl _) ->
61 failwith
62 (Printf.sprintf "%s: No AST representation for position variables" nm)
b23ff9c7
C
63 | (Some nm,Ast.MetaMetaDecl _) ->
64 failwith
65 (Printf.sprintf
66 "%s: No AST representation for metavariables declared as \"%s\""
67 "metavariable" nm)
aba5c457
C
68 | (Some nm,Ast.MetaIdDecl _) -> print_match ctr nm "Str"
69 | (Some nm,Ast.MetaFreshIdDecl _) -> print_match ctr nm "Str"
70 | (Some nm,Ast.MetaTypeDecl _) -> print_match ctr nm "Type"
71 | (Some nm,Ast.MetaInitDecl _) -> print_match ctr nm "Init"
8f657093 72 | (Some nm,Ast.MetaInitListDecl _) -> print_match ctr nm "InitList"
aba5c457
C
73 | (Some nm,Ast.MetaListlenDecl _) ->
74 failwith
75 (Printf.sprintf "%s: No AST representation for listlen variables" nm)
76 | (Some nm,Ast.MetaParamDecl _) -> print_match ctr nm "Param"
77 | (Some nm,Ast.MetaParamListDecl _) -> print_match ctr nm "ParamList"
78 | (Some nm,Ast.MetaConstDecl _) -> print_match ctr nm "Expr"
79 | (Some nm,Ast.MetaErrDecl _) -> failwith ("not supported: "^nm)
80 | (Some nm,Ast.MetaExpDecl _) -> print_match ctr nm "Expr"
81 | (Some nm,Ast.MetaIdExpDecl _) -> print_match ctr nm "Expr"
82 | (Some nm,Ast.MetaLocalIdExpDecl _) -> print_match ctr nm "Expr"
83 | (Some nm,Ast.MetaExpListDecl _) -> print_match ctr nm "ExprList"
413ffc02
C
84 | (Some nm,Ast.MetaDeclDecl _) -> print_match ctr nm "Decl"
85 | (Some nm,Ast.MetaFieldDecl _) -> print_match ctr nm "Field"
190f1acf 86 | (Some nm,Ast.MetaFieldListDecl _) -> print_match ctr nm "FieldList"
aba5c457
C
87 | (Some nm,Ast.MetaStmDecl _) -> print_match ctr nm "Stmt"
88 | (Some nm,Ast.MetaStmListDecl _) -> failwith ("not supported: "^nm)
89 | (Some nm,Ast.MetaFuncDecl _) -> print_match ctr nm "Str"
90 | (Some nm,Ast.MetaLocalFuncDecl _) -> print_match ctr nm "Str"
91 | (Some nm,Ast.MetaDeclarerDecl _) -> print_match ctr nm "Str"
92 | (Some nm,Ast.MetaIteratorDecl _) -> print_match ctr nm "Str"
93 | (None,_) -> ""
94
413ffc02
C
95let manage_script_vars script_vars =
96 let rec loop n = function
97 [] -> ""
98 | (_,x)::xs ->
99 (Printf.sprintf "let %s = List.nth script_args %d in\n" x n) ^
100 (loop (n+1) xs) in
101 loop 0 script_vars
102
3a314143
C
103(* ---------------------------------------------------------------------- *)
104(* Iteration management *)
105
106let print_iteration_code o =
107 let translator l =
108 String.concat "\n | "
109 (List.map
110 (function x -> Printf.sprintf "%s -> \"%s\""
111 (String.capitalize x) x)
112 l) in
113 let add_virt_rules_method =
114 match !Iteration.parsed_virtual_rules with
115 [] -> ""
116 | l ->
117 Printf.sprintf "
118 method add_virtual_rule r =
119 let r = match r with %s in
120 virtual_rules <- Common.union_set [r] virtual_rules\n"
121 (translator l) in
122 let add_virt_ids_method =
123 match !Iteration.parsed_virtual_identifiers with
124 [] -> ""
125 | l ->
126 Printf.sprintf "
127 method add_virtual_identifier i v =
128 let i = match i with %s in
129 try
130 let v1 = List.assoc i virtual_identifiers in
131 if not (v = v1)
132 then failwith (\"multiple values specified for \"^i)
133 with Not_found ->
134 virtual_identifiers <- (i,v) :: virtual_identifiers"
135 (translator l) in
136 Printf.fprintf o "
137class iteration () =
138 object
139 val mutable files = None
140 val mutable files_changed = false
141 val mutable virtual_rules = ([] : string list)
142 val mutable virtual_identifiers = ([] : (string * string) list)
143 method set_files f = files <- Some f
144 %s%s
145 method register () =
146 Iteration.add_pending_instance (files,virtual_rules,virtual_identifiers)
147 end\n\n" add_virt_rules_method add_virt_ids_method
148
149(* ---------------------------------------------------------------------- *)
150
413ffc02 151let prepare_rule (name, metavars, script_vars, code) =
174d1640
C
152 let fname = String.concat "_" (Str.split (Str.regexp " ") name) in
153 (* function header *)
154 let function_header body =
413ffc02 155 Printf.sprintf "let %s args script_args =\n %s" fname body in
174d1640
C
156 (* parameter list *)
157 let build_parameter_list body =
158 let ctr = ref 0 in
aba5c457
C
159 let lets =
160 String.concat ""
161 (List.rev
162 (List.fold_left
163 (function prev ->
164 function ((str_nm,ast_nm),_,mv) ->
165 (* order important; ctr is incremented *)
166 let string_rep = string_rep_binding ctr (str_nm,mv) in
167 let ast_rep = ast_rep_binding ctr (ast_nm,mv) in
168 ast_rep :: string_rep :: prev)
169 [] metavars)) in
413ffc02 170 lets ^ (manage_script_vars script_vars) ^ body in
174d1640
C
171 (* add to hash table *)
172 let hash_add body =
173 Printf.sprintf
174 "%s\nlet _ = Hashtbl.add Coccilib.fcts \"%s\" %s\n" body name fname in
175 hash_add (function_header (build_parameter_list code))
176
177let prepare coccifile code =
178 let init_rules =
179 List.fold_left
180 (function prev ->
181 function
182 Ast_cocci.InitialScriptRule (name,"ocaml",deps,code) ->
183 code :: prev
184 | _ -> prev)
185 [] code in
186 let init_rules = List.rev init_rules in
187 let other_rules =
188 List.fold_left
189 (function prev ->
190 function
413ffc02
C
191 Ast_cocci.ScriptRule (name,"ocaml",deps,mv,script_vars,code) ->
192 (name,mv,script_vars,code) :: prev
174d1640
C
193 | Ast_cocci.InitialScriptRule (name,"ocaml",deps,code) -> prev
194 | Ast_cocci.FinalScriptRule (name,"ocaml",deps,code) ->
413ffc02 195 (name,[],[],code) :: prev
174d1640
C
196 | _ -> prev)
197 [] code in
198 let other_rules = List.rev other_rules in
199 if init_rules = [] && other_rules = []
200 then None
201 else
3a314143
C
202 begin
203 let basefile = Filename.basename (Filename.chop_extension coccifile) in
204 let basefile =
205 String.concat "_" (Str.split (Str.regexp "-") basefile) in
206 let (file,o) = Filename.open_temp_file basefile ".ml" in
174d1640 207 (* Global initialization *)
3a314143
C
208 Printf.fprintf o "%s\n" (init_ocamlcocci());
209 (* virtual rules and identifiers *)
210 (if !Iteration.parsed_virtual_rules != []
211 then
212 Printf.fprintf o "type __virtual_rules__ = %s\n\n"
213 (String.concat " | "
214 (List.map String.capitalize !Iteration.parsed_virtual_rules)));
215 (if !Iteration.parsed_virtual_identifiers != []
216 then
217 Printf.fprintf o "type __virtual_identifiers__ = %s\n\n"
218 (String.concat " | "
219 (List.map
220 (function x -> Printf.sprintf "%s" x)
221 (List.map String.capitalize
222 !Iteration.parsed_virtual_identifiers))));
223 print_iteration_code o;
174d1640
C
224 (* Semantic patch specific initialization *)
225 Printf.fprintf o "%s" (String.concat "\n\n" init_rules);
226 (* Semantic patch rules and finalizer *)
227 let rule_code = List.map prepare_rule other_rules in
3a314143
C
228 Printf.fprintf o "%s" (String.concat "\n\n" rule_code);
229 close_out o;
230 check_runtime ();
231 Some file
232 end
174d1640 233
aba5c457 234let filter_dep (accld, accinc) dep =
174d1640
C
235 match dep with
236 (* Built-in and OCaml defaults are filtered out *)
237 "Arg" | "Arith_status" | "Array" | "ArrayLabels" | "Big_int" | "Bigarray"
aba5c457
C
238 | "Buffer" | "Callback" | "CamlinternalLazy" | "CamlinternalMod"
239 | "CamlinternalOO"
240 | "Char" | "Complex" | "Condition" | "Digest" | "Dynlink" | "Event"
241 | "Filename"
242 | "Format" | "Gc" | "Genlex" | "GraphicsX11" | "Hashtbl" | "Int32"
243 | "Int64"
244 | "Lazy" | "Lexing" | "List" | "ListLabels" | "Map" | "Marshal"
245 | "MoreLabels" | "Mutex"
246 | "Nativeint" | "Num" | "Obj" | "Oo" | "Parsing" | "Pervasives"
247 | "Printexc" | "Printf"
248 | "Queue" | "Random" | "Scanf" | "Set" | "Sort" | "Stack" | "StdLabels"
249 | "Str" | "Stream"
250 | "String" | "StringLabels" | "Sys" | "ThreadUnix" | "Unix" | "UnixLabels"
174d1640
C
251 | "Weak"
252
253 (* Coccilib is filtered out too *)
3a314143
C
254 | "Coccilib" | "Common" | "Ast_c" | "Visitor_c" | "Lib_parsing_c"
255 | "Iteration" ->
aba5c457
C
256 (accld, accinc)
257
258 | "Dbm" -> ("dbm"::accld, accinc)
259 | "Graphics" -> ("graphics"::accld, accinc)
260 | "Thread" -> ("thread"::accld, accinc)
261 | "Tk" -> ("tk"::accld, accinc)
174d1640
C
262
263 | _ ->
264 let l = Char.lowercase (String.get dep 0)in
265 String.set dep 0 l;
aba5c457
C
266 (accld, dep::accinc)
267
268let get_dir p =
269 let inclcmd = !Flag.ocamlfind ^" query "^p in
270 let dir = List.hd (Common.cmd_to_list inclcmd) in
271 (dir, p)
174d1640
C
272
273let parse_dep mlfile depout =
274 let re_colon = Str.regexp_string ":" in
275 match Str.split re_colon depout with
aba5c457
C
276 _::[dep] ->
277 let deplist = Str.split (Str.regexp_string " ") dep in
278 let (libs, orderdep) = List.fold_left filter_dep ([],[]) deplist in
279 if libs <> [] || orderdep <> [] then
ca417fcf
C
280 begin
281 if check_cmd (!Flag.ocamlfind ^ " printconf 2>&1 > /dev/null")
aba5c457 282 then
ca417fcf
C
283 let packages = List.rev orderdep in
284 let inclflags = List.map get_dir packages in
285 let intlib = List.map get_dir libs in
286 let alllibs = List.rev_append intlib inclflags in
287 let plist =
288 List.fold_left (fun acc (_,p) -> acc ^" "^p) "" alllibs in
289 let flags =
290 String.concat " " (List.map (fun (d,_) -> "-I "^d) inclflags) in
291 if flags <> "" || libs <> []
292 then
293 begin
294 Common.pr2
295 ("Extra OCaml packages used in the semantic patch:"^ plist);
296 (alllibs (* , inclflags *), flags)
297 end
298 else
299 raise
300 (CompileFailure
301 ("ocamlfind did not find "^
302 (if (List.length libs + List.length orderdep) = 1
303 then "this package:"
304 else "one of these packages:")^ plist))
174d1640 305 else
aba5c457 306 raise
ca417fcf
C
307 (CompileFailure ("ocamlfind not found but "^mlfile^" uses "^dep))
308 end
aba5c457
C
309 else
310 ([] (* , [] *), "")
311 | _ ->
312 raise
313 (CompileFailure ("Wrong dependencies for "^mlfile^" (Got "^depout^")"))
413ffc02 314
174d1640
C
315let dep_flag mlfile =
316 let depcmd = !Flag.ocamldep ^" -modules "^mlfile in
aba5c457
C
317 match Common.cmd_to_list depcmd with
318 [dep] -> parse_dep mlfile dep
1eddfd50
C
319 | err ->
320 List.iter (function x -> Common.pr2 (x^"\n")) err;
321 raise (CompileFailure ("Failed ocamldep for "^mlfile))
413ffc02 322
174d1640
C
323let compile_bytecode_cmd flags mlfile =
324 let obj = (Filename.chop_extension mlfile) ^ ".cmo" in
aba5c457 325 (obj, Printf.sprintf "%s -c %s %s %s" !Flag.ocamlc obj flags mlfile)
413ffc02 326
174d1640
C
327let compile_native_cmd flags mlfile =
328 let obj = (Filename.chop_extension mlfile) ^ ".cmxs" in
aba5c457
C
329 (obj,
330 Printf.sprintf "%s -shared -o %s %s %s" !Flag.ocamlopt obj flags mlfile)
174d1640
C
331
332let compile mlfile cmd =
333 Common.pr2 cmd;
334 match Sys.command cmd with
335 0 -> ()
336 | _ -> raise (CompileFailure mlfile)
337
aba5c457
C
338let rec load_obj obj =
339 try
340 Dynlink.loadfile obj
341 with Dynlink.Error e ->
342 match e with
343 Dynlink.Unsafe_file ->
344 Dynlink.allow_unsafe_modules true;
345 load_obj obj
346 | _ ->
347 Common.pr2 (Dynlink.error_message e);
348 raise (LinkFailure obj)
349
350(*
351let link_lib (dir, name) = name ^ ext
352
353let link_libs libs =
354 String.concat " " (List.map link_lib libs)
355*)
356
357let load_lib (dir, name) =
358 let obj = dir ^ "/" ^name ^ ext in
359 Common.pr2 ("Loading "^ obj ^"...");
360 load_obj obj
361
362let load_libs libs =
363 List.iter load_lib libs
364
174d1640 365let load_file mlfile =
aba5c457
C
366 let (ldlibs (* , lklibs *), inc) = dep_flag mlfile in
367(* let linklibs = link_libs lklibs in *)
368 let flags =
369 Printf.sprintf
3a314143 370 "-thread -g -dtypes -I %s %s -I %s/globals -I %s/ocaml -I %s/parsing_c -I %s/commons "
8babbc8f 371 (sysdir ()) inc Config.path Config.path Config.path Config.path in
174d1640
C
372 let (obj, cmd) =
373 if Dynlink.is_native
374 then compile_native_cmd flags mlfile
aba5c457
C
375 else compile_bytecode_cmd flags mlfile in
376 compile mlfile cmd;
377 Common.pr2 "Compilation OK!";
378 load_libs ldlibs;
379 Common.pr2 "Loading ML code of the SP...";
380 try Dynlink.loadfile obj
381 with Dynlink.Error e ->
382 Common.pr2 (Dynlink.error_message e);
383 raise (LinkFailure obj)
174d1640
C
384
385let clean_file mlfile =
386 let basefile = Filename.chop_extension mlfile in
387 let files =
388 if Dynlink.is_native then
389 [basefile ^ ".cmxs";
390 basefile ^ ".cmx";
aba5c457
C
391 basefile ^ ".o";
392 basefile ^ ".annot"]
174d1640 393 else
aba5c457
C
394 [basefile ^ ".cmo";
395 basefile ^ ".annot"]
174d1640 396 in
993936c0 397 if not !Flag_parsing_cocci.keep_ml_script then Sys.remove mlfile;
174d1640 398 Sys.remove (basefile^".cmi");
aba5c457 399 List.iter (fun f -> try Sys.remove f with _ -> ()) files
174d1640
C
400
401(*
402 This function is used in testing.ml.
403 Once the ML file is compiled and loaded,
404 newly available functions are reported here.
405*)
406let test () =
407 Hashtbl.iter
408 (fun key fct ->
409 Common.pr2 ("Fct registered: \""^key^"\"")
410 ) Coccilib.fcts