Release coccinelle-0.2.3rc1
[bpt/coccinelle.git] / parsing_cocci / pretty_print_cocci.ml
CommitLineData
9f8e26f4 1(*
ae4735db 2 * Copyright 2005-2010, Ecole des Mines de Nantes, University of Copenhagen
9f8e26f4
C
3 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
4 * This file is part of Coccinelle.
5 *
6 * Coccinelle is free software: you can redistribute it and/or modify
7 * it under the terms of the GNU General Public License as published by
8 * the Free Software Foundation, according to version 2 of the License.
9 *
10 * Coccinelle is distributed in the hope that it will be useful,
11 * but WITHOUT ANY WARRANTY; without even the implied warranty of
12 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13 * GNU General Public License for more details.
14 *
15 * You should have received a copy of the GNU General Public License
16 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
17 *
18 * The authors reserve the right to distribute this or future versions of
19 * Coccinelle under other licenses.
20 *)
21
22
5636bb2c
C
23(*
24 * Copyright 2005-2010, Ecole des Mines de Nantes, University of Copenhagen
25 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
26 * This file is part of Coccinelle.
27 *
28 * Coccinelle is free software: you can redistribute it and/or modify
29 * it under the terms of the GNU General Public License as published by
30 * the Free Software Foundation, according to version 2 of the License.
31 *
32 * Coccinelle is distributed in the hope that it will be useful,
33 * but WITHOUT ANY WARRANTY; without even the implied warranty of
34 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
35 * GNU General Public License for more details.
36 *
37 * You should have received a copy of the GNU General Public License
38 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
39 *
40 * The authors reserve the right to distribute this or future versions of
41 * Coccinelle under other licenses.
42 *)
43
44
34e49164
C
45open Format
46module Ast = Ast_cocci
47
48let print_plus_flag = ref true
49let print_minus_flag = ref true
50let print_newlines_disj = ref true
51
52let start_block str =
53 force_newline(); print_string " "; open_box 0
54
55let end_block str =
56 close_box(); force_newline ()
57
58let print_string_box s = print_string s; open_box 0
59
60
61let print_option = Common.do_option
62let print_between = Common.print_between
63
64(* --------------------------------------------------------------------- *)
65(* Modified code *)
66
67(* avoid polyvariance problems *)
68let anything : (Ast.anything -> unit) ref = ref (function _ -> ())
69
70let rec print_anything str = function
71 [] -> ()
72 | stream ->
73 start_block();
74 print_between force_newline
75 (function x ->
76 print_string str; open_box 0; print_anything_list x; close_box())
77 stream;
78 end_block()
79
80and print_anything_list = function
81 [] -> ()
82 | [x] -> !anything x
83 | bef::((aft::_) as rest) ->
84 !anything bef;
85 let space =
86 (match bef with
87 Ast.Rule_elemTag(_) | Ast.AssignOpTag(_) | Ast.BinaryOpTag(_)
88 | Ast.ArithOpTag(_) | Ast.LogicalOpTag(_)
89 | Ast.Token("if",_) | Ast.Token("while",_) -> true | _ -> false) or
90 (match aft with
91 Ast.Rule_elemTag(_) | Ast.AssignOpTag(_) | Ast.BinaryOpTag(_)
92 | Ast.ArithOpTag(_) | Ast.LogicalOpTag(_) | Ast.Token("{",_) -> true
93 | _ -> false) in
94 if space then print_string " ";
95 print_anything_list rest
96
97let print_around printer term = function
98 Ast.NOTHING -> printer term
951c7801
C
99 | Ast.BEFORE(bef,_) -> print_anything "<<< " bef; printer term
100 | Ast.AFTER(aft,_) -> printer term; print_anything ">>> " aft
101 | Ast.BEFOREAFTER(bef,aft,_) ->
34e49164
C
102 print_anything "<<< " bef; printer term; print_anything ">>> " aft
103
104let print_string_befaft fn x info =
c3e37e97
C
105 let print = function Ast.Noindent s | Ast.Indent s -> print_string s in
106 List.iter (function (s,_,_) -> print s; force_newline()) info.Ast.strbef;
34e49164 107 fn x;
c3e37e97 108 List.iter (function (s,_,_) -> force_newline(); print s) info.Ast.straft
34e49164
C
109
110let print_meta (r,x) = print_string r; print_string ":"; print_string x
111
112let print_pos = function
113 Ast.MetaPos(name,_,_,_,_) ->
114 let name = Ast.unwrap_mcode name in
115 print_string "@"; print_meta name
116 | _ -> ()
117
118let mcode fn = function
708f4980 119 (x, _, Ast.MINUS(_,_,adj,plus_stream), pos) ->
34e49164
C
120 if !print_minus_flag
121 then print_string (if !Flag.sgrep_mode2 then "*" else "-");
122 fn x; print_pos pos;
faf9a90c 123 if !print_plus_flag
34e49164 124 then print_anything ">>> " plus_stream
faf9a90c 125 | (x, _, Ast.CONTEXT(_,plus_streams), pos) ->
34e49164
C
126 if !print_plus_flag
127 then
128 let fn x = fn x; print_pos pos in
129 print_around fn x plus_streams
130 else (fn x; print_pos pos)
951c7801 131 | (x, info, Ast.PLUS _, pos) ->
34e49164
C
132 let fn x = fn x; print_pos pos in
133 print_string_befaft fn x info
134
faf9a90c 135let print_mcodekind = function
708f4980 136 Ast.MINUS(_,_,_,plus_stream) ->
34e49164
C
137 print_string "MINUS";
138 print_anything ">>> " plus_stream
139 | Ast.CONTEXT(_,plus_streams) ->
140 print_around (function _ -> print_string "CONTEXT") () plus_streams
951c7801 141 | Ast.PLUS _ -> print_string "PLUS"
34e49164
C
142
143(* --------------------------------------------------------------------- *)
144(* --------------------------------------------------------------------- *)
145(* Dots *)
146
147let dots between fn d =
148 match Ast.unwrap d with
149 Ast.DOTS(l) -> print_between between fn l
150 | Ast.CIRCLES(l) -> print_between between fn l
151 | Ast.STARS(l) -> print_between between fn l
152
5636bb2c
C
153let nest_dots starter ender fn f d =
154 mcode print_string starter;
155 f(); start_block();
156 (match Ast.unwrap d with
157 Ast.DOTS(l) -> print_between force_newline fn l
158 | Ast.CIRCLES(l) -> print_between force_newline fn l
159 | Ast.STARS(l) -> print_between force_newline fn l);
160 end_block();
161 mcode print_string ender
34e49164
C
162
163(* --------------------------------------------------------------------- *)
164
165let print_type keep info = function
166 None -> ()
167 (* print_string "/* ";
168 print_string "keep:"; print_unitary keep;
169 print_string " inherited:"; print_bool inherited;
170 print_string " */"*)
171 | Some ty -> ()
172 (*;
173 print_string "/* ";
174 print_between (function _ -> print_string ", ") Type_cocci.typeC ty;(*
175 print_string "keep:"; print_unitary keep;
176 print_string " inherited:"; print_bool inherited;*)
177 print_string " */"*)
178
951c7801
C
179(* --------------------------------------------------------------------- *)
180(* Contraint on Identifier and Function *)
181(* FIXME: Not called at the moment *)
182
5636bb2c
C
183let rec idconstraint = function
184 Ast.IdNoConstraint -> print_string "/* No constraint */"
185 | Ast.IdNegIdSet (str,meta) ->
186 List.iter (function s -> print_string (" "^s)) str;
187 List.iter (function (r,n) -> print_string " "; print_meta(r,n)) meta
188 | Ast.IdRegExpConstraint re -> regconstraint re
189
190and regconstraint = function
191 Ast.IdRegExp (re,_) ->
192 print_string "~= \""; print_string re; print_string "\""
193 | Ast.IdNotRegExp (re,_) ->
194 print_string "~!= \""; print_string re; print_string "\""
951c7801 195
34e49164
C
196(* --------------------------------------------------------------------- *)
197(* Identifier *)
198
199let rec ident i =
200 match Ast.unwrap i with
951c7801
C
201 Ast.Id(name) -> mcode print_string name
202 | Ast.MetaId(name,_,keep,inherited) -> mcode print_meta name
203 | Ast.MetaFunc(name,_,_,_) -> mcode print_meta name
204 | Ast.MetaLocalFunc(name,_,_,_) -> mcode print_meta name
205 | Ast.OptIdent(id) -> print_string "?"; ident id
206 | Ast.UniqueIdent(id) -> print_string "!"; ident id
34e49164
C
207
208and print_unitary = function
209 Type_cocci.Unitary -> print_string "unitary"
210 | Type_cocci.Nonunitary -> print_string "nonunitary"
211 | Type_cocci.Saved -> print_string "saved"
212
213(* --------------------------------------------------------------------- *)
214(* Expression *)
215
216let print_disj_list fn l =
217 if !print_newlines_disj
218 then (force_newline(); print_string "("; force_newline())
219 else print_string "(";
220 print_between
221 (function _ ->
222 if !print_newlines_disj
223 then (force_newline(); print_string "|"; force_newline())
224 else print_string " | ")
225 fn l;
226 if !print_newlines_disj
227 then (force_newline(); print_string ")"; force_newline())
228 else print_string ")"
229
230let rec expression e =
231 match Ast.unwrap e with
232 Ast.Ident(id) -> ident id
233 | Ast.Constant(const) -> mcode constant const
234 | Ast.FunCall(fn,lp,args,rp) ->
235 expression fn; mcode print_string_box lp;
236 dots (function _ -> ()) expression args;
237 close_box(); mcode print_string rp
238 | Ast.Assignment(left,op,right,simple) ->
239 expression left; print_string " "; mcode assignOp op;
240 print_string " "; expression right
241 | Ast.CondExpr(exp1,why,exp2,colon,exp3) ->
242 expression exp1; print_string " "; mcode print_string why;
243 print_option (function e -> print_string " "; expression e) exp2;
244 print_string " "; mcode print_string colon; expression exp3
245 | Ast.Postfix(exp,op) -> expression exp; mcode fixOp op
246 | Ast.Infix(exp,op) -> mcode fixOp op; expression exp
247 | Ast.Unary(exp,op) -> mcode unaryOp op; expression exp
248 | Ast.Binary(left,op,right) ->
249 expression left; print_string " "; mcode binaryOp op; print_string " ";
250 expression right
251 | Ast.Nested(left,op,right) ->
252 expression left; print_string " "; mcode binaryOp op; print_string " ";
253 expression right
254 | Ast.Paren(lp,exp,rp) ->
255 mcode print_string_box lp; expression exp; close_box();
256 mcode print_string rp
257 | Ast.ArrayAccess(exp1,lb,exp2,rb) ->
258 expression exp1; mcode print_string_box lb; expression exp2; close_box();
259 mcode print_string rb
260 | Ast.RecordAccess(exp,pt,field) ->
261 expression exp; mcode print_string pt; ident field
262 | Ast.RecordPtAccess(exp,ar,field) ->
263 expression exp; mcode print_string ar; ident field
264 | Ast.Cast(lp,ty,rp,exp) ->
265 mcode print_string_box lp; fullType ty; close_box();
266 mcode print_string rp; expression exp
267 | Ast.SizeOfExpr(sizeof,exp) ->
268 mcode print_string sizeof; expression exp
269 | Ast.SizeOfType(sizeof,lp,ty,rp) ->
270 mcode print_string sizeof;
271 mcode print_string_box lp; fullType ty; close_box();
272 mcode print_string rp
273 | Ast.TypeExp(ty) -> fullType ty
274
275 | Ast.MetaErr(name,_,_,_) -> mcode print_meta name
276 | Ast.MetaExpr(name,_,keep,ty,form,inherited) ->
277 mcode print_meta name; print_type keep inherited ty
278 | Ast.MetaExprList(name,_,_,_) -> mcode print_meta name
279 | Ast.EComma(cm) -> mcode print_string cm; print_space()
280 | Ast.DisjExpr(exp_list) -> print_disj_list expression exp_list
5636bb2c
C
281 | Ast.NestExpr(starter,expr_dots,ender,Some whencode,multi) ->
282 nest_dots starter ender expression
34e49164
C
283 (function _ -> print_string " when != "; expression whencode)
284 expr_dots
5636bb2c
C
285 | Ast.NestExpr(starter,expr_dots,ender,None,multi) ->
286 nest_dots starter ender expression (function _ -> ()) expr_dots
34e49164
C
287 | Ast.Edots(dots,Some whencode)
288 | Ast.Ecircles(dots,Some whencode)
289 | Ast.Estars(dots,Some whencode) ->
290 mcode print_string dots; print_string " when != "; expression whencode
291 | Ast.Edots(dots,None)
292 | Ast.Ecircles(dots,None)
293 | Ast.Estars(dots,None) -> mcode print_string dots
294 | Ast.OptExp(exp) -> print_string "?"; expression exp
295 | Ast.UniqueExp(exp) -> print_string "!"; expression exp
296
297and unaryOp = function
298 Ast.GetRef -> print_string "&"
299 | Ast.DeRef -> print_string "*"
300 | Ast.UnPlus -> print_string "+"
301 | Ast.UnMinus -> print_string "-"
302 | Ast.Tilde -> print_string "~"
303 | Ast.Not -> print_string "!"
304
305and assignOp = function
306 Ast.SimpleAssign -> print_string "="
307 | Ast.OpAssign(aop) -> arithOp aop; print_string "="
308
309and fixOp = function
310 Ast.Dec -> print_string "--"
311 | Ast.Inc -> print_string "++"
312
313and binaryOp = function
314 Ast.Arith(aop) -> arithOp aop
315 | Ast.Logical(lop) -> logicalOp lop
316
317and arithOp = function
318 Ast.Plus -> print_string "+"
319 | Ast.Minus -> print_string "-"
320 | Ast.Mul -> print_string "*"
321 | Ast.Div -> print_string "/"
322 | Ast.Mod -> print_string "%"
323 | Ast.DecLeft -> print_string "<<"
324 | Ast.DecRight -> print_string ">>"
325 | Ast.And -> print_string "&"
326 | Ast.Or -> print_string "|"
327 | Ast.Xor -> print_string "^"
328
329and logicalOp = function
330 Ast.Inf -> print_string "<"
331 | Ast.Sup -> print_string ">"
332 | Ast.InfEq -> print_string "<="
333 | Ast.SupEq -> print_string ">="
334 | Ast.Eq -> print_string "=="
335 | Ast.NotEq -> print_string "!="
336 | Ast.AndLog -> print_string "&&"
337 | Ast.OrLog -> print_string "||"
338
339and constant = function
340 Ast.String(s) -> print_string "\""; print_string s; print_string "\""
341 | Ast.Char(s) -> print_string "'"; print_string s; print_string "'"
342 | Ast.Int(s) -> print_string s
343 | Ast.Float(s) -> print_string s
344
345(* --------------------------------------------------------------------- *)
346(* Declarations *)
347
348and storage = function
349 Ast.Static -> print_string "static "
350 | Ast.Auto -> print_string "auto "
351 | Ast.Register -> print_string "register "
352 | Ast.Extern -> print_string "extern "
353
354(* --------------------------------------------------------------------- *)
355(* Types *)
356
357and fullType ft =
358 match Ast.unwrap ft with
359 Ast.Type(cv,ty) ->
360 print_option (function x -> mcode const_vol x; print_string " ") cv;
361 typeC ty
362 | Ast.DisjType(decls) -> print_disj_list fullType decls
363 | Ast.OptType(ty) -> print_string "?"; fullType ty
364 | Ast.UniqueType(ty) -> print_string "!"; fullType ty
365
366and print_function_pointer (ty,lp1,star,rp1,lp2,params,rp2) fn =
367 fullType ty; mcode print_string lp1; mcode print_string star; fn();
368 mcode print_string rp1; mcode print_string lp1;
369 parameter_list params; mcode print_string rp2
370
371and print_function_type (ty,lp1,params,rp1) fn =
372 print_option fullType ty; fn(); mcode print_string lp1;
373 parameter_list params; mcode print_string rp1
374
375and print_fninfo = function
376 Ast.FStorage(stg) -> mcode storage stg
377 | Ast.FType(ty) -> fullType ty
378 | Ast.FInline(inline) -> mcode print_string inline; print_string " "
379 | Ast.FAttr(attr) -> mcode print_string attr; print_string " "
380
381and typeC ty =
382 match Ast.unwrap ty with
faf9a90c
C
383 Ast.BaseType(ty,strings) ->
384 List.iter (function s -> mcode print_string s; print_string " ") strings
385 | Ast.SignedT(sgn,ty) -> mcode sign sgn; print_option typeC ty
34e49164
C
386 | Ast.Pointer(ty,star) -> fullType ty; mcode print_string star
387 | Ast.FunctionPointer(ty,lp1,star,rp1,lp2,params,rp2) ->
388 print_function_pointer (ty,lp1,star,rp1,lp2,params,rp2)
389 (function _ -> ())
390 | Ast.FunctionType (_,ty,lp1,params,rp1) ->
391 print_function_type (ty,lp1,params,rp1) (function _ -> ())
392 | Ast.Array(ty,lb,size,rb) ->
393 fullType ty; mcode print_string lb; print_option expression size;
394 mcode print_string rb
faf9a90c
C
395 | Ast.EnumName(kind,name) -> mcode print_string kind; print_string " ";
396 ident name
34e49164
C
397 | Ast.StructUnionName(kind,name) ->
398 mcode structUnion kind;
399 print_option (function x -> ident x; print_string " ") name
400 | Ast.StructUnionDef(ty,lb,decls,rb) ->
401 fullType ty; mcode print_string lb;
402 dots force_newline declaration decls;
403 mcode print_string rb
404 | Ast.TypeName(name) -> mcode print_string name; print_string " "
405 | Ast.MetaType(name,_,_) ->
406 mcode print_meta name; print_string " "
407
408and baseType = function
409 Ast.VoidType -> print_string "void "
410 | Ast.CharType -> print_string "char "
411 | Ast.ShortType -> print_string "short "
412 | Ast.IntType -> print_string "int "
413 | Ast.DoubleType -> print_string "double "
414 | Ast.FloatType -> print_string "float "
415 | Ast.LongType -> print_string "long "
faf9a90c 416 | Ast.LongLongType -> print_string "long long "
34e49164
C
417
418and structUnion = function
419 Ast.Struct -> print_string "struct "
420 | Ast.Union -> print_string "union "
421
422and sign = function
423 Ast.Signed -> print_string "signed "
424 | Ast.Unsigned -> print_string "unsigned "
425
426and const_vol = function
427 Ast.Const -> print_string "const"
428 | Ast.Volatile -> print_string "volatile"
429
430(* --------------------------------------------------------------------- *)
431(* Variable declaration *)
432(* Even if the Cocci program specifies a list of declarations, they are
433 split out into multiple declarations of a single variable each. *)
434
435and print_named_type ty id =
436 match Ast.unwrap ty with
437 Ast.Type(None,ty1) ->
438 (match Ast.unwrap ty1 with
439 Ast.FunctionPointer(ty,lp1,star,rp1,lp2,params,rp2) ->
440 print_function_pointer (ty,lp1,star,rp1,lp2,params,rp2)
441 (function _ -> print_string " "; ident id)
442 | Ast.FunctionType(_,ty,lp1,params,rp1) ->
443 print_function_type (ty,lp1,params,rp1)
444 (function _ -> print_string " "; ident id)
445 | Ast.Array(ty,lb,size,rb) ->
446 let rec loop ty k =
447 match Ast.unwrap ty with
448 Ast.Array(ty,lb,size,rb) ->
449 (match Ast.unwrap ty with
450 Ast.Type(None,ty) ->
451 loop ty
452 (function _ ->
453 k ();
454 mcode print_string lb;
455 print_option expression size;
456 mcode print_string rb)
457 | _ -> failwith "complex array types not supported")
458 | _ -> typeC ty; ident id; k () in
459 loop ty1 (function _ -> ())
460 | _ -> fullType ty; ident id)
461 | _ -> fullType ty; ident id
462
463and declaration d =
464 match Ast.unwrap d with
465 Ast.Init(stg,ty,id,eq,ini,sem) ->
466 print_option (mcode storage) stg; print_named_type ty id;
467 print_string " "; mcode print_string eq;
468 print_string " "; initialiser ini; mcode print_string sem
469 | Ast.UnInit(stg,ty,id,sem) ->
470 print_option (mcode storage) stg; print_named_type ty id;
471 mcode print_string sem
472 | Ast.MacroDecl(name,lp,args,rp,sem) ->
473 ident name; mcode print_string_box lp;
474 dots (function _ -> ()) expression args;
475 close_box(); mcode print_string rp; mcode print_string sem
476 | Ast.TyDecl(ty,sem) -> fullType ty; mcode print_string sem
477 | Ast.Typedef(stg,ty,id,sem) ->
478 mcode print_string stg; print_string " "; fullType ty; typeC id;
479 mcode print_string sem
480 | Ast.DisjDecl(decls) -> print_disj_list declaration decls
faf9a90c 481 | Ast.Ddots(dots,Some whencode) ->
34e49164
C
482 mcode print_string dots; print_string " when != "; declaration whencode
483 | Ast.Ddots(dots,None) -> mcode print_string dots
484 | Ast.MetaDecl(name,_,_) -> mcode print_meta name
485 | Ast.OptDecl(decl) -> print_string "?"; declaration decl
486 | Ast.UniqueDecl(decl) -> print_string "!"; declaration decl
487
488(* --------------------------------------------------------------------- *)
489(* Initialiser *)
490
491and initialiser i =
492 match Ast.unwrap i with
113803cf
C
493 Ast.MetaInit(name,_,_) ->
494 mcode print_meta name; print_string " "
495 | Ast.InitExpr(exp) -> expression exp
34e49164
C
496 | Ast.InitList(lb,initlist,rb,whencode) ->
497 mcode print_string lb; open_box 0;
498 if not (whencode = [])
499 then
500 (print_string " WHEN != ";
501 print_between (function _ -> print_string " v ")
502 initialiser whencode;
503 force_newline());
504 List.iter initialiser initlist; close_box();
505 mcode print_string rb
113803cf
C
506 | Ast.InitGccExt(designators,eq,ini) ->
507 List.iter designator designators; print_string " ";
34e49164
C
508 mcode print_string eq; print_string " "; initialiser ini
509 | Ast.InitGccName(name,eq,ini) ->
510 ident name; mcode print_string eq; initialiser ini
34e49164
C
511 | Ast.IComma(comma) -> mcode print_string comma; force_newline()
512 | Ast.OptIni(ini) -> print_string "?"; initialiser ini
513 | Ast.UniqueIni(ini) -> print_string "!"; initialiser ini
514
113803cf
C
515and designator = function
516 Ast.DesignatorField(dot,id) -> mcode print_string dot; ident id
517 | Ast.DesignatorIndex(lb,exp,rb) ->
518 mcode print_string lb; expression exp; mcode print_string rb
519 | Ast.DesignatorRange(lb,min,dots,max,rb) ->
520 mcode print_string lb; expression min; mcode print_string dots;
521 expression max; mcode print_string rb
522
34e49164
C
523(* --------------------------------------------------------------------- *)
524(* Parameter *)
525
526and parameterTypeDef p =
527 match Ast.unwrap p with
528 Ast.VoidParam(ty) -> fullType ty
529 | Ast.Param(ty,Some id) -> print_named_type ty id
530 | Ast.Param(ty,None) -> fullType ty
531 | Ast.MetaParam(name,_,_) -> mcode print_meta name
532 | Ast.MetaParamList(name,_,_,_) -> mcode print_meta name
533 | Ast.PComma(cm) -> mcode print_string cm; print_space()
534 | Ast.Pdots(dots) -> mcode print_string dots
535 | Ast.Pcircles(dots) -> mcode print_string dots
536 | Ast.OptParam(param) -> print_string "?"; parameterTypeDef param
537 | Ast.UniqueParam(param) -> print_string "!"; parameterTypeDef param
538
539and parameter_list l = dots (function _ -> ()) parameterTypeDef l
540
541(* --------------------------------------------------------------------- *)
542(* Top-level code *)
543
544let rec rule_elem arity re =
545 match Ast.unwrap re with
546 Ast.FunHeader(bef,allminus,fninfo,name,lp,params,rp) ->
547 mcode (function _ -> ()) ((),Ast.no_info,bef,Ast.NoMetaPos);
548 print_string arity; List.iter print_fninfo fninfo;
549 ident name; mcode print_string_box lp;
550 parameter_list params; close_box(); mcode print_string rp;
551 print_string " "
552 | Ast.Decl(bef,allminus,decl) ->
553 mcode (function _ -> ()) ((),Ast.no_info,bef,Ast.NoMetaPos);
554 print_string arity;
555 declaration decl
556 | Ast.SeqStart(brace) ->
557 print_string arity; mcode print_string brace;
558 if !print_newlines_disj then start_block()
559 | Ast.SeqEnd(brace) ->
560 if !print_newlines_disj then end_block();
561 print_string arity; mcode print_string brace
562 | Ast.ExprStatement(exp,sem) ->
563 print_string arity; expression exp; mcode print_string sem
564 | Ast.IfHeader(iff,lp,exp,rp) ->
565 print_string arity;
566 mcode print_string iff; print_string " "; mcode print_string_box lp;
567 expression exp; close_box(); mcode print_string rp; print_string " "
568 | Ast.Else(els) ->
569 print_string arity; mcode print_string els; print_string " "
570 | Ast.WhileHeader(whl,lp,exp,rp) ->
571 print_string arity;
572 mcode print_string whl; print_string " "; mcode print_string_box lp;
573 expression exp; close_box(); mcode print_string rp; print_string " "
574 | Ast.DoHeader(d) ->
575 print_string arity; mcode print_string d; print_string " "
576 | Ast.WhileTail(whl,lp,exp,rp,sem) ->
577 print_string arity;
578 mcode print_string whl; print_string " "; mcode print_string_box lp;
579 expression exp; close_box(); mcode print_string rp;
580 mcode print_string sem
581 | Ast.ForHeader(fr,lp,e1,sem1,e2,sem2,e3,rp) ->
582 print_string arity;
583 mcode print_string fr; mcode print_string_box lp;
584 print_option expression e1; mcode print_string sem1;
585 print_option expression e2; mcode print_string sem2;
586 print_option expression e3; close_box();
587 mcode print_string rp; print_string " "
588 | Ast.IteratorHeader(nm,lp,args,rp) ->
589 print_string arity;
590 ident nm; print_string " "; mcode print_string_box lp;
591 dots (function _ -> ()) expression args; close_box();
592 mcode print_string rp; print_string " "
593 | Ast.SwitchHeader(switch,lp,exp,rp) ->
594 print_string arity;
595 mcode print_string switch; print_string " "; mcode print_string_box lp;
596 expression exp; close_box(); mcode print_string rp; print_string " "
597 | Ast.Break(br,sem) ->
598 print_string arity; mcode print_string br; mcode print_string sem
599 | Ast.Continue(cont,sem) ->
600 print_string arity; mcode print_string cont; mcode print_string sem
601 | Ast.Label(l,dd) -> ident l; mcode print_string dd
602 | Ast.Goto(goto,l,sem) ->
603 mcode print_string goto; ident l; mcode print_string sem
604 | Ast.Return(ret,sem) ->
605 print_string arity; mcode print_string ret; mcode print_string sem
606 | Ast.ReturnExpr(ret,exp,sem) ->
607 print_string arity; mcode print_string ret; print_string " ";
608 expression exp; mcode print_string sem
609 | Ast.MetaRuleElem(name,_,_) ->
610 print_string arity; mcode print_meta name
611 | Ast.MetaStmt(name,_,_,_) ->
612 print_string arity; mcode print_meta name
613 | Ast.MetaStmtList(name,_,_) ->
614 print_string arity; mcode print_meta name
615 | Ast.Exp(exp) -> print_string arity; expression exp
616 | Ast.TopExp(exp) -> print_string arity; expression exp
617 | Ast.Ty(ty) -> print_string arity; fullType ty
1be43e12 618 | Ast.TopInit(init) -> initialiser init
34e49164
C
619 | Ast.Include(inc,s) ->
620 mcode print_string inc; print_string " "; mcode inc_file s
621 | Ast.DefineHeader(def,id,params) ->
622 mcode print_string def; print_string " "; ident id;
623 print_define_parameters params
624 | Ast.Default(def,colon) ->
625 mcode print_string def; mcode print_string colon; print_string " "
626 | Ast.Case(case,exp,colon) ->
627 mcode print_string case; print_string " "; expression exp;
628 mcode print_string colon; print_string " "
629 | Ast.DisjRuleElem(res) ->
630 print_string arity;
631 force_newline(); print_string "("; force_newline();
632 print_between
633 (function _ -> force_newline();print_string "|"; force_newline())
634 (rule_elem arity)
635 res;
636 force_newline(); print_string ")"
637
638
639and print_define_parameters params =
640 match Ast.unwrap params with
641 Ast.NoParams -> ()
642 | Ast.DParams(lp,params,rp) ->
643 mcode print_string lp;
644 dots (function _ -> ()) print_define_param params; mcode print_string rp
645
646and print_define_param param =
647 match Ast.unwrap param with
648 Ast.DParam(id) -> ident id
649 | Ast.DPComma(comma) -> mcode print_string comma
650 | Ast.DPdots(dots) -> mcode print_string dots
651 | Ast.DPcircles(circles) -> mcode print_string circles
652 | Ast.OptDParam(dp) -> print_string "?"; print_define_param dp
653 | Ast.UniqueDParam(dp) -> print_string "!"; print_define_param dp
654
655and statement arity s =
656 match Ast.unwrap s with
708f4980 657 Ast.Seq(lbrace,body,rbrace) ->
34e49164 658 rule_elem arity lbrace;
34e49164
C
659 dots force_newline (statement arity) body;
660 rule_elem arity rbrace
661 | Ast.IfThen(header,branch,(_,_,_,aft)) ->
662 rule_elem arity header; statement arity branch;
663 mcode (function _ -> ()) ((),Ast.no_info,aft,Ast.NoMetaPos)
664 | Ast.IfThenElse(header,branch1,els,branch2,(_,_,_,aft)) ->
665 rule_elem arity header; statement arity branch1; print_string " ";
666 rule_elem arity els; statement arity branch2;
667 mcode (function _ -> ()) ((),Ast.no_info,aft,Ast.NoMetaPos)
668 | Ast.While(header,body,(_,_,_,aft)) ->
669 rule_elem arity header; statement arity body;
670 mcode (function _ -> ()) ((),Ast.no_info,aft,Ast.NoMetaPos)
671 | Ast.Do(header,body,tail) ->
672 rule_elem arity header; statement arity body;
673 rule_elem arity tail
674 | Ast.For(header,body,(_,_,_,aft)) ->
675 rule_elem arity header; statement arity body;
676 mcode (function _ -> ()) ((),Ast.no_info,aft,Ast.NoMetaPos)
677 | Ast.Iterator(header,body,(_,_,_,aft)) ->
678 rule_elem arity header; statement arity body;
679 mcode (function _ -> ()) ((),Ast.no_info,aft,Ast.NoMetaPos)
fc1ad971 680 | Ast.Switch(header,lb,decls,cases,rb) ->
34e49164 681 rule_elem arity header; rule_elem arity lb;
fc1ad971 682 dots force_newline (statement arity) decls;
34e49164
C
683 List.iter (function x -> case_line arity x; force_newline()) cases;
684 rule_elem arity rb
685 | Ast.Atomic(re) -> rule_elem arity re
708f4980 686 | Ast.FunDecl(header,lbrace,body,rbrace) ->
34e49164 687 rule_elem arity header; rule_elem arity lbrace;
34e49164
C
688 dots force_newline (statement arity) body;
689 rule_elem arity rbrace
690 | Ast.Disj([stmt_dots]) ->
691 print_string arity;
692 dots (function _ -> if !print_newlines_disj then force_newline())
693 (statement arity) stmt_dots
694 | Ast.Disj(stmt_dots_list) -> (* ignores newline directive for readability *)
695 print_string arity;
696 force_newline(); print_string "("; force_newline();
697 print_between
698 (function _ -> force_newline();print_string "|"; force_newline())
699 (dots force_newline (statement arity))
700 stmt_dots_list;
701 force_newline(); print_string ")"
702 | Ast.Define(header,body) ->
703 rule_elem arity header; print_string " ";
704 dots force_newline (statement arity) body
5636bb2c 705 | Ast.Nest(starter,stmt_dots,ender,whn,multi,_,_) ->
34e49164 706 print_string arity;
5636bb2c 707 nest_dots starter ender (statement arity)
34e49164
C
708 (function _ ->
709 open_box 0;
710 print_between force_newline
711 (whencode (dots force_newline (statement "")) (statement "")) whn;
712 close_box(); force_newline())
713 stmt_dots
714 | Ast.Dots(d,whn,_,_) | Ast.Circles(d,whn,_,_) | Ast.Stars(d,whn,_,_) ->
715 print_string arity; mcode print_string d;
716 open_box 0;
717 print_between force_newline
718 (whencode (dots force_newline (statement "")) (statement "")) whn;
719 close_box(); force_newline()
720 | Ast.OptStm(s) -> statement "?" s
721 | Ast.UniqueStm(s) -> statement "!" s
722
723and print_statement_when whencode =
724 print_string " WHEN != ";
725 open_box 0;
726 print_between (function _ -> print_string " &"; force_newline())
727 (dots force_newline (statement "")) whencode;
728 close_box()
729
730
731and whencode notfn alwaysfn = function
732 Ast.WhenNot a ->
733 print_string " WHEN != "; open_box 0; notfn a; close_box()
734 | Ast.WhenAlways a ->
735 print_string " WHEN = "; open_box 0; alwaysfn a; close_box()
736 | Ast.WhenModifier x -> print_string " WHEN "; print_when_modif x
1be43e12
C
737 | Ast.WhenNotTrue a ->
738 print_string " WHEN != TRUE "; open_box 0; rule_elem "" a; close_box()
739 | Ast.WhenNotFalse a ->
740 print_string " WHEN != FALSE "; open_box 0; rule_elem "" a; close_box()
34e49164
C
741
742and print_when_modif = function
743 | Ast.WhenAny -> print_string "ANY"
744 | Ast.WhenStrict -> print_string "STRICT"
745 | Ast.WhenForall -> print_string "FORALL"
746 | Ast.WhenExists -> print_string "EXISTS"
747
748and case_line arity c =
749 match Ast.unwrap c with
750 Ast.CaseLine(header,code) ->
751 rule_elem arity header; print_string " ";
752 dots force_newline (statement arity) code
753 | Ast.OptCase(case) -> case_line "?" case
754
755(* --------------------------------------------------------------------- *)
756(* CPP code *)
757
758and inc_file = function
759 Ast.Local(elems) ->
760 print_string "\"";
761 print_between (function _ -> print_string "/") inc_elem elems;
762 print_string "\""
763 | Ast.NonLocal(elems) ->
764 print_string "<";
765 print_between (function _ -> print_string "/") inc_elem elems;
766 print_string ">"
767
768and inc_elem = function
769 Ast.IncPath s -> print_string s
770 | Ast.IncDots -> print_string "..."
771
772(* for export only *)
773let statement_dots l = dots force_newline (statement "") l
774
775let top_level t =
776 match Ast.unwrap t with
777 Ast.FILEINFO(old_file,new_file) ->
778 print_string "--- "; mcode print_string old_file; force_newline();
779 print_string "+++ "; mcode print_string new_file
780 | Ast.DECL(stmt) -> statement "" stmt
781 | Ast.CODE(stmt_dots) ->
782 dots force_newline (statement "") stmt_dots
783 | Ast.ERRORWORDS(exps) ->
784 print_string "error words = [";
785 print_between (function _ -> print_string ", ") expression exps;
786 print_string "]"
787
788let rule =
789 print_between (function _ -> force_newline(); force_newline()) top_level
790
791let pp_print_anything x = !anything x
792
793let _ =
794 anything := function
795 Ast.FullTypeTag(x) -> fullType x
796 | Ast.BaseTypeTag(x) -> baseType x
797 | Ast.StructUnionTag(x) -> structUnion x
798 | Ast.SignTag(x) -> sign x
799 | Ast.IdentTag(x) -> ident x
800 | Ast.ExpressionTag(x) -> expression x
801 | Ast.ConstantTag(x) -> constant x
802 | Ast.UnaryOpTag(x) -> unaryOp x
803 | Ast.AssignOpTag(x) -> assignOp x
804 | Ast.FixOpTag(x) -> fixOp x
805 | Ast.BinaryOpTag(x) -> binaryOp x
806 | Ast.ArithOpTag(x) -> arithOp x
807 | Ast.LogicalOpTag(x) -> logicalOp x
808 | Ast.InitTag(x) -> initialiser x
809 | Ast.DeclarationTag(x) -> declaration x
810 | Ast.StorageTag(x) -> storage x
811 | Ast.IncFileTag(x) -> inc_file x
812 | Ast.Rule_elemTag(x) -> rule_elem "" x
813 | Ast.StatementTag(x) -> statement "" x
814 | Ast.CaseLineTag(x) -> case_line "" x
815 | Ast.ConstVolTag(x) -> const_vol x
816 | Ast.Token(x,Some info) -> print_string_befaft print_string x info
817 | Ast.Token(x,None) -> print_string x
c3e37e97
C
818 | Ast.Pragma(xs) ->
819 let print = function Ast.Noindent s | Ast.Indent s -> print_string s in
820 print_between force_newline print xs
34e49164
C
821 | Ast.Code(x) -> let _ = top_level x in ()
822 | Ast.ExprDotsTag(x) -> dots (function _ -> ()) expression x
823 | Ast.ParamDotsTag(x) -> parameter_list x
824 | Ast.StmtDotsTag(x) -> dots (function _ -> ()) (statement "") x
825 | Ast.DeclDotsTag(x) -> dots (function _ -> ()) declaration x
826 | Ast.TypeCTag(x) -> typeC x
827 | Ast.ParamTag(x) -> parameterTypeDef x
828 | Ast.SgrepStartTag(x) -> print_string x
829 | Ast.SgrepEndTag(x) -> print_string x
830
831let rec dep in_and = function
832 Ast.Dep(s) -> print_string s
833 | Ast.AntiDep(s) -> print_string "!"; print_string s
834 | Ast.EverDep(s) -> print_string "ever "; print_string s
835 | Ast.NeverDep(s) -> print_string "never "; print_string s
836 | Ast.AndDep(s1,s2) ->
837 let print_and _ = dep true s1; print_string " && "; dep true s2 in
838 if in_and
839 then print_and ()
840 else (print_string "("; print_and(); print_string ")")
841 | Ast.OrDep(s1,s2) ->
842 let print_or _ = dep false s1; print_string " || "; dep false s2 in
843 if not in_and
844 then print_or ()
845 else (print_string "("; print_or(); print_string ")")
7f004419
C
846 | Ast.NoDep -> print_string "no_dep"
847 | Ast.FailDep -> print_string "fail_dep"
34e49164 848
c3e37e97
C
849let script_header str lang deps code =
850 print_string "@@";
851 force_newline();
852 print_string (str ^ ":" ^ lang);
853 (match deps with
854 Ast.NoDep -> ()
855 | _ -> print_string " depends on "; dep true deps);
856 force_newline();
857 print_string "@@";
858 force_newline();
859 print_string code;
860 force_newline()
861
34e49164
C
862let unparse z =
863 match z with
c3e37e97
C
864 Ast.InitialScriptRule (lang,deps,code) ->
865 script_header "initialize" lang deps code
866 | Ast.FinalScriptRule (lang,deps,code) ->
867 script_header "finalize" lang deps code
b1b2de81 868 | Ast.ScriptRule (lang,deps,bindings,code) ->
c3e37e97 869 script_header "script" lang deps code
faf9a90c 870 | Ast.CocciRule (nm, (deps, drops, exists), x, _, _) ->
b1b2de81
C
871 print_string "@@";
872 force_newline();
873 print_string nm;
874 (match deps with
875 Ast.NoDep -> ()
876 | _ -> print_string " depends on "; dep true deps);
34e49164
C
877 (*
878 print_string "line ";
879 print_int (Ast.get_line (List.hd x));
880 *)
b1b2de81
C
881 force_newline();
882 print_string "@@";
883 print_newlines_disj := true;
884 force_newline();
885 force_newline();
886 rule x;
887 force_newline()
34e49164
C
888
889let rule_elem_to_string x =
890 print_newlines_disj := true;
891 Common.format_to_string (function _ -> rule_elem "" x)
892
893let ident_to_string x =
894 print_newlines_disj := true;
895 Common.format_to_string (function _ -> ident x)
896
897let unparse_to_string x =
898 print_newlines_disj := true;
899 Common.format_to_string (function _ -> unparse x)
900
901let print_rule_elem re =
902 let nl = !print_newlines_disj in
903 print_newlines_disj := false;
904 rule_elem "" re;
905 print_newlines_disj := nl
906