Release coccinelle-0.2.3rc1
[bpt/coccinelle.git] / parsing_c / cpp_token_c.ml
CommitLineData
708f4980 1(* Yoann Padioleau
ae4735db
C
2 *
3 * Copyright (C) 2010, University of Copenhagen DIKU and INRIA.
708f4980
C
4 * Copyright (C) 2007, 2008 Ecole des Mines de Nantes
5 *
6 * This program is free software; you can redistribute it and/or
7 * modify it under the terms of the GNU General Public License (GPL)
8 * version 2 as published by the Free Software Foundation.
ae4735db 9 *
708f4980
C
10 * This program 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 * file license.txt for more details.
14 *)
15
16open Common
17
18module TH = Token_helpers
19
20open Parser_c
21open Token_views_c
22
23(*****************************************************************************)
24(* Prelude *)
25(*****************************************************************************)
26
27(* cpp functions working at the token level. Cf cpp_ast_c for cpp functions
ae4735db 28 * working at the AST level (which is very unusual but makes sense in
708f4980 29 * the coccinelle context for instance).
ae4735db 30 *
708f4980 31 * Note that as I use a single lexer to work both at the C and cpp level
ae4735db
C
32 * there are some inconveniencies.
33 * For instance 'for' is a valid name for a macro parameter and macro
34 * body, but is interpreted in a special way by our single lexer, and
708f4980
C
35 * so at some places where I expect a TIdent I need also to
36 * handle special cases and accept Tfor, Tif, etc at those places.
ae4735db 37 *
708f4980
C
38 * There are multiple issues related to those keywords incorrect tokens.
39 * Those keywords can be:
40 * - (1) in the name of the macro as in #define inline
41 * - (2) in a parameter of the macro as in #define foo(char) char x;
42 * - (3) in an argument to a macro call as in IDENT(if);
43 * Case 1 is easy to fix in define_ident.
ae4735db 44 * Case 2 is easy to fix in define_parse where detect such toks in
708f4980 45 * the parameter and then replace their occurence in the body in a Tident.
ae4735db 46 * Case 3 is only an issue when the expanded token is not really use
708f4980
C
47 * as usual but use for instance in concatenation as in a ## if
48 * when expanded. In the case the grammar this time will not be happy
49 * so this is also easy to fix in cpp_engine.
ae4735db 50 *
708f4980
C
51 *)
52
53(*****************************************************************************)
54(* Wrappers *)
55(*****************************************************************************)
ae4735db 56let pr2, pr2_once = Common.mk_pr2_wrappers Flag_parsing_c.verbose_parsing
708f4980
C
57
58(*****************************************************************************)
59(* Types *)
60(*****************************************************************************)
61
708f4980
C
62(* ------------------------------------------------------------------------- *)
63(* mimic standard.h *)
64(* ------------------------------------------------------------------------- *)
65
ae4735db
C
66type define_def = string * define_param * define_body
67 and define_param =
708f4980
C
68 | NoParam
69 | Params of string list
ae4735db 70 and define_body =
708f4980
C
71 | DefineBody of Parser_c.token list
72 | DefineHint of parsinghack_hint
73
ae4735db 74 and parsinghack_hint =
708f4980
C
75 | HintIterator
76 | HintDeclarator
77 | HintMacroString
78 | HintMacroStatement
79 | HintAttribute
80 | HintMacroIdentBuilder
81
82
978fd7e5
C
83(*****************************************************************************)
84(* Parsing and helpers of hints *)
85(*****************************************************************************)
708f4980
C
86
87(* cf also data/test.h *)
88let assoc_hint_string = [
89 "YACFE_ITERATOR" , HintIterator;
90 "YACFE_DECLARATOR" , HintDeclarator;
91 "YACFE_STRING" , HintMacroString;
92 "YACFE_STATEMENT" , HintMacroStatement;
93 "YACFE_ATTRIBUTE" , HintAttribute;
94 "YACFE_IDENT_BUILDER" , HintMacroIdentBuilder;
95
96 "MACROSTATEMENT" , HintMacroStatement; (* backward compatibility *)
97]
98
99
ae4735db 100let (parsinghack_hint_of_string: string -> parsinghack_hint option) = fun s ->
708f4980 101 Common.assoc_option s assoc_hint_string
ae4735db 102let (string_of_parsinghack_hint: parsinghack_hint -> string) = fun hint ->
978fd7e5
C
103 let assoc' = assoc_hint_string +> List.map (fun (a,b) -> (b,a) ) in
104 Common.assoc hint assoc'
105
106
708f4980 107
ae4735db 108let (is_parsinghack_hint: string -> bool) = fun s ->
708f4980
C
109 parsinghack_hint_of_string s <> None
110
ae4735db
C
111let (token_from_parsinghack_hint:
112 (string * Ast_c.info) -> parsinghack_hint -> Parser_c.token) =
708f4980
C
113 fun (s,ii) hint ->
114 match hint with
ae4735db 115 | HintIterator ->
708f4980 116 Parser_c.TMacroIterator (s, ii)
ae4735db 117 | HintDeclarator ->
708f4980 118 Parser_c.TMacroDecl (s, ii)
ae4735db 119 | HintMacroString ->
708f4980 120 Parser_c.TMacroString (s, ii)
ae4735db 121 | HintMacroStatement ->
708f4980 122 Parser_c.TMacroStmt (s, ii)
ae4735db 123 | HintAttribute ->
708f4980 124 Parser_c.TMacroAttr (s, ii)
ae4735db 125 | HintMacroIdentBuilder ->
708f4980 126 Parser_c.TMacroIdentBuilder (s, ii)
ae4735db 127
708f4980 128
978fd7e5
C
129(* used in extract_macros for example *)
130let string_of_define_def (s, params, body) =
708f4980 131
ae4735db 132 let s1 =
978fd7e5 133 match params with
ae4735db 134 | NoParam ->
978fd7e5 135 spf "#define %s " s
ae4735db 136 | Params xs ->
978fd7e5
C
137 spf "#define %s(%s) " s (Common.join "," xs)
138 in
ae4735db 139 let s2 =
978fd7e5 140 match body with
ae4735db 141 | DefineHint hint ->
978fd7e5 142 string_of_parsinghack_hint hint
ae4735db 143 | DefineBody xs ->
978fd7e5
C
144 Common.join " " (xs +> List.map Token_helpers.str_of_tok)
145 in
146 s1 ^ s2
708f4980
C
147
148
149(*****************************************************************************)
150(* Expansion helpers *)
151(*****************************************************************************)
152
ae4735db
C
153(* In some cases we can have macros like IDENT(if) that expands to some
154 * 'int xxx_if(void)', but as the lexer will currently generate a Tif for
708f4980
C
155 * the expanded code, that may not be accepted as a token after a ##
156 * in the grammar. Hence this function to remap some tokens. This is because
157 * we should not use a single lexer for both working at the C level and
158 * cpp level.
ae4735db
C
159 *
160 * update: it can also rename some TypedefIdent into TIdent, possibly
708f4980
C
161 * because of bad interaction with add_typedef_root in parsing_hacks.
162 *)
ae4735db 163let rec remap_keyword_tokens xs =
708f4980
C
164 match xs with
165 | [] -> []
166 | [x] -> [x]
ae4735db 167 | x::y::xs ->
708f4980 168 (match x, y with
ae4735db 169 | Parser_c.TCppConcatOp _, Parser_c.TIdent _ ->
708f4980 170 x::y::remap_keyword_tokens xs
ae4735db 171 | Parser_c.TIdent _, Parser_c.TCppConcatOp _ ->
708f4980
C
172 x::y::remap_keyword_tokens xs
173
ae4735db 174 | Parser_c.TCppConcatOp (i1), y ->
708f4980
C
175
176 let s = TH.str_of_tok y in
177 let ii = TH.info_of_tok y in
178 if s ==~ Common.regexp_alpha
179 then begin
978fd7e5 180 pr2 (spf "remapping: %s to an ident in expanded code" s);
708f4980
C
181 x::(Parser_c.TIdent (s, ii))::remap_keyword_tokens xs
182 end
ae4735db 183 else
708f4980
C
184 x::y::remap_keyword_tokens xs
185
ae4735db 186 | x, Parser_c.TCppConcatOp (i1) ->
708f4980
C
187 let s = TH.str_of_tok x in
188 let ii = TH.info_of_tok x in
189 if s ==~ Common.regexp_alpha
190 then begin
978fd7e5 191 pr2 (spf "remapping: %s to an ident in expanded code" s);
708f4980
C
192 (Parser_c.TIdent (s, ii))::remap_keyword_tokens (y::xs)
193 end
ae4735db 194 else
708f4980
C
195 x::y::remap_keyword_tokens xs
196
ae4735db 197 | _, _ ->
708f4980
C
198 x::remap_keyword_tokens (y::xs)
199 )
978fd7e5
C
200
201
202(* works with agglomerate_concat_op_ident below *)
ae4735db 203let rec get_ident_in_concat_op xs =
978fd7e5 204 match xs with
ae4735db 205 | [] ->
978fd7e5
C
206 pr2 "weird: ident after ## operator not found";
207 "", []
ae4735db 208 | [x] ->
978fd7e5
C
209 (match x with
210 | Parser_c.TIdent (s, i1) -> s, []
ae4735db 211 | _ ->
978fd7e5
C
212 pr2 "weird: ident after ## operator not found";
213 "", [x]
214 )
ae4735db 215 | x::y::xs ->
978fd7e5 216 (match x, y with
ae4735db 217 | Parser_c.TIdent (s,i1), Parser_c.TCppConcatOp (i2) ->
978fd7e5
C
218 let (s2, rest) = get_ident_in_concat_op xs in
219 s ^ s2, rest
ae4735db 220 | Parser_c.TIdent (s, i1), _ ->
978fd7e5 221 s, (y::xs)
ae4735db 222 | _ ->
978fd7e5
C
223 pr2 "weird: ident after ## operator not found";
224 "", x::y::xs
225 )
226
227(* must be run after the expansion has been done for the parameter so
228 * that all idents are actually ident, not macro parameter names.
229 *)
ae4735db 230let rec agglomerate_concat_op_ident xs =
978fd7e5
C
231 match xs with
232 | [] -> []
233 | [x] -> [x]
ae4735db
C
234 | x::y::xs ->
235 (* can we have ## id, and so ## as first token ? yes
978fd7e5
C
236 * but the semantic is different as it represents variadic
237 * names so this must be handled elsewhere.
238 *)
239 (match x, y with
ae4735db
C
240 | Parser_c.TIdent (s,i1), Parser_c.TCppConcatOp (i2) ->
241 let (all_str_ident, rest_toks) =
978fd7e5
C
242 get_ident_in_concat_op xs
243 in
244 let new_s = s ^ all_str_ident in
245 let i1' = Ast_c.rewrap_str new_s i1 in
246 Parser_c.TIdent (new_s, i1')::agglomerate_concat_op_ident rest_toks
ae4735db 247 | Parser_c.TCppConcatOp _, _ ->
978fd7e5
C
248 pr2 "weird, ## alone";
249 x::agglomerate_concat_op_ident (y::xs)
ae4735db 250 | _ ->
978fd7e5 251 x::agglomerate_concat_op_ident (y::xs)
ae4735db 252
978fd7e5 253 )
ae4735db
C
254
255
708f4980
C
256
257(* To expand the parameter of the macro. The env corresponds to the actual
258 * code that is binded to the parameters of the macro.
259 * Recurse ? fixpoint ? the expansion may also contain macro.
260 * Or to macro expansion in a strict manner, that is process first
261 * the parameters, expands macro in params, and then process enclosing
262 * macro call.
ae4735db 263 *
708f4980
C
264 * note: do the concatenation job of a##b here ?
265 * normally this should be done in the grammar. Here just expand
266 * tokens. The only thing we handle here is we may have to remap
267 * some tokens.
ae4735db 268 *
708f4980 269 * todo: handle stringification here ? if #n
ae4735db
C
270 *
271 * todo? but could parsing_hacks then pass over the remapped tokens,
708f4980
C
272 * for instance transform some of the back into some TypedefIdent
273 * so cpp_engine may be fooled?
274 *)
ae4735db 275let rec (cpp_engine:
978fd7e5 276 ?evaluate_concatop:bool ->
ae4735db
C
277 (string , Parser_c.token list) assoc ->
278 Parser_c.token list -> Parser_c.token list) =
978fd7e5 279 fun ?(evaluate_concatop=true) env xs ->
ae4735db 280 xs +> List.map (fun tok ->
708f4980 281 (* expand only TIdent ? no cos the parameter of the macro
ae4735db 282 * can actually be some 'register' so may have to look for
708f4980
C
283 * any tokens candidates for the expansion.
284 * Only subtelity is maybe dont expand the TDefineIdent.
ae4735db
C
285 *
286 * update: in fact now the caller (define_parse) will have done
708f4980
C
287 * the job right and already replaced the macro parameter with a TIdent.
288 *)
289 match tok with
290 | TIdent (s,i1) when List.mem_assoc s env -> Common.assoc s env
291 | x -> [x]
292 )
293 +> List.flatten
294 +> remap_keyword_tokens
ae4735db 295 +> (fun xs ->
978fd7e5
C
296 if evaluate_concatop
297 then agglomerate_concat_op_ident xs
298 else xs
ae4735db 299 )
708f4980
C
300
301
302
303(* ------------------------------------------------------------------------- *)
304(* apply macro, using standard.h or other defs *)
305(* ------------------------------------------------------------------------- *)
306
307(* Thanks to this function many stuff are not anymore hardcoded in ocaml code.
ae4735db 308 * At some point there were hardcoded in a standard.h file but now I
708f4980
C
309 * can even generate them on the fly on demand when there is actually
310 * a parsing problem.
ae4735db 311 *
708f4980
C
312 * No need to take care to not substitute the macro name itself
313 * that occurs in the macro definition because the macro name is
314 * after fix_token_define a TDefineIdent, no more a TIdent.
315 *)
316
ae4735db
C
317let rec apply_macro_defs
318 ~msg_apply_known_macro
319 ~msg_apply_known_macro_hint
978fd7e5
C
320 ?evaluate_concatop
321 ?(inplace_when_single=true)
ae4735db
C
322 defs xs =
323 let rec apply_macro_defs xs =
708f4980
C
324 match xs with
325 | [] -> ()
326
327 (* old: "but could do more, could reuse same original token
328 * so that have in the Ast a Dbg, not a MACROSTATEMENT"
ae4735db
C
329 *
330 * | PToken ({tok = TIdent (s,i1)} as id)::xs
331 * when s = "MACROSTATEMENT" ->
332 *
708f4980
C
333 * msg_macro_statement_hint s;
334 * id.tok <- TMacroStmt(TH.info_of_tok id.tok);
335 * find_macro_paren xs
ae4735db
C
336 *
337 * let msg_macro_statement_hint s =
708f4980
C
338 * incr Stat.nMacroHint;
339 * ()
ae4735db 340 *
708f4980
C
341 *)
342
343 (* recognized macro of standard.h (or other) *)
ae4735db
C
344 | PToken ({tok = TIdent (s,i1)} as id)::Parenthised (xxs,info_parens)::xs
345 when Hashtbl.mem defs s ->
346
708f4980
C
347 msg_apply_known_macro s;
348 let (s, params, body) = Hashtbl.find defs s in
349
350 (match params with
ae4735db 351 | NoParam ->
708f4980
C
352 pr2 ("WEIRD: macro without param used before parenthize: " ^ s);
353 (* ex: PRINTP("NCR53C400 card%s detected\n" ANDP(((struct ... *)
354
355 (match body with
ae4735db 356 | DefineBody bodymacro ->
708f4980
C
357 set_as_comment (Token_c.CppMacro) id;
358 id.new_tokens_before <- bodymacro;
ae4735db 359 | DefineHint hint ->
708f4980
C
360 msg_apply_known_macro_hint s;
361 id.tok <- token_from_parsinghack_hint (s,i1) hint;
362 )
ae4735db 363 | Params params ->
708f4980 364 (match body with
ae4735db 365 | DefineBody bodymacro ->
708f4980 366
ae4735db 367 (* bugfix: better to put this that before the match body,
708f4980
C
368 * cos our macrostatement hint can have variable number of
369 * arguments and so it's ok if it does not match exactly
370 * the number of arguments. *)
371 if List.length params != List.length xxs
ae4735db 372 then begin
708f4980
C
373 pr2_once ("WEIRD: macro with wrong number of arguments: " ^ s);
374 (* old: id.new_tokens_before <- bodymacro; *)
375
376 (* update: if wrong number, then I just pass this macro *)
ae4735db 377 [Parenthised (xxs, info_parens)] +>
708f4980
C
378 iter_token_paren (set_as_comment Token_c.CppMacro);
379 set_as_comment Token_c.CppMacro id;
380
381 ()
382 end
ae4735db 383 else
708f4980 384
ae4735db
C
385 let xxs' = xxs +> List.map (fun x ->
386 (tokens_of_paren_ordered x) +> List.map (fun x ->
708f4980
C
387 TH.visitor_info_of_tok Ast_c.make_expanded x.tok
388 )
389 ) in
390 id.new_tokens_before <-
391 (* !!! cpp expansion job here !!! *)
ae4735db 392 cpp_engine ?evaluate_concatop
978fd7e5 393 (Common.zip params xxs') bodymacro;
708f4980
C
394
395 (* important to do that after have apply the macro, otherwise
396 * will pass as argument to the macro some tokens that
397 * are all TCommentCpp
398 *)
ae4735db 399 [Parenthised (xxs, info_parens)] +>
708f4980
C
400 iter_token_paren (set_as_comment Token_c.CppMacro);
401 set_as_comment Token_c.CppMacro id;
402
ae4735db 403 | DefineHint (HintMacroStatement as hint) ->
708f4980
C
404 (* important to do that after have apply the macro, otherwise
405 * will pass as argument to the macro some tokens that
406 * are all TCommentCpp
ae4735db 407 *
708f4980
C
408 * note: such macrostatement can have a variable number of
409 * arguments but here we don't care, we just pass all the
410 * parameters.
411 *)
412
413 (match xs with
ae4735db
C
414 | PToken ({tok = TPtVirg _} as id2)::_ ->
415 pr2_once
708f4980
C
416 ("macro stmt with trailing ';', passing also ';' for: "^
417 s);
418 (* sometimes still want pass its params ... as in
419 * DEBUGPOLL(static unsigned int prev_mask = 0);
420 *)
421
422 msg_apply_known_macro_hint s;
423 id.tok <- token_from_parsinghack_hint (s,i1) hint;
ae4735db 424 [Parenthised (xxs, info_parens)] +>
708f4980
C
425 iter_token_paren (set_as_comment Token_c.CppMacro);
426 set_as_comment Token_c.CppMacro id2;
427
428 | _ ->
429 msg_apply_known_macro_hint s;
430 id.tok <- token_from_parsinghack_hint (s,i1) hint;
ae4735db 431 [Parenthised (xxs, info_parens)] +>
708f4980
C
432 iter_token_paren (set_as_comment Token_c.CppMacro);
433 )
708f4980 434
ae4735db
C
435
436 | DefineHint hint ->
708f4980
C
437 msg_apply_known_macro_hint s;
438 id.tok <- token_from_parsinghack_hint (s,i1) hint;
439 )
440 );
441 apply_macro_defs xs
442
ae4735db
C
443 | PToken ({tok = TIdent (s,i1)} as id)::xs
444 when Hashtbl.mem defs s ->
708f4980
C
445
446 msg_apply_known_macro s;
447 let (_s, params, body) = Hashtbl.find defs s in
448
449 (match params with
ae4735db 450 | Params params ->
708f4980
C
451 pr2 ("WEIRD: macro with params but no parens found: " ^ s);
452 (* dont apply the macro, perhaps a redefinition *)
453 ()
ae4735db 454 | NoParam ->
708f4980 455 (match body with
978fd7e5
C
456 (* bugfix: we prefer not using this special case when we come
457 * from extract_macros context
458 *)
ae4735db 459 | DefineBody [newtok] when inplace_when_single ->
708f4980 460 (* special case when 1-1 substitution, we reuse the token *)
ae4735db 461 id.tok <- (newtok +> TH.visitor_info_of_tok (fun _ ->
708f4980 462 TH.info_of_tok id.tok))
ae4735db 463 | DefineBody bodymacro ->
708f4980
C
464 set_as_comment Token_c.CppMacro id;
465 id.new_tokens_before <- bodymacro;
ae4735db 466 | DefineHint hint ->
708f4980
C
467 msg_apply_known_macro_hint s;
468 id.tok <- token_from_parsinghack_hint (s,i1) hint;
469 )
470 );
471 apply_macro_defs xs
472
473
474
475
476 (* recurse *)
ae4735db
C
477 | (PToken x)::xs -> apply_macro_defs xs
478 | (Parenthised (xxs, info_parens))::xs ->
708f4980
C
479 xxs +> List.iter apply_macro_defs;
480 apply_macro_defs xs
481 in
482 apply_macro_defs xs
483
484
485
708f4980 486(*****************************************************************************)
978fd7e5 487(* extracting define_def from a standard.h *)
708f4980 488(*****************************************************************************)
978fd7e5 489(* was the cpp-builtin, standard.h, part 0 *)
708f4980 490
ae4735db 491let macro_body_to_maybe_hint body =
708f4980
C
492 match body with
493 | [] -> DefineBody body
ae4735db 494 | [TIdent (s,i1)] ->
708f4980
C
495 (match parsinghack_hint_of_string s with
496 | Some hint -> DefineHint hint
497 | None -> DefineBody body
498 )
499 | xs -> DefineBody body
500
5636bb2c 501exception Bad_param
708f4980 502
ae4735db 503let rec (define_parse: Parser_c.token list -> (string * define_def) list) =
978fd7e5 504 fun xs ->
708f4980
C
505 match xs with
506 | [] -> []
ae4735db 507 | TDefine i1::TIdentDefine (s,i2)::TOParDefine i3::xs ->
708f4980
C
508 (* note: the macro could be badly written and have no closing ')' for
509 * its param, which would make us go too far away, but I don't think
510 * it's important to handle such an error *)
5636bb2c
C
511 let def =
512 try
513 let (tokparams, _, xs) =
514 xs +> Common.split_when (function TCPar _ -> true | _ -> false) in
515 let (body, _, xs) =
516 xs +> Common.split_when (function TDefEOL _ -> true | _ -> false) in
517 let params =
518 tokparams +> Common.map_filter (function
519 | TComma _ -> None
520 | TIdent (s, _) -> Some s
521
522 (* TODO *)
523 | TDefParamVariadic (s, _) -> Some s
524 (* TODO *)
525 | TEllipsis _ -> Some "..."
526
527 | x ->
528 (* bugfix: param of macros can be tricky *)
529 let s = TH.str_of_tok x in
530 if s ==~ Common.regexp_alpha
531 then begin
532 pr2 (spf "remapping: %s to a macro parameter" s);
533 Some s
534 end
535 else
536 begin
537 pr2 (spf "bad character %s in macro parameter list" s);
538 raise Bad_param
539 end) in
540 (* bugfix: also substitute to ident in body so cpp_engine will
541 * have an easy job.
542 *)
543 let body = body +> List.map (fun tok ->
544 match tok with
545 | TIdent _ -> tok
546 | _ ->
547 let s = TH.str_of_tok tok in
548 let ii = TH.info_of_tok tok in
549 if s ==~ Common.regexp_alpha && List.mem s params
550 then begin
551 pr2 (spf "remapping: %s to an ident in macro body" s);
552 TIdent (s, ii)
553 end
554 else tok) +>
555 List.map (TH.visitor_info_of_tok Ast_c.make_expanded) in
556 Some (s, (s, Params params, macro_body_to_maybe_hint body))
557 with Bad_param -> None in
558 (match def with
559 Some def -> def::define_parse xs
560 | None -> define_parse xs)
708f4980 561
ae4735db
C
562 | TDefine i1::TIdentDefine (s,i2)::xs ->
563 let (body, _, xs) =
708f4980 564 xs +> Common.split_when (function TDefEOL _ -> true | _ -> false) in
ae4735db 565 let body = body +> List.map
708f4980
C
566 (TH.visitor_info_of_tok Ast_c.make_expanded) in
567 let def = (s, (s, NoParam, macro_body_to_maybe_hint body)) in
568 def::define_parse xs
569
570 (* cf tests-bis/define_plus.c *)
ae4735db 571 | TDefine i1::xs ->
708f4980
C
572 let line = Ast_c.line_of_info i1 in
573 pr2 (spf "WEIRD: no ident in define at line %d" line);
574 define_parse xs
ae4735db
C
575
576 | x::xs -> define_parse xs
577
708f4980
C
578
579
ae4735db
C
580let extract_macros xs =
581 let cleaner = xs +> List.filter (fun x ->
708f4980
C
582 not (TH.is_comment x)
583 ) in
584 define_parse cleaner
708f4980
C
585
586