835fa8cb87d93bf6148e891eb2605e261e354b75
[bpt/coccinelle.git] / parsing_c / parsing_hacks.ml
1 (* Yoann Padioleau
2 *
3 * Copyright (C) 2010, University of Copenhagen DIKU and INRIA.
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.
9 *
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
16 open Common
17
18 module TH = Token_helpers
19 module TV = Token_views_c
20 module LP = Lexer_parser
21
22 module Stat = Parsing_stat
23
24 open Parser_c
25
26 open TV
27
28 (*****************************************************************************)
29 (* Some debugging functions *)
30 (*****************************************************************************)
31
32 let pr2, pr2_once = Common.mk_pr2_wrappers Flag_parsing_c.verbose_parsing
33
34 let pr2_cpp s =
35 if !Flag_parsing_c.debug_cpp
36 then Common.pr2_once ("CPP-" ^ s)
37
38
39 let msg_gen cond is_known printer s =
40 if cond
41 then
42 if not (!Flag_parsing_c.filter_msg)
43 then printer s
44 else
45 if not (is_known s)
46 then printer s
47
48
49 (* In the following, there are some harcoded names of types or macros
50 * but they are not used by our heuristics! They are just here to
51 * enable to detect false positive by printing only the typedef/macros
52 * that we don't know yet. If we print everything, then we can easily
53 * get lost with too much verbose tracing information. So those
54 * functions "filter" some messages. So our heuristics are still good,
55 * there is no more (or not that much) hardcoded linux stuff.
56 *)
57
58 let is_known_typdef =
59 (fun s ->
60 (match s with
61 | "u_char" | "u_short" | "u_int" | "u_long"
62 | "u8" | "u16" | "u32" | "u64"
63 | "s8" | "s16" | "s32" | "s64"
64 | "__u8" | "__u16" | "__u32" | "__u64"
65 -> true
66
67 | "acpi_handle"
68 | "acpi_status"
69 -> true
70
71 | "FILE"
72 | "DIR"
73 -> true
74
75 | s when s =~ ".*_t$" -> true
76 | _ -> false
77 )
78 )
79
80 (* note: cant use partial application with let msg_typedef =
81 * because it would compute msg_typedef at compile time when
82 * the flag debug_typedef is always false
83 *)
84 let msg_typedef s =
85 incr Stat.nTypedefInfer;
86 msg_gen (!Flag_parsing_c.debug_typedef)
87 is_known_typdef
88 (fun s ->
89 pr2_cpp ("TYPEDEF: promoting: " ^ s)
90 )
91 s
92
93 let msg_maybe_dangereous_typedef s =
94 if not (is_known_typdef s)
95 then
96 pr2
97 ("PB MAYBE: dangerous typedef inference, maybe not a typedef: " ^ s)
98
99
100
101 let msg_declare_macro s =
102 incr Stat.nMacroDecl;
103 msg_gen (!Flag_parsing_c.debug_cpp)
104 (fun s ->
105 (match s with
106 | "DECLARE_MUTEX" | "DECLARE_COMPLETION" | "DECLARE_RWSEM"
107 | "DECLARE_WAITQUEUE" | "DECLARE_WAIT_QUEUE_HEAD"
108 | "DEFINE_SPINLOCK" | "DEFINE_TIMER"
109 | "DEVICE_ATTR" | "CLASS_DEVICE_ATTR" | "DRIVER_ATTR"
110 | "SENSOR_DEVICE_ATTR"
111 | "LIST_HEAD"
112 | "DECLARE_WORK" | "DECLARE_TASKLET"
113 | "PORT_ATTR_RO" | "PORT_PMA_ATTR"
114 | "DECLARE_BITMAP"
115
116 -> true
117 (*
118 | s when s =~ "^DECLARE_.*" -> true
119 | s when s =~ ".*_ATTR$" -> true
120 | s when s =~ "^DEFINE_.*" -> true
121 *)
122
123 | _ -> false
124 )
125 )
126 (fun s -> pr2_cpp ("MACRO: found declare-macro: " ^ s))
127 s
128
129
130 let msg_foreach s =
131 incr Stat.nIteratorHeuristic;
132 pr2_cpp ("MACRO: found foreach: " ^ s)
133
134
135 (* ??
136 let msg_debug_macro s =
137 pr2_cpp ("MACRO: found debug-macro: " ^ s)
138 *)
139
140
141 let msg_macro_noptvirg s =
142 incr Stat.nMacroStmt;
143 pr2_cpp ("MACRO: found macro with param noptvirg: " ^ s)
144
145 let msg_macro_toplevel_noptvirg s =
146 incr Stat.nMacroStmt;
147 pr2_cpp ("MACRO: found toplevel macro noptvirg: " ^ s)
148
149 let msg_macro_noptvirg_single s =
150 incr Stat.nMacroStmt;
151 pr2_cpp ("MACRO: found single-macro noptvirg: " ^ s)
152
153
154
155
156 let msg_macro_higher_order s =
157 incr Stat.nMacroHigherOrder;
158 msg_gen (!Flag_parsing_c.debug_cpp)
159 (fun s ->
160 (match s with
161 | "DBGINFO"
162 | "DBGPX"
163 | "DFLOW"
164 -> true
165 | _ -> false
166 )
167 )
168 (fun s -> pr2_cpp ("MACRO: found higher ordre macro : " ^ s))
169 s
170
171
172 let msg_stringification s =
173 incr Stat.nMacroString;
174 msg_gen (!Flag_parsing_c.debug_cpp)
175 (fun s ->
176 (match s with
177 | "REVISION"
178 | "UTS_RELEASE"
179 | "SIZE_STR"
180 | "DMA_STR"
181 -> true
182 (* s when s =~ ".*STR.*" -> true *)
183 | _ -> false
184 )
185 )
186 (fun s -> pr2_cpp ("MACRO: found string-macro " ^ s))
187 s
188
189 let msg_stringification_params s =
190 incr Stat.nMacroString;
191 pr2_cpp ("MACRO: string-macro with params : " ^ s)
192
193
194
195 let msg_apply_known_macro s =
196 incr Stat.nMacroExpand;
197 pr2_cpp ("MACRO: found known macro = " ^ s)
198
199 let msg_apply_known_macro_hint s =
200 incr Stat.nMacroHint;
201 pr2_cpp ("MACRO: found known macro hint = " ^ s)
202
203
204
205
206 let msg_ifdef_bool_passing is_ifdef_positif =
207 incr Stat.nIfdefZero; (* of Version ? *)
208 if is_ifdef_positif
209 then pr2_cpp "commenting parts of a #if 1 or #if LINUX_VERSION"
210 else pr2_cpp "commenting a #if 0 or #if LINUX_VERSION or __cplusplus"
211
212
213 let msg_ifdef_mid_something () =
214 incr Stat.nIfdefExprPassing;
215 pr2_cpp "found ifdef-mid-something"
216
217 let msg_ifdef_funheaders () =
218 incr Stat.nIfdefFunheader;
219 ()
220
221 let msg_ifdef_cparen_else () =
222 incr Stat.nIfdefPassing;
223 pr2_cpp("found ifdef-cparen-else")
224
225
226 let msg_attribute s =
227 incr Stat.nMacroAttribute;
228 pr2_cpp("ATTR:" ^ s)
229
230
231
232 (*****************************************************************************)
233 (* The regexp and basic view definitions *)
234 (*****************************************************************************)
235
236 (* opti: better to built then once and for all, especially regexp_foreach *)
237
238 let regexp_macro = Str.regexp
239 "^[A-Z_][A-Z_0-9]*$"
240
241 (* linuxext: *)
242 let regexp_annot = Str.regexp
243 "^__.*$"
244
245 (* linuxext: *)
246 let regexp_declare = Str.regexp
247 ".*DECLARE.*"
248
249 (* linuxext: *)
250 let regexp_foreach = Str.regexp_case_fold
251 ".*\\(for_?each\\|for_?all\\|iterate\\|loop\\|walk\\|scan\\|each\\|for\\)"
252
253 let regexp_typedef = Str.regexp
254 ".*_t$"
255
256 let false_typedef = [
257 "printk";
258 ]
259
260
261 let ok_typedef s = not (List.mem s false_typedef)
262
263 let not_annot s =
264 not (s ==~ regexp_annot)
265
266
267
268
269 (*****************************************************************************)
270 (* Helpers *)
271 (*****************************************************************************)
272
273 (* ------------------------------------------------------------------------- *)
274 (* the pair is the status of '()' and '{}', ex: (-1,0)
275 * if too much ')' and good '{}'
276 * could do for [] too ?
277 * could do for ',' if encounter ',' at "toplevel", not inside () or {}
278 * then if have ifdef, then certainly can lead to a problem.
279 *)
280 let (count_open_close_stuff_ifdef_clause: TV.ifdef_grouped list -> (int * int))=
281 fun xs ->
282 let cnt_paren, cnt_brace = ref 0, ref 0 in
283 xs +> TV.iter_token_ifdef (fun x ->
284 (match x.tok with
285 | x when TH.is_opar x -> incr cnt_paren
286 | TOBrace _ -> incr cnt_brace
287 | x when TH.is_cpar x -> decr cnt_paren
288 | TCBrace _ -> decr cnt_brace
289 | _ -> ()
290 )
291 );
292 !cnt_paren, !cnt_brace
293
294
295 (* ------------------------------------------------------------------------- *)
296 let forLOOKAHEAD = 30
297
298
299 (* look if there is a '{' just after the closing ')', and handling the
300 * possibility to have nested expressions inside nested parenthesis
301 *
302 * todo: use indentation instead of premier(statement) ?
303 *)
304 let rec is_really_foreach xs =
305 let rec is_foreach_aux = function
306 | [] -> false, []
307 | TCPar _::TOBrace _::xs -> true, xs
308 (* the following attempts to handle the cases where there is a
309 single statement in the body of the loop. undoubtedly more
310 cases are needed.
311 todo: premier(statement) - suivant(funcall)
312 *)
313 | TCPar _::TIdent _::xs -> true, xs
314 | TCPar _::Tif _::xs -> true, xs
315 | TCPar _::Twhile _::xs -> true, xs
316 | TCPar _::Tfor _::xs -> true, xs
317 | TCPar _::Tswitch _::xs -> true, xs
318 | TCPar _::Treturn _::xs -> true, xs
319
320
321 | TCPar _::xs -> false, xs
322 | TOPar _::xs ->
323 let (_, xs') = is_foreach_aux xs in
324 is_foreach_aux xs'
325 | x::xs -> is_foreach_aux xs
326 in
327 is_foreach_aux xs +> fst
328
329
330 (* ------------------------------------------------------------------------- *)
331 let set_ifdef_token_parenthize_info cnt x =
332 match x with
333 | TIfdef (tag, _)
334 | TIfdefelse (tag, _)
335 | TIfdefelif (tag, _)
336 | TEndif (tag, _)
337
338 | TIfdefBool (_, tag, _)
339 | TIfdefMisc (_, tag, _)
340 | TIfdefVersion (_, tag, _)
341 ->
342 tag := Some cnt;
343
344 | _ -> raise Impossible
345
346
347
348 let ifdef_paren_cnt = ref 0
349
350
351 let rec set_ifdef_parenthize_info xs =
352 xs +> List.iter (function
353 | NotIfdefLine xs -> ()
354 | Ifdefbool (_, xxs, info_ifdef)
355 | Ifdef (xxs, info_ifdef) ->
356
357 incr ifdef_paren_cnt;
358 let total_directives = List.length info_ifdef in
359
360 info_ifdef +> List.iter (fun x ->
361 set_ifdef_token_parenthize_info (!ifdef_paren_cnt, total_directives)
362 x.tok);
363 xxs +> List.iter set_ifdef_parenthize_info
364 )
365
366
367 (*****************************************************************************)
368 (* The parsing hack for #define *)
369 (*****************************************************************************)
370
371 (* To parse macro definitions I need to do some tricks
372 * as some information can be get only at the lexing level. For instance
373 * the space after the name of the macro in '#define foo (x)' is meaningful
374 * but the grammar can not get this information. So define_ident below
375 * look at such space and generate a special TOpardefine. In a similar
376 * way macro definitions can contain some antislash and newlines
377 * and the grammar need to know where the macro ends (which is
378 * a line-level and so low token-level information). Hence the
379 * function 'define_line' below and the TDefEol.
380 *
381 * update: TDefEol is handled in a special way at different places,
382 * a little bit like EOF, especially for error recovery, so this
383 * is an important token that should not be retagged!
384 *
385 *
386 * ugly hack, a better solution perhaps would be to erase TDefEOL
387 * from the Ast and list of tokens in parse_c.
388 *
389 * note: I do a +1 somewhere, it's for the unparsing to correctly sync.
390 *
391 * note: can't replace mark_end_define by simply a fakeInfo(). The reason
392 * is where is the \n TCommentSpace. Normally there is always a last token
393 * to synchronize on, either EOF or the token of the next toplevel.
394 * In the case of the #define we got in list of token
395 * [TCommentSpace "\n"; TDefEOL] but if TDefEOL is a fakeinfo then we will
396 * not synchronize on it and so we will not print the "\n".
397 * A solution would be to put the TDefEOL before the "\n".
398 * (jll: tried to do this, see the comment "Put end of line..." below)
399 *
400 * todo?: could put a ExpandedTok for that ?
401 *)
402 let mark_end_define ii =
403 let ii' =
404 { Ast_c.pinfo = Ast_c.OriginTok { (Ast_c.parse_info_of_info ii) with
405 Common.str = "";
406 Common.charpos = Ast_c.pos_of_info ii + 1
407 };
408 cocci_tag = ref Ast_c.emptyAnnot;
409 comments_tag = ref Ast_c.emptyComments;
410 }
411 in
412 TDefEOL (ii')
413
414 (* put the TDefEOL at the good place *)
415 let rec define_line_1 acc xs =
416 match xs with
417 | [] -> List.rev acc
418 | TDefine ii::xs ->
419 let line = Ast_c.line_of_info ii in
420 let acc = (TDefine ii) :: acc in
421 define_line_2 acc line ii xs
422 | TUndef ii::xs ->
423 let line = Ast_c.line_of_info ii in
424 let acc = (TUndef ii) :: acc in
425 define_line_2 acc line ii xs
426 | TCppEscapedNewline ii::xs ->
427 pr2 ("SUSPICIOUS: a \\ character appears outside of a #define at");
428 pr2 (Ast_c.strloc_of_info ii);
429 let acc = (TCommentSpace ii) :: acc in
430 define_line_1 acc xs
431 | x::xs -> define_line_1 (x::acc) xs
432
433 and define_line_2 acc line lastinfo xs =
434 match xs with
435 | [] ->
436 (* should not happened, should meet EOF before *)
437 pr2 "PB: WEIRD";
438 List.rev (mark_end_define lastinfo::acc)
439 | x::xs ->
440 let line' = TH.line_of_tok x in
441 let info = TH.info_of_tok x in
442
443 (match x with
444 | EOF ii ->
445 let acc = (mark_end_define lastinfo) :: acc in
446 let acc = (EOF ii) :: acc in
447 define_line_1 acc xs
448 | TCppEscapedNewline ii ->
449 if (line' <> line) then pr2 "PB: WEIRD: not same line number";
450 let acc = (TCommentSpace ii) :: acc in
451 define_line_2 acc (line+1) info xs
452 | x ->
453 if line' =|= line
454 then define_line_2 (x::acc) line info xs
455 else
456 (* Put end of line token before the newline. A newline at least
457 must be there because the line changed and because we saw a
458 #define previously to get to this function at all *)
459 define_line_1
460 ((List.hd acc)::(mark_end_define lastinfo::(List.tl acc)))
461 (x::xs)
462 )
463
464 let rec define_ident acc xs =
465 match xs with
466 | [] -> List.rev acc
467 | TUndef ii::xs ->
468 let acc = TUndef ii :: acc in
469 (match xs with
470 TCommentSpace i1::TIdent (s,i2)::xs ->
471 let acc = (TCommentSpace i1) :: acc in
472 let acc = (TIdentDefine (s,i2)) :: acc in
473 define_ident acc xs
474 | _ ->
475 pr2 "WEIRD: weird #define body";
476 define_ident acc xs
477 )
478 | TDefine ii::xs ->
479 let acc = TDefine ii :: acc in
480 (match xs with
481 | TCommentSpace i1::TIdent (s,i2)::TOPar (i3)::xs ->
482 (* Change also the kind of TIdent to avoid bad interaction
483 * with other parsing_hack tricks. For instant if keep TIdent then
484 * the stringication algo can believe the TIdent is a string-macro.
485 * So simpler to change the kind of the ident too.
486 *)
487 (* if TOParDefine sticked to the ident, then
488 * it's a macro-function. Change token to avoid ambiguity
489 * between #define foo(x) and #define foo (x)
490 *)
491 let acc = (TCommentSpace i1) :: acc in
492 let acc = (TIdentDefine (s,i2)) :: acc in
493 let acc = (TOParDefine i3) :: acc in
494 define_ident acc xs
495
496 | TCommentSpace i1::TIdent (s,i2)::xs ->
497 let acc = (TCommentSpace i1) :: acc in
498 let acc = (TIdentDefine (s,i2)) :: acc in
499 define_ident acc xs
500
501 (* bugfix: ident of macro (as well as params, cf below) can be tricky
502 * note, do we need to subst in the body of the define ? no cos
503 * here the issue is the name of the macro, as in #define inline,
504 * so obviously the name of this macro will not be used in its
505 * body (it would be a recursive macro, which is forbidden).
506 *)
507
508 | TCommentSpace i1::t::xs ->
509
510 let s = TH.str_of_tok t in
511 let ii = TH.info_of_tok t in
512 if s ==~ Common.regexp_alpha
513 then begin
514 pr2 (spf "remapping: %s to an ident in macro name" s);
515 let acc = (TCommentSpace i1) :: acc in
516 let acc = (TIdentDefine (s,ii)) :: acc in
517 define_ident acc xs
518 end
519 else begin
520 pr2 "WEIRD: weird #define body";
521 define_ident acc xs
522 end
523
524 | _ ->
525 pr2 "WEIRD: weird #define body";
526 define_ident acc xs
527 )
528 | x::xs ->
529 let acc = x :: acc in
530 define_ident acc xs
531
532
533
534 let fix_tokens_define2 xs =
535 define_ident [] (define_line_1 [] xs)
536
537 let fix_tokens_define a =
538 Common.profile_code "C parsing.fix_define" (fun () -> fix_tokens_define2 a)
539
540
541
542
543
544 (* ------------------------------------------------------------------------- *)
545 (* Other parsing hacks related to cpp, Include/Define hacks *)
546 (* ------------------------------------------------------------------------- *)
547
548 (* Sometimes I prefer to generate a single token for a list of things in the
549 * lexer so that if I have to passed them, like for passing TInclude then
550 * it's easy. Also if I don't do a single token, then I need to
551 * parse the rest which may not need special stuff, like detecting
552 * end of line which the parser is not really ready for. So for instance
553 * could I parse a #include <a/b/c/xxx.h> as 2 or more tokens ? just
554 * lex #include ? so then need recognize <a/b/c/xxx.h> as one token ?
555 * but this kind of token is valid only after a #include and the
556 * lexing and parsing rules are different for such tokens so not that
557 * easy to parse such things in parser_c.mly. Hence the following hacks.
558 *
559 * less?: maybe could get rid of this like I get rid of some of fix_define.
560 *)
561
562 (* helpers *)
563
564 (* used to generate new token from existing one *)
565 let new_info posadd str ii =
566 { Ast_c.pinfo =
567 Ast_c.OriginTok { (Ast_c.parse_info_of_info ii) with
568 charpos = Ast_c.pos_of_info ii + posadd;
569 str = str;
570 column = Ast_c.col_of_info ii + posadd;
571 };
572 (* must generate a new ref each time, otherwise share *)
573 cocci_tag = ref Ast_c.emptyAnnot;
574 comments_tag = ref Ast_c.emptyComments;
575 }
576
577
578 let rec comment_until_defeol xs =
579 match xs with
580 | [] ->
581 (* job not done in Cpp_token_c.define_parse ? *)
582 failwith "cant find end of define token TDefEOL"
583 | x::xs ->
584 (match x with
585 | Parser_c.TDefEOL i ->
586 Parser_c.TCommentCpp (Token_c.CppDirective, TH.info_of_tok x)
587 ::xs
588 | _ ->
589 let x' =
590 (* bugfix: otherwise may lose a TComment token *)
591 if TH.is_real_comment x
592 then x
593 else Parser_c.TCommentCpp (Token_c.CppPassingNormal (*good?*), TH.info_of_tok x)
594 in
595 x'::comment_until_defeol xs
596 )
597
598 let drop_until_defeol xs =
599 List.tl
600 (Common.drop_until (function Parser_c.TDefEOL _ -> true | _ -> false) xs)
601
602
603
604 (* ------------------------------------------------------------------------- *)
605 (* returns a pair (replaced token, list of next tokens) *)
606 (* ------------------------------------------------------------------------- *)
607
608 let tokens_include (info, includes, filename, inifdef) =
609 Parser_c.TIncludeStart (Ast_c.rewrap_str includes info, inifdef),
610 [Parser_c.TIncludeFilename
611 (filename, (new_info (String.length includes) filename info))
612 ]
613
614
615
616
617 (*****************************************************************************)
618 (* CPP handling: macros, ifdefs, macros defs *)
619 (*****************************************************************************)
620
621 (* ------------------------------------------------------------------------- *)
622 (* special skip_start skip_end handling *)
623 (* ------------------------------------------------------------------------- *)
624
625 (* note: after this normally the token list should not contain any more the
626 * TCommentSkipTagStart and End tokens.
627 *)
628 let rec commentize_skip_start_to_end xs =
629 match xs with
630 | [] -> ()
631 | x::xs ->
632 (match x with
633 | {tok = TCommentSkipTagStart info} ->
634 (try
635 let (before, x2, after) =
636 xs +> Common.split_when (function
637 | {tok = TCommentSkipTagEnd _ } -> true
638 | _ -> false
639 )
640 in
641 let topass = x::x2::before in
642 topass +> List.iter (fun tok ->
643 set_as_comment Token_c.CppPassingExplicit tok
644 );
645 commentize_skip_start_to_end after
646 with Not_found ->
647 failwith "could not find end of skip_start special comment"
648 )
649 | {tok = TCommentSkipTagEnd info} ->
650 failwith "found skip_end comment but no skip_start"
651 | _ ->
652 commentize_skip_start_to_end xs
653 )
654
655
656
657
658 (* ------------------------------------------------------------------------- *)
659 (* ifdef keeping/passing *)
660 (* ------------------------------------------------------------------------- *)
661
662 (* #if 0, #if 1, #if LINUX_VERSION handling *)
663 let rec find_ifdef_bool xs =
664 xs +> List.iter (function
665 | NotIfdefLine _ -> ()
666 | Ifdefbool (is_ifdef_positif, xxs, info_ifdef_stmt) ->
667
668 msg_ifdef_bool_passing is_ifdef_positif;
669
670 (match xxs with
671 | [] -> raise Impossible
672 | firstclause::xxs ->
673 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
674
675 if is_ifdef_positif
676 then xxs +> List.iter
677 (iter_token_ifdef (set_as_comment Token_c.CppPassingNormal))
678 else begin
679 firstclause +> iter_token_ifdef (set_as_comment Token_c.CppPassingNormal);
680 (match List.rev xxs with
681 (* keep only last *)
682 | last::startxs ->
683 startxs +> List.iter
684 (iter_token_ifdef (set_as_comment Token_c.CppPassingNormal))
685 | [] -> (* not #else *) ()
686 );
687 end
688 );
689
690 | Ifdef (xxs, info_ifdef_stmt) -> xxs +> List.iter find_ifdef_bool
691 )
692
693
694
695 let thresholdIfdefSizeMid = 6
696
697 (* infer ifdef involving not-closed expressions/statements *)
698 let rec find_ifdef_mid xs =
699 xs +> List.iter (function
700 | NotIfdefLine _ -> ()
701 | Ifdef (xxs, info_ifdef_stmt) ->
702 (match xxs with
703 | [] -> raise Impossible
704 | [first] -> ()
705 | first::second::rest ->
706 (* don't analyse big ifdef *)
707 if xxs +> List.for_all
708 (fun xs -> List.length xs <= thresholdIfdefSizeMid) &&
709 (* don't want nested ifdef *)
710 xxs +> List.for_all (fun xs ->
711 xs +> List.for_all
712 (function NotIfdefLine _ -> true | _ -> false)
713 )
714
715 then
716 let counts = xxs +> List.map count_open_close_stuff_ifdef_clause in
717 let cnt1, cnt2 = List.hd counts in
718 if cnt1 <> 0 || cnt2 <> 0 &&
719 counts +> List.for_all (fun x -> x =*= (cnt1, cnt2))
720 (*
721 if counts +> List.exists (fun (cnt1, cnt2) ->
722 cnt1 <> 0 || cnt2 <> 0
723 )
724 *)
725 then begin
726 msg_ifdef_mid_something();
727
728 (* keep only first, treat the rest as comment *)
729 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
730 (second::rest) +> List.iter
731 (iter_token_ifdef (set_as_comment Token_c.CppPassingCosWouldGetError));
732 end
733
734 );
735 List.iter find_ifdef_mid xxs
736
737 (* no need complex analysis for ifdefbool *)
738 | Ifdefbool (_, xxs, info_ifdef_stmt) ->
739 List.iter find_ifdef_mid xxs
740
741
742 )
743
744
745 let thresholdFunheaderLimit = 4
746
747 (* ifdef defining alternate function header, type *)
748 let rec find_ifdef_funheaders = function
749 | [] -> ()
750 | NotIfdefLine _::xs -> find_ifdef_funheaders xs
751
752 (* ifdef-funheader if ifdef with 2 lines and a '{' in next line *)
753 | Ifdef
754 ([(NotIfdefLine (({col = 0} as _xline1)::line1))::ifdefblock1;
755 (NotIfdefLine (({col = 0} as xline2)::line2))::ifdefblock2
756 ], info_ifdef_stmt
757 )
758 ::NotIfdefLine (({tok = TOBrace i; col = 0})::line3)
759 ::xs
760 when List.length ifdefblock1 <= thresholdFunheaderLimit &&
761 List.length ifdefblock2 <= thresholdFunheaderLimit
762 ->
763 find_ifdef_funheaders xs;
764
765 msg_ifdef_funheaders ();
766 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
767 let all_toks = [xline2] @ line2 in
768 all_toks +> List.iter (set_as_comment Token_c.CppPassingCosWouldGetError) ;
769 ifdefblock2 +> iter_token_ifdef (set_as_comment Token_c.CppPassingCosWouldGetError);
770
771 (* ifdef with nested ifdef *)
772 | Ifdef
773 ([[NotIfdefLine (({col = 0} as _xline1)::line1)];
774 [Ifdef
775 ([[NotIfdefLine (({col = 0} as xline2)::line2)];
776 [NotIfdefLine (({col = 0} as xline3)::line3)];
777 ], info_ifdef_stmt2
778 )
779 ]
780 ], info_ifdef_stmt
781 )
782 ::NotIfdefLine (({tok = TOBrace i; col = 0})::line4)
783 ::xs
784 ->
785 find_ifdef_funheaders xs;
786
787 msg_ifdef_funheaders ();
788 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
789 info_ifdef_stmt2 +> List.iter (set_as_comment Token_c.CppDirective);
790 let all_toks = [xline2;xline3] @ line2 @ line3 in
791 all_toks +> List.iter (set_as_comment Token_c.CppPassingCosWouldGetError);
792
793 (* ifdef with elseif *)
794 | Ifdef
795 ([[NotIfdefLine (({col = 0} as _xline1)::line1)];
796 [NotIfdefLine (({col = 0} as xline2)::line2)];
797 [NotIfdefLine (({col = 0} as xline3)::line3)];
798 ], info_ifdef_stmt
799 )
800 ::NotIfdefLine (({tok = TOBrace i; col = 0})::line4)
801 ::xs
802 ->
803 find_ifdef_funheaders xs;
804
805 msg_ifdef_funheaders ();
806 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
807 let all_toks = [xline2;xline3] @ line2 @ line3 in
808 all_toks +> List.iter (set_as_comment Token_c.CppPassingCosWouldGetError)
809
810 (* recurse *)
811 | Ifdef (xxs,info_ifdef_stmt)::xs
812 | Ifdefbool (_, xxs,info_ifdef_stmt)::xs ->
813 List.iter find_ifdef_funheaders xxs;
814 find_ifdef_funheaders xs
815
816
817
818 (* ?? *)
819 let rec adjust_inifdef_include xs =
820 xs +> List.iter (function
821 | NotIfdefLine _ -> ()
822 | Ifdef (xxs, info_ifdef_stmt) | Ifdefbool (_, xxs, info_ifdef_stmt) ->
823 xxs +> List.iter (iter_token_ifdef (fun tokext ->
824 match tokext.tok with
825 | Parser_c.TInclude (s1, s2, inifdef_ref, ii) ->
826 inifdef_ref := true;
827 | _ -> ()
828 ));
829 )
830
831
832
833
834
835
836
837 let rec find_ifdef_cparen_else xs =
838 let rec aux xs =
839 xs +> List.iter (function
840 | NotIfdefLine _ -> ()
841 | Ifdef (xxs, info_ifdef_stmt) ->
842 (match xxs with
843 | [] -> raise Impossible
844 | [first] -> ()
845 | first::second::rest ->
846
847 (* found a closing ')' just after the #else *)
848
849 (* Too bad ocaml does not support better list pattern matching
850 * a la Prolog-III where can match the end of lists.
851 *)
852 let condition =
853 if List.length first = 0 then false
854 else
855 let last_line = Common.last first in
856 match last_line with
857 | NotIfdefLine xs ->
858 if List.length xs = 0 then false
859 else
860 let last_tok = Common.last xs in
861 TH.is_cpar last_tok.tok
862 | Ifdef _ | Ifdefbool _ -> false
863 in
864 if condition then begin
865 msg_ifdef_cparen_else();
866
867 (* keep only first, treat the rest as comment *)
868 info_ifdef_stmt +> List.iter (set_as_comment Token_c.CppDirective);
869 (second::rest) +> List.iter
870 (iter_token_ifdef (set_as_comment Token_c.CppPassingCosWouldGetError));
871 end
872
873 );
874 List.iter aux xxs
875
876 (* no need complex analysis for ifdefbool *)
877 | Ifdefbool (_, xxs, info_ifdef_stmt) ->
878 List.iter aux xxs
879 )
880 in aux xs
881
882
883 (* ------------------------------------------------------------------------- *)
884 (* cpp-builtin part2, macro, using standard.h or other defs *)
885 (* ------------------------------------------------------------------------- *)
886
887 (* now in cpp_token_c.ml *)
888
889 (* ------------------------------------------------------------------------- *)
890 (* stringification *)
891 (* ------------------------------------------------------------------------- *)
892
893 let rec find_string_macro_paren xs =
894 match xs with
895 | [] -> ()
896 | Parenthised(xxs, info_parens)::xs ->
897 xxs +> List.iter (fun xs ->
898 if xs +> List.exists
899 (function PToken({tok = (TString _| TMacroString _)}) -> true | _ -> false) &&
900 xs +> List.for_all
901 (function PToken({tok = (TString _| TMacroString _)}) | PToken({tok = TIdent _}) ->
902 true | _ -> false)
903 then
904 xs +> List.iter (fun tok ->
905 match tok with
906 | PToken({tok = TIdent (s,_)} as id) ->
907 msg_stringification s;
908 id.tok <- TMacroString (s, TH.info_of_tok id.tok);
909 | _ -> ()
910 )
911 else
912 find_string_macro_paren xs
913 );
914 find_string_macro_paren xs
915 | PToken(tok)::xs ->
916 find_string_macro_paren xs
917
918
919 (* ------------------------------------------------------------------------- *)
920 (* macro2 *)
921 (* ------------------------------------------------------------------------- *)
922
923 (* don't forget to recurse in each case *)
924 let rec find_macro_paren xs =
925 match xs with
926 | [] -> ()
927
928 (* attribute *)
929 | PToken ({tok = Tattribute _} as id)
930 ::Parenthised (xxs,info_parens)
931 ::xs
932 ->
933 pr2_cpp ("MACRO: __attribute detected ");
934 [Parenthised (xxs, info_parens)] +>
935 iter_token_paren (set_as_comment Token_c.CppAttr);
936 set_as_comment Token_c.CppAttr id;
937 find_macro_paren xs
938
939 | PToken ({tok = TattributeNoarg _} as id)
940 ::xs
941 ->
942 pr2_cpp ("MACRO: __attributenoarg detected ");
943 set_as_comment Token_c.CppAttr id;
944 find_macro_paren xs
945
946 (*
947 (* attribute cpp, __xxx id *)
948 | PToken ({tok = TIdent (s,i1)} as id)
949 ::PToken ({tok = TIdent (s2, i2)} as id2)
950 ::xs when s ==~ regexp_annot
951 ->
952 msg_attribute s;
953 id.tok <- TMacroAttr (s, i1);
954 find_macro_paren ((PToken id2)::xs); (* recurse also on id2 ? *)
955
956 (* attribute cpp, id __xxx *)
957 | PToken ({tok = TIdent (s,i1)} as _id)
958 ::PToken ({tok = TIdent (s2, i2)} as id2)
959 ::xs when s2 ==~ regexp_annot && (not (s ==~ regexp_typedef))
960 ->
961 msg_attribute s2;
962 id2.tok <- TMacroAttr (s2, i2);
963 find_macro_paren xs
964
965 | PToken ({tok = (Tstatic _ | Textern _)} as tok1)
966 ::PToken ({tok = TIdent (s,i1)} as attr)
967 ::xs when s ==~ regexp_annot
968 ->
969 pr2_cpp ("storage attribute: " ^ s);
970 attr.tok <- TMacroAttrStorage (s,i1);
971 (* recurse, may have other storage attributes *)
972 find_macro_paren (PToken (tok1)::xs)
973
974
975 *)
976
977 (* storage attribute *)
978 | PToken ({tok = (Tstatic _ | Textern _)} as tok1)
979 ::PToken ({tok = TMacroAttr (s,i1)} as attr)::xs
980 ->
981 pr2_cpp ("storage attribute: " ^ s);
982 attr.tok <- TMacroAttrStorage (s,i1);
983 (* recurse, may have other storage attributes *)
984 find_macro_paren (PToken (tok1)::xs)
985
986
987 (* stringification
988 *
989 * the order of the matching clause is important
990 *
991 *)
992
993 (* string macro with params, before case *)
994 | PToken ({tok = (TString _| TMacroString _)})::PToken ({tok = TIdent (s,_)} as id)
995 ::Parenthised (xxs, info_parens)
996 ::xs ->
997
998 msg_stringification_params s;
999 id.tok <- TMacroString (s, TH.info_of_tok id.tok);
1000 [Parenthised (xxs, info_parens)] +>
1001 iter_token_paren (set_as_comment Token_c.CppMacro);
1002 find_macro_paren xs
1003
1004 (* after case *)
1005 | PToken ({tok = TIdent (s,_)} as id)
1006 ::Parenthised (xxs, info_parens)
1007 ::PToken ({tok = (TString _ | TMacroString _)})
1008 ::xs ->
1009
1010 msg_stringification_params s;
1011 id.tok <- TMacroString (s, TH.info_of_tok id.tok);
1012 [Parenthised (xxs, info_parens)] +>
1013 iter_token_paren (set_as_comment Token_c.CppMacro);
1014 find_macro_paren xs
1015
1016
1017 (* for the case where the string is not inside a funcall, but
1018 * for instance in an initializer.
1019 *)
1020
1021 (* string macro variable, before case *)
1022 | PToken ({tok = (TString _ | TMacroString _)})::PToken ({tok = TIdent (s,_)} as id)
1023 ::xs ->
1024
1025 msg_stringification s;
1026 id.tok <- TMacroString (s, TH.info_of_tok id.tok);
1027 find_macro_paren xs
1028
1029 (* after case *)
1030 | PToken ({tok = TIdent (s,_)} as id)
1031 ::PToken ({tok = (TString _ | TMacroString _)})
1032 ::xs ->
1033
1034 msg_stringification s;
1035 id.tok <- TMacroString (s, TH.info_of_tok id.tok);
1036 find_macro_paren xs
1037
1038
1039
1040
1041
1042 (* recurse *)
1043 | (PToken x)::xs -> find_macro_paren xs
1044 | (Parenthised (xxs, info_parens))::xs ->
1045 xxs +> List.iter find_macro_paren;
1046 find_macro_paren xs
1047
1048
1049
1050
1051
1052 (* don't forget to recurse in each case *)
1053 let rec find_macro_lineparen xs =
1054 match xs with
1055 | [] -> ()
1056
1057 (* linuxext: ex: static [const] DEVICE_ATTR(); *)
1058 | (Line
1059 (
1060 [PToken ({tok = Tstatic _});
1061 PToken ({tok = TIdent (s,_)} as macro);
1062 Parenthised (xxs,info_parens);
1063 PToken ({tok = TPtVirg _});
1064 ]
1065 ))
1066 ::xs
1067 when (s ==~ regexp_macro) ->
1068
1069 msg_declare_macro s;
1070 let info = TH.info_of_tok macro.tok in
1071 macro.tok <- TMacroDecl (Ast_c.str_of_info info, info);
1072
1073 find_macro_lineparen (xs)
1074
1075 (* the static const case *)
1076 | (Line
1077 (
1078 [PToken ({tok = Tstatic _});
1079 PToken ({tok = Tconst _} as const);
1080 PToken ({tok = TIdent (s,_)} as macro);
1081 Parenthised (xxs,info_parens);
1082 PToken ({tok = TPtVirg _});
1083 ]
1084 (*as line1*)
1085
1086 ))
1087 ::xs
1088 when (s ==~ regexp_macro) ->
1089
1090 msg_declare_macro s;
1091 let info = TH.info_of_tok macro.tok in
1092 macro.tok <- TMacroDecl (Ast_c.str_of_info info, info);
1093
1094 (* need retag this const, otherwise ambiguity in grammar
1095 21: shift/reduce conflict (shift 121, reduce 137) on Tconst
1096 decl2 : Tstatic . TMacroDecl TOPar argument_list TCPar ...
1097 decl2 : Tstatic . Tconst TMacroDecl TOPar argument_list TCPar ...
1098 storage_class_spec : Tstatic . (137)
1099 *)
1100 const.tok <- TMacroDeclConst (TH.info_of_tok const.tok);
1101
1102 find_macro_lineparen (xs)
1103
1104
1105 (* same but without trailing ';'
1106 *
1107 * I do not put the final ';' because it can be on a multiline and
1108 * because of the way mk_line is coded, we will not have access to
1109 * this ';' on the next line, even if next to the ')' *)
1110 | (Line
1111 ([PToken ({tok = Tstatic _});
1112 PToken ({tok = TIdent (s,_)} as macro);
1113 Parenthised (xxs,info_parens);
1114 ]
1115 ))
1116 ::xs
1117 when s ==~ regexp_macro ->
1118
1119 msg_declare_macro s;
1120 let info = TH.info_of_tok macro.tok in
1121 macro.tok <- TMacroDecl (Ast_c.str_of_info info, info);
1122
1123 find_macro_lineparen (xs)
1124
1125
1126
1127
1128 (* on multiple lines *)
1129 | (Line
1130 (
1131 (PToken ({tok = Tstatic _})::[]
1132 )))
1133 ::(Line
1134 (
1135 [PToken ({tok = TIdent (s,_)} as macro);
1136 Parenthised (xxs,info_parens);
1137 PToken ({tok = TPtVirg _});
1138 ]
1139 )
1140 )
1141 ::xs
1142 when (s ==~ regexp_macro) ->
1143
1144 msg_declare_macro s;
1145 let info = TH.info_of_tok macro.tok in
1146 macro.tok <- TMacroDecl (Ast_c.str_of_info info, info);
1147
1148 find_macro_lineparen (xs)
1149
1150
1151 (* linuxext: ex: DECLARE_BITMAP();
1152 *
1153 * Here I use regexp_declare and not regexp_macro because
1154 * Sometimes it can be a FunCallMacro such as DEBUG(foo());
1155 * Here we don't have the preceding 'static' so only way to
1156 * not have positive is to restrict to .*DECLARE.* macros.
1157 *
1158 * but there is a grammar rule for that, so don't need this case anymore
1159 * unless the parameter of the DECLARE_xxx are weird and can not be mapped
1160 * on a argument_list
1161 *)
1162
1163 | (Line
1164 ([PToken ({tok = TIdent (s,_)} as macro);
1165 Parenthised (xxs,info_parens);
1166 PToken ({tok = TPtVirg _});
1167 ]
1168 ))
1169 ::xs
1170 when (s ==~ regexp_declare) ->
1171
1172 msg_declare_macro s;
1173 let info = TH.info_of_tok macro.tok in
1174 macro.tok <- TMacroDecl (Ast_c.str_of_info info, info);
1175
1176 find_macro_lineparen (xs)
1177
1178
1179 (* toplevel macros.
1180 * module_init(xxx)
1181 *
1182 * Could also transform the TIdent in a TMacroTop but can have false
1183 * positive, so easier to just change the TCPar and so just solve
1184 * the end-of-stream pb of ocamlyacc
1185 *)
1186 | (Line
1187 ([PToken ({tok = TIdent (s,ii); col = col1; where = ctx} as _macro);
1188 Parenthised (xxs,info_parens);
1189 ] as _line1
1190 ))
1191 ::xs when col1 =|= 0
1192 ->
1193 let condition =
1194 (* to reduce number of false positive *)
1195 (match xs with
1196 | (Line (PToken ({col = col2 } as other)::restline2))::_ ->
1197 TH.is_eof other.tok || (col2 =|= 0 &&
1198 (match other.tok with
1199 | TOBrace _ -> false (* otherwise would match funcdecl *)
1200 | TCBrace _ when ctx <> InFunction -> false
1201 | TPtVirg _
1202 | TDotDot _
1203 -> false
1204 | tok when TH.is_binary_operator tok -> false
1205
1206 | _ -> true
1207 )
1208 )
1209 | _ -> false
1210 )
1211 in
1212 if condition
1213 then begin
1214
1215 msg_macro_toplevel_noptvirg s;
1216 (* just to avoid the end-of-stream pb of ocamlyacc *)
1217 let tcpar = Common.last info_parens in
1218 tcpar.tok <- TCParEOL (TH.info_of_tok tcpar.tok);
1219
1220 (*macro.tok <- TMacroTop (s, TH.info_of_tok macro.tok);*)
1221
1222 end;
1223
1224 find_macro_lineparen (xs)
1225
1226
1227
1228 (* macro with parameters
1229 * ex: DEBUG()
1230 * return x;
1231 *)
1232 | (Line
1233 ([PToken ({tok = TIdent (s,ii); col = col1; where = ctx} as macro);
1234 Parenthised (xxs,info_parens);
1235 ] as _line1
1236 ))
1237 ::(Line
1238 (PToken ({col = col2 } as other)::restline2
1239 ) as line2)
1240 ::xs
1241 (* when s ==~ regexp_macro *)
1242 ->
1243 let condition =
1244 (col1 =|= col2 &&
1245 (match other.tok with
1246 | TOBrace _ -> false (* otherwise would match funcdecl *)
1247 | TCBrace _ when ctx <> InFunction -> false
1248 | TPtVirg _
1249 | TDotDot _
1250 -> false
1251 | tok when TH.is_binary_operator tok -> false
1252
1253 | _ -> true
1254 )
1255 )
1256 ||
1257 (col2 <= col1 &&
1258 (match other.tok, restline2 with
1259 | TCBrace _, _ when ctx =*= InFunction -> true
1260 | Treturn _, _ -> true
1261 | Tif _, _ -> true
1262 | Telse _, _ -> true
1263
1264 (* case of label, usually put in first line *)
1265 | TIdent _, (PToken ({tok = TDotDot _}))::_ ->
1266 true
1267
1268
1269 | _ -> false
1270 )
1271 )
1272
1273 in
1274
1275 if condition
1276 then
1277 if col1 =|= 0 then ()
1278 else begin
1279 msg_macro_noptvirg s;
1280 macro.tok <- TMacroStmt (s, TH.info_of_tok macro.tok);
1281 [Parenthised (xxs, info_parens)] +>
1282 iter_token_paren (set_as_comment Token_c.CppMacro);
1283 end;
1284
1285 find_macro_lineparen (line2::xs)
1286
1287 (* linuxext:? single macro
1288 * ex: LOCK
1289 * foo();
1290 * UNLOCK
1291 *
1292 * todo: factorize code with previous rule ?
1293 *)
1294 | (Line
1295 ([PToken ({tok = TIdent (s,ii); col = col1; where = ctx} as macro);
1296 ] as _line1
1297 ))
1298 ::(Line
1299 (PToken ({col = col2 } as other)::restline2
1300 ) as line2)
1301 ::xs ->
1302 (* when s ==~ regexp_macro *)
1303
1304 let condition =
1305 (col1 =|= col2 &&
1306 col1 <> 0 && (* otherwise can match typedef of fundecl*)
1307 (match other.tok with
1308 | TPtVirg _ -> false
1309 | TOr _ -> false
1310 | TCBrace _ when ctx <> InFunction -> false
1311 | tok when TH.is_binary_operator tok -> false
1312
1313 | _ -> true
1314 )) ||
1315 (col2 <= col1 &&
1316 (match other.tok with
1317 | TCBrace _ when ctx =*= InFunction -> true
1318 | Treturn _ -> true
1319 | Tif _ -> true
1320 | Telse _ -> true
1321 | _ -> false
1322 ))
1323 in
1324
1325 if condition
1326 then begin
1327 msg_macro_noptvirg_single s;
1328 macro.tok <- TMacroStmt (s, TH.info_of_tok macro.tok);
1329 end;
1330 find_macro_lineparen (line2::xs)
1331
1332 | x::xs ->
1333 find_macro_lineparen xs
1334
1335
1336
1337 (* ------------------------------------------------------------------------- *)
1338 (* define tobrace init *)
1339 (* ------------------------------------------------------------------------- *)
1340
1341 let rec find_define_init_brace_paren xs =
1342 let rec aux xs =
1343 match xs with
1344 | [] -> ()
1345
1346 (* mainly for firefox *)
1347 | (PToken {tok = TDefine _})
1348 ::(PToken {tok = TIdentDefine (s,_)})
1349 ::(PToken ({tok = TOBrace i1} as tokbrace))
1350 ::(PToken tok2)
1351 ::(PToken tok3)
1352 ::xs ->
1353 let is_init =
1354 match tok2.tok, tok3.tok with
1355 | TInt _, TComma _ -> true
1356 | TString _, TComma _ -> true
1357 | TIdent _, TComma _ -> true
1358 | _ -> false
1359
1360 in
1361 if is_init
1362 then begin
1363 pr2_cpp("found define initializer: " ^s);
1364 tokbrace.tok <- TOBraceDefineInit i1;
1365 end;
1366
1367 aux xs
1368
1369 (* mainly for linux, especially in sound/ *)
1370 | (PToken {tok = TDefine _})
1371 ::(PToken {tok = TIdentDefine (s,_)})
1372 ::(Parenthised(xxx, info_parens))
1373 ::(PToken ({tok = TOBrace i1} as tokbrace))
1374 ::(PToken tok2)
1375 ::(PToken tok3)
1376 ::xs ->
1377 let is_init =
1378 match tok2.tok, tok3.tok with
1379 | TInt _, TComma _ -> true
1380 | TDot _, TIdent _ -> true
1381 | TIdent _, TComma _ -> true
1382 | _ -> false
1383
1384 in
1385 if is_init
1386 then begin
1387 pr2_cpp("found define initializer with param: " ^ s);
1388 tokbrace.tok <- TOBraceDefineInit i1;
1389 end;
1390
1391 aux xs
1392
1393
1394
1395 (* recurse *)
1396 | (PToken x)::xs -> aux xs
1397 | (Parenthised (xxs, info_parens))::xs ->
1398 (* not need for tobrace init:
1399 * xxs +> List.iter aux;
1400 *)
1401 aux xs
1402 in
1403 aux xs
1404
1405
1406 (* ------------------------------------------------------------------------- *)
1407 (* action *)
1408 (* ------------------------------------------------------------------------- *)
1409
1410 (* obsolete now with macro expansion ? get some regression if comment.
1411 * todo: if do bad decision here, then it can influence other phases
1412 * and make it hard to parse. So maybe when have a parse error, should
1413 * undo some of the guess those heuristics have done, and restore
1414 * the original token value.
1415 *)
1416
1417 let rec find_actions = function
1418 | [] -> ()
1419
1420 | PToken ({tok = TIdent (s,ii)})
1421 ::Parenthised (xxs,info_parens)
1422 ::xs ->
1423 find_actions xs;
1424 xxs +> List.iter find_actions;
1425 let modified = find_actions_params xxs in
1426 if modified
1427 then msg_macro_higher_order s
1428
1429 | x::xs ->
1430 find_actions xs
1431
1432 and find_actions_params xxs =
1433 xxs +> List.fold_left (fun acc xs ->
1434 let toks = tokens_of_paren xs in
1435 if toks +> List.exists (fun x -> TH.is_statement x.tok)
1436 (* undo: && List.length toks > 1
1437 * good for sparse, not good for linux
1438 *)
1439 then begin
1440 xs +> iter_token_paren (fun x ->
1441 if TH.is_eof x.tok
1442 then
1443 (* certainly because paren detection had a pb because of
1444 * some ifdef-exp. Do similar additional checking than
1445 * what is done in set_as_comment.
1446 *)
1447 pr2 "PB: weird, I try to tag an EOF token as an action"
1448 else
1449 (* cf tests-bis/no_cpar_macro.c *)
1450 if TH.is_eom x.tok
1451 then
1452 pr2 "PB: weird, I try to tag an EOM token as an action"
1453 else
1454 x.tok <- TAction (TH.info_of_tok x.tok);
1455 );
1456 true (* modified *)
1457 end
1458 else acc
1459 ) false
1460
1461
1462
1463 (* ------------------------------------------------------------------------- *)
1464 (* main fix cpp function *)
1465 (* ------------------------------------------------------------------------- *)
1466
1467 let filter_cpp_stuff xs =
1468 List.filter
1469 (function x ->
1470 (match x.tok with
1471 | tok when TH.is_comment tok -> false
1472 (* don't want drop the define, or if drop, have to drop
1473 * also its body otherwise the line heuristics may be lost
1474 * by not finding the TDefine in column 0 but by finding
1475 * a TDefineIdent in a column > 0
1476 *)
1477 | Parser_c.TDefine _ -> true
1478 | tok when TH.is_cpp_instruction tok -> false
1479 | _ -> true
1480 ))
1481 xs
1482
1483 let insert_virtual_positions l =
1484 let strlen x = String.length (Ast_c.str_of_info x) in
1485 let rec loop prev offset acc = function
1486 [] -> List.rev acc
1487 | x::xs ->
1488 let ii = TH.info_of_tok x in
1489 let inject pi =
1490 TH.visitor_info_of_tok (function ii -> Ast_c.rewrap_pinfo pi ii) x in
1491 match Ast_c.pinfo_of_info ii with
1492 Ast_c.OriginTok pi ->
1493 let prev = Ast_c.parse_info_of_info ii in
1494 loop prev (strlen ii) (x::acc) xs
1495 | Ast_c.ExpandedTok (pi,_) ->
1496 let x' = inject (Ast_c.ExpandedTok (pi,(prev,offset))) in
1497 loop prev (offset + (strlen ii)) (x'::acc) xs
1498 | Ast_c.FakeTok (s,_) ->
1499 let x' = inject (Ast_c.FakeTok (s,(prev,offset))) in
1500 loop prev (offset + (strlen ii)) (x'::acc) xs
1501 | Ast_c.AbstractLineTok _ -> failwith "abstract not expected" in
1502 let rec skip_fake = function
1503 | [] -> []
1504 | x::xs ->
1505 let ii = TH.info_of_tok x in
1506 match Ast_c.pinfo_of_info ii with
1507 | Ast_c.OriginTok pi ->
1508 let prev = Ast_c.parse_info_of_info ii in
1509 let res = loop prev (strlen ii) [] xs in
1510 x::res
1511 | _ -> x::skip_fake xs in
1512 skip_fake l
1513
1514 (* ------------------------------------------------------------------------- *)
1515
1516 let fix_tokens_cpp2 ~macro_defs tokens =
1517 let tokens2 = ref (tokens +> Common.acc_map TV.mk_token_extended) in
1518
1519 begin
1520 (* the order is important, if you put the action heuristic first,
1521 * then because of ifdef, can have not closed paren
1522 * and so may believe that higher order macro
1523 * and it will eat too much tokens. So important to do
1524 * first the ifdef.
1525 *
1526 * I recompute multiple times cleaner cos the mutable
1527 * can have be changed and so may have more comments
1528 * in the token original list.
1529 *
1530 *)
1531
1532 commentize_skip_start_to_end !tokens2;
1533
1534 (* ifdef *)
1535 let cleaner = !tokens2 +> List.filter (fun x ->
1536 (* is_comment will also filter the TCommentCpp created in
1537 * commentize_skip_start_to_end *)
1538 not (TH.is_comment x.tok) (* could filter also #define/#include *)
1539 ) in
1540 let ifdef_grouped = TV.mk_ifdef cleaner in
1541 set_ifdef_parenthize_info ifdef_grouped;
1542
1543 find_ifdef_funheaders ifdef_grouped;
1544 find_ifdef_bool ifdef_grouped;
1545 find_ifdef_mid ifdef_grouped;
1546 (* change order ? maybe cparen_else heuristic make some of the funheaders
1547 * heuristics irrelevant ?
1548 *)
1549 find_ifdef_cparen_else ifdef_grouped;
1550 adjust_inifdef_include ifdef_grouped;
1551
1552
1553 (* macro 1 *)
1554 let cleaner = !tokens2 +> filter_cpp_stuff in
1555
1556 let paren_grouped = TV.mk_parenthised cleaner in
1557 Cpp_token_c.apply_macro_defs
1558 ~msg_apply_known_macro
1559 ~msg_apply_known_macro_hint
1560 macro_defs paren_grouped;
1561 (* because the before field is used by apply_macro_defs *)
1562 tokens2 := TV.rebuild_tokens_extented !tokens2;
1563
1564 (* tagging contextual info (InFunc, InStruct, etc). Better to do
1565 * that after the "ifdef-simplification" phase.
1566 *)
1567 let cleaner = !tokens2 +> List.filter (fun x ->
1568 not (TH.is_comment x.tok) (* could filter also #define/#include *)
1569 ) in
1570
1571 let brace_grouped = TV.mk_braceised cleaner in
1572 set_context_tag brace_grouped;
1573
1574 (* macro *)
1575 let cleaner = !tokens2 +> filter_cpp_stuff in
1576
1577 let paren_grouped = TV.mk_parenthised cleaner in
1578 let line_paren_grouped = TV.mk_line_parenthised paren_grouped in
1579 find_define_init_brace_paren paren_grouped;
1580 find_string_macro_paren paren_grouped;
1581 find_macro_lineparen line_paren_grouped;
1582 find_macro_paren paren_grouped;
1583
1584
1585 (* obsolete: actions ? not yet *)
1586 let cleaner = !tokens2 +> filter_cpp_stuff in
1587 let paren_grouped = TV.mk_parenthised cleaner in
1588 find_actions paren_grouped;
1589
1590
1591
1592 insert_virtual_positions (!tokens2 +> Common.acc_map (fun x -> x.tok))
1593 end
1594
1595 let time_hack1 ~macro_defs a =
1596 Common.profile_code_exclusif "HACK" (fun () -> fix_tokens_cpp2 ~macro_defs a)
1597
1598 let fix_tokens_cpp ~macro_defs a =
1599 Common.profile_code "C parsing.fix_cpp" (fun () -> time_hack1 ~macro_defs a)
1600
1601
1602
1603
1604 (*****************************************************************************)
1605 (* Lexing with lookahead *)
1606 (*****************************************************************************)
1607
1608 (* Why using yet another parsing_hack technique ? The fix_xxx where do
1609 * some pre-processing on the full list of tokens is not enough ?
1610 * No cos sometimes we need more contextual info, and even if
1611 * set_context() tries to give some contextual info, it's not completely
1612 * accurate so the following code give yet another alternative, yet another
1613 * chance to transform some tokens.
1614 *
1615 * todo?: maybe could try to get rid of this technique. Maybe a better
1616 * set_context() would make possible to move this code using a fix_xx
1617 * technique.
1618 *
1619 * LALR(k) trick. We can do stuff by adding cases in lexer_c.mll, but
1620 * it is more general to do it via my LALR(k) tech. Because here we can
1621 * transform some token give some context information. So sometimes it
1622 * makes sense to transform a token in one context, sometimes not, and
1623 * lex can not provide us this context information. Note that the order
1624 * in the pattern matching in lookahead is important. Do not cut/paste.
1625 *
1626 * Note that in next there is only "clean" tokens, there is no comment
1627 * or space tokens. This is done by the caller.
1628 *
1629 *)
1630
1631 open Lexer_parser (* for the fields of lexer_hint type *)
1632
1633 let not_struct_enum = function
1634 | (Parser_c.Tstruct _ | Parser_c.Tunion _ | Parser_c.Tenum _)::_ -> false
1635 | _ -> true
1636
1637 let pointer = function
1638 TMul _ -> true
1639 | TAnd _ when !Flag.c_plus_plus -> true
1640 | _ -> false
1641
1642 let lookahead2 ~pass next before =
1643
1644 match (next, before) with
1645
1646 (*-------------------------------------------------------------*)
1647 (* typedef inference, parse_typedef_fix3 *)
1648 (*-------------------------------------------------------------*)
1649 (* xx xx *)
1650 | (TIdent(s,i1)::TIdent(s2,i2)::_ , _) when not_struct_enum before && s =$= s2
1651 && ok_typedef s
1652 (* (take_safe 1 !passed_tok <> [TOPar]) -> *)
1653 ->
1654 (* parse_typedef_fix3:
1655 * acpi_object acpi_object;
1656 * etait mal parsé, car pas le temps d'appeler dt() dans le type_spec.
1657 * Le parser en interne a deja appelé le prochain token pour pouvoir
1658 * decider des choses.
1659 * => special case in lexer_heuristic, again
1660 *)
1661 if !Flag_parsing_c.debug_typedef
1662 then pr2 ("TYPEDEF: disable typedef cos special case: " ^ s);
1663
1664 LP.disable_typedef();
1665
1666 msg_typedef s; LP.add_typedef_root s;
1667 TypedefIdent (s, i1)
1668
1669 (* xx yy *)
1670 | (TIdent (s, i1)::TIdent (s2, i2)::_ , _) when not_struct_enum before
1671 && ok_typedef s
1672 ->
1673 (* && not_annot s2 BUT lead to false positive*)
1674
1675 msg_typedef s; LP.add_typedef_root s;
1676 TypedefIdent (s, i1)
1677
1678
1679 (* xx inline *)
1680 | (TIdent (s, i1)::Tinline i2::_ , _) when not_struct_enum before
1681 && ok_typedef s
1682 ->
1683 msg_typedef s; LP.add_typedef_root s;
1684 TypedefIdent (s, i1)
1685
1686
1687 (* [,(] xx [,)] AND param decl *)
1688 | (TIdent (s, i1)::(TComma _|TCPar _)::_ , (TComma _ |TOPar _)::_ )
1689 when not_struct_enum before && (LP.current_context() =*= LP.InParameter)
1690 && ok_typedef s
1691 ->
1692 msg_typedef s; LP.add_typedef_root s;
1693 TypedefIdent (s, i1)
1694
1695 (* xx* [,)] *)
1696 (* specialcase: [,(] xx* [,)] *)
1697 | (TIdent (s, i1)::ptr::(TComma _|TCPar _)::_ , (*(TComma _|TOPar _)::*)_ )
1698 when pointer ptr && not_struct_enum before
1699 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1700 && ok_typedef s
1701 ->
1702 msg_typedef s; LP.add_typedef_root s;
1703 TypedefIdent (s, i1)
1704
1705
1706 (* xx** [,)] *)
1707 (* specialcase: [,(] xx** [,)] *)
1708 | (TIdent (s, i1)::TMul _::TMul _::(TComma _|TCPar _)::_ , (*(TComma _|TOPar _)::*)_ )
1709 when not_struct_enum before
1710 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1711 && ok_typedef s
1712 ->
1713 msg_typedef s; LP.add_typedef_root s;
1714 TypedefIdent (s, i1)
1715
1716
1717
1718 (* xx const * USELESS because of next rule ? *)
1719 | (TIdent (s, i1)::(Tconst _|Tvolatile _|Trestrict _)::TMul _::_ , _ )
1720 when not_struct_enum before
1721 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1722 && ok_typedef s
1723 ->
1724
1725 msg_typedef s; LP.add_typedef_root s;
1726 TypedefIdent (s, i1)
1727
1728 (* xx const *)
1729 | (TIdent (s, i1)::(Tconst _|Tvolatile _|Trestrict _)::_ , _ )
1730 when not_struct_enum before
1731 && ok_typedef s
1732 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1733 ->
1734
1735 msg_typedef s; LP.add_typedef_root s;
1736 TypedefIdent (s, i1)
1737
1738
1739 (* xx * const *)
1740 | (TIdent (s, i1)::ptr::(Tconst _ | Tvolatile _|Trestrict _)::_ , _ )
1741 when pointer ptr && not_struct_enum before
1742 && ok_typedef s
1743 ->
1744 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1745
1746 msg_typedef s; LP.add_typedef_root s;
1747 TypedefIdent (s, i1)
1748
1749
1750 (* ( const xx) *)
1751 | (TIdent (s, i1)::TCPar _::_, (Tconst _ | Tvolatile _|Trestrict _)::TOPar _::_) when
1752 ok_typedef s ->
1753 msg_typedef s; LP.add_typedef_root s;
1754 TypedefIdent (s, i1)
1755
1756
1757
1758 (* ( xx ) [sizeof, ~] *)
1759 | (TIdent (s, i1)::TCPar _::(Tsizeof _|TTilde _)::_ , TOPar _::_ )
1760 when not_struct_enum before
1761 && ok_typedef s
1762 ->
1763 msg_typedef s; LP.add_typedef_root s;
1764 TypedefIdent (s, i1)
1765
1766 (* [(,] xx [ AND parameterdeclaration *)
1767 | (TIdent (s, i1)::TOCro _::_, (TComma _ |TOPar _)::_)
1768 when (LP.current_context() =*= LP.InParameter)
1769 && ok_typedef s
1770 ->
1771 msg_typedef s; LP.add_typedef_root s;
1772 TypedefIdent (s, i1)
1773
1774 (*------------------------------------------------------------*)
1775 (* if 'x*y' maybe an expr, maybe just a classic multiplication *)
1776 (* but if have a '=', or ',' I think not *)
1777 (*------------------------------------------------------------*)
1778
1779 (* static xx * yy *)
1780 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::_ ,
1781 (Tregister _|Tstatic _ |Tvolatile _|Tconst _|Trestrict _)::_) when
1782 pointer ptr && ok_typedef s
1783 ->
1784 msg_typedef s; LP.add_typedef_root s;
1785 TypedefIdent (s, i1)
1786
1787 (* TODO xx * yy ; AND in start of compound element *)
1788
1789
1790 (* xx * yy, AND in paramdecl *)
1791 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TComma _::_ , _)
1792 when not_struct_enum before && (LP.current_context() =*= LP.InParameter)
1793 && pointer ptr && ok_typedef s
1794 ->
1795
1796 msg_typedef s; LP.add_typedef_root s;
1797 TypedefIdent (s, i1)
1798
1799
1800 (* xx * yy ; AND in Toplevel, except when have = before *)
1801 | (TIdent (s, i1)::TMul _::TIdent (s2, i2)::TPtVirg _::_ , TEq _::_) ->
1802 TIdent (s, i1)
1803 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TPtVirg _::_ , _)
1804 when not_struct_enum before && pointer ptr &&
1805 (LP.is_top_or_struct (LP.current_context ()))
1806 ->
1807 msg_typedef s; LP.add_typedef_root s;
1808 TypedefIdent (s, i1)
1809
1810 (* xx * yy , AND in Toplevel *)
1811 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TComma _::_ , _)
1812 when not_struct_enum before && (LP.current_context () =*= LP.InTopLevel)
1813 && ok_typedef s && pointer ptr
1814 ->
1815
1816 msg_typedef s; LP.add_typedef_root s;
1817 TypedefIdent (s, i1)
1818
1819 (* xx * yy ( AND in Toplevel *)
1820 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TOPar _::_ , _)
1821 when not_struct_enum before
1822 && (LP.is_top_or_struct (LP.current_context ()))
1823 && ok_typedef s && pointer ptr
1824 ->
1825 msg_typedef s; LP.add_typedef_root s;
1826 TypedefIdent (s, i1)
1827
1828 (* xx * yy [ *)
1829 (* todo? enough ? cos in struct def we can have some expression ! *)
1830 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TOCro _::_ , _)
1831 when not_struct_enum before &&
1832 (LP.is_top_or_struct (LP.current_context ()))
1833 && ok_typedef s && pointer ptr
1834 ->
1835 msg_typedef s; LP.add_typedef_root s;
1836 TypedefIdent (s, i1)
1837
1838 (* u16: 10; in struct *)
1839 | (TIdent (s, i1)::TDotDot _::_ , (TOBrace _ | TPtVirg _)::_)
1840 when (LP.is_top_or_struct (LP.current_context ()))
1841 && ok_typedef s
1842 ->
1843 msg_typedef s; LP.add_typedef_root s;
1844 TypedefIdent (s, i1)
1845
1846
1847 (* why need TOPar condition as stated in preceding rule ? really needed ? *)
1848 (* YES cos at toplevel can have some expression !! for instance when *)
1849 (* enter in the dimension of an array *)
1850 (*
1851 | (TIdent s::TMul::TIdent s2::_ , _)
1852 when (take_safe 1 !passed_tok <> [Tstruct] &&
1853 (take_safe 1 !passed_tok <> [Tenum]))
1854 &&
1855 !LP._lexer_hint = Some LP.Toplevel ->
1856 msg_typedef s; LP.add_typedef_root s;
1857 TypedefIdent s
1858 *)
1859
1860 (* xx * yy = *)
1861 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TEq _::_ , _)
1862 when not_struct_enum before
1863 && ok_typedef s && pointer ptr
1864 ->
1865 msg_typedef s; LP.add_typedef_root s;
1866 TypedefIdent (s, i1)
1867
1868
1869 (* xx * yy) AND in paramdecl *)
1870 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TCPar _::_ , _)
1871 when not_struct_enum before && (LP.current_context () =*= LP.InParameter)
1872 && ok_typedef s && pointer ptr
1873 ->
1874 msg_typedef s; LP.add_typedef_root s;
1875 TypedefIdent (s, i1)
1876
1877
1878 (* xx * yy; *) (* wrong ? *)
1879 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TPtVirg _::_ ,
1880 (TOBrace _| TPtVirg _)::_) when not_struct_enum before
1881 && ok_typedef s & pointer ptr
1882 ->
1883 msg_typedef s; LP.add_typedef_root s;
1884 msg_maybe_dangereous_typedef s;
1885 TypedefIdent (s, i1)
1886
1887
1888 (* xx * yy, and ';' before xx *) (* wrong ? *)
1889 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::TComma _::_ ,
1890 (TOBrace _| TPtVirg _)::_) when
1891 ok_typedef s && pointer ptr
1892 ->
1893 msg_typedef s; LP.add_typedef_root s;
1894 TypedefIdent (s, i1)
1895
1896
1897 (* xx_t * yy *)
1898 | (TIdent (s, i1)::ptr::TIdent (s2, i2)::_ , _)
1899 when s ==~ regexp_typedef && not_struct_enum before
1900 (* struct user_info_t sometimes *)
1901 && ok_typedef s && pointer ptr
1902 ->
1903 msg_typedef s; LP.add_typedef_root s;
1904 TypedefIdent (s, i1)
1905
1906 (* xx ** yy *) (* wrong ? *)
1907 | (TIdent (s, i1)::TMul _::TMul _::TIdent (s2, i2)::_ , _)
1908 when not_struct_enum before
1909 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1910 && ok_typedef s
1911 ->
1912 msg_typedef s; LP.add_typedef_root s;
1913 TypedefIdent (s, i1)
1914
1915 (* xx *** yy *)
1916 | (TIdent (s, i1)::TMul _::TMul _::TMul _::TIdent (s2, i2)::_ , _)
1917 when not_struct_enum before
1918 && ok_typedef s
1919 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1920 ->
1921 msg_typedef s; LP.add_typedef_root s;
1922 TypedefIdent (s, i1)
1923
1924 (* xx ** ) *)
1925 | (TIdent (s, i1)::TMul _::TMul _::TCPar _::_ , _)
1926 when not_struct_enum before
1927 (* && !LP._lexer_hint = Some LP.ParameterDeclaration *)
1928 && ok_typedef s
1929 ->
1930 msg_typedef s; LP.add_typedef_root s;
1931 TypedefIdent (s, i1)
1932
1933
1934
1935 (* ----------------------------------- *)
1936 (* old: why not do like for other rules and start with TIdent ?
1937 * why do TOPar :: TIdent :: ..., _ and not TIdent :: ..., TOPAr::_ ?
1938 * new: prefer now start with TIdent because otherwise the add_typedef_root
1939 * may have no effect if in second pass or if have disable the add_typedef.
1940 *)
1941
1942 (* (xx) yy *)
1943 | (TIdent (s, i1)::TCPar i2::(TIdent (_,i3)|TInt (_,i3))::_ ,
1944 (TOPar info)::x::_)
1945 when not (TH.is_stuff_taking_parenthized x) &&
1946 Ast_c.line_of_info i2 =|= Ast_c.line_of_info i3
1947 && ok_typedef s
1948 ->
1949
1950 msg_typedef s; LP.add_typedef_root s;
1951 (*TOPar info*)
1952 TypedefIdent (s, i1)
1953
1954
1955 (* (xx) ( yy)
1956 * but false positif: typedef int (xxx_t)(...), so do specialisation below.
1957 *)
1958 (*
1959 | (TIdent (s, i1)::TCPar _::TOPar _::_ , (TOPar info)::x::_)
1960 when not (TH.is_stuff_taking_parenthized x)
1961 && ok_typedef s
1962 ->
1963 msg_typedef s; LP.add_typedef_root s;
1964 (* TOPar info *)
1965 TypedefIdent (s, i1)
1966 *)
1967 (* special case: = (xx) ( yy) *)
1968 | (TIdent (s, i1)::TCPar _::TOPar _::_ ,
1969 (TOPar info)::(TEq _ |TEqEq _)::_)
1970 when ok_typedef s
1971 ->
1972 msg_typedef s; LP.add_typedef_root s;
1973 (* TOPar info *)
1974 TypedefIdent (s, i1)
1975
1976
1977 (* (xx * ) yy *)
1978 | (TIdent (s, i1)::ptr::TCPar _::TIdent (s2, i2)::_ , (TOPar info)::_)
1979 when ok_typedef s && pointer ptr
1980 ->
1981 msg_typedef s; LP.add_typedef_root s;
1982 (*TOPar info*)
1983 TypedefIdent (s,i1)
1984
1985
1986 (* (xx){ ... } constructor *)
1987 | (TIdent (s, i1)::TCPar _::TOBrace _::_ , TOPar _::x::_)
1988 when (*s ==~ regexp_typedef && *) not (TH.is_stuff_taking_parenthized x)
1989 && ok_typedef s
1990 ->
1991 msg_typedef s; LP.add_typedef_root s;
1992 TypedefIdent (s, i1)
1993
1994
1995 (* can have sizeof on expression
1996 | (Tsizeof::TOPar::TIdent s::TCPar::_, _) ->
1997 msg_typedef s; LP.add_typedef_root s;
1998 Tsizeof
1999 *)
2000
2001
2002 (* ----------------------------------- *)
2003 (* x ( *y )(params), function pointer *)
2004 | (TIdent (s, i1)::TOPar _::TMul _::TIdent _::TCPar _::TOPar _::_, _)
2005 when not_struct_enum before
2006 && ok_typedef s
2007 ->
2008 msg_typedef s; LP.add_typedef_root s;
2009 TypedefIdent (s, i1)
2010
2011 (* x* ( *y )(params), function pointer 2 *)
2012 | (TIdent (s, i1)::TMul _::TOPar _::TMul _::TIdent _::TCPar _::TOPar _::_, _)
2013 when not_struct_enum before
2014 && ok_typedef s
2015 ->
2016 msg_typedef s; LP.add_typedef_root s;
2017 TypedefIdent (s, i1)
2018
2019
2020 (*-------------------------------------------------------------*)
2021 (* CPP *)
2022 (*-------------------------------------------------------------*)
2023 | ((TIfdef (_,ii) |TIfdefelse (_,ii) |TIfdefelif (_,ii) |TEndif (_,ii) |
2024 TIfdefBool (_,_,ii)|TIfdefMisc(_,_,ii)|TIfdefVersion(_,_,ii))
2025 as x)
2026 ::_, _
2027 ->
2028 (*
2029 if not !Flag_parsing_c.ifdef_to_if
2030 then TCommentCpp (Ast_c.CppDirective, ii)
2031 else
2032 *)
2033 (* not !LP._lexer_hint.toplevel *)
2034 if !Flag_parsing_c.ifdef_directive_passing
2035 || (pass >= 2)
2036 then begin
2037
2038 if (LP.current_context () =*= LP.InInitializer)
2039 then begin
2040 pr2_cpp "In Initializer passing"; (* cheat: dont count in stat *)
2041 incr Stat.nIfdefInitializer;
2042 end else begin
2043 pr2_cpp("IFDEF: or related inside function. I treat it as comment");
2044 incr Stat.nIfdefPassing;
2045 end;
2046 TCommentCpp (Token_c.CppDirective, ii)
2047 end
2048 else x
2049
2050 | (TUndef (ii) as x)::_, _
2051 ->
2052 if (pass >= 2)
2053 then begin
2054 pr2_cpp("UNDEF: I treat it as comment");
2055 TCommentCpp (Token_c.CppDirective, ii)
2056 end
2057 else x
2058
2059 | (TCppDirectiveOther (ii) as x)::_, _
2060 ->
2061 if (pass >= 2)
2062 then begin
2063 pr2_cpp ("OTHER directive: I treat it as comment");
2064 TCommentCpp (Token_c.CppDirective, ii)
2065 end
2066 else x
2067
2068 (* If ident contain a for_each, then certainly a macro. But to be
2069 * sure should look if there is a '{' after the ')', but it requires
2070 * to count the '('. Because this can be expensive, we do that only
2071 * when the token contains "for_each".
2072 *)
2073 | (TIdent (s, i1)::TOPar _::rest, _)
2074 when not (LP.current_context () =*= LP.InTopLevel)
2075 (* otherwise a function such as static void loopback_enable(int i) {
2076 * will be considered as a loop
2077 *)
2078 ->
2079
2080 if s ==~ regexp_foreach &&
2081 is_really_foreach (Common.take_safe forLOOKAHEAD rest)
2082
2083 then begin
2084 msg_foreach s;
2085 TMacroIterator (s, i1)
2086 end
2087 else TIdent (s, i1)
2088
2089
2090
2091 (*-------------------------------------------------------------*)
2092 | v::xs, _ -> v
2093 | _ -> raise Impossible
2094
2095 let lookahead ~pass a b =
2096 Common.profile_code "C parsing.lookahead" (fun () -> lookahead2 ~pass a b)
2097
2098