3cd332211794df058b405368c0da28e200802462
[bpt/coccinelle.git] / parsing_c / lexer_c.mll
1 {
2 (* Yoann Padioleau
3 *
4 * Copyright (C) 2002, 2006, 2007, 2008, 2009, 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 open Common
16
17 open Parser_c
18
19 open Ast_c (* to factorise tokens, OpAssign, ... *)
20
21 (*****************************************************************************)
22 (*
23 * subtil: ocamllex use side effect on lexbuf, so must take care.
24 * For instance must do
25 *
26 * let info = tokinfo lexbuf in
27 * TComment (info +> tok_add_s (comment lexbuf))
28 *
29 * and not
30 *
31 * TComment (tokinfo lexbuf +> tok_add_s (comment lexbuf))
32 *
33 * because of the "wierd" order of evaluation of OCaml.
34 *
35 *
36 *
37 * note: can't use Lexer_parser._lexer_hint here to do different
38 * things, because now we call the lexer to get all the tokens
39 * (tokens_all), and then we parse. So we can't have the _lexer_hint
40 * info here. We can have it only in parse_c. For the same reason, the
41 * typedef handling here is now useless.
42 *)
43 (*****************************************************************************)
44
45 (*****************************************************************************)
46 (* Wrappers *)
47 (*****************************************************************************)
48 let pr2, pr2_once = Common.mk_pr2_wrappers Flag_parsing_c.verbose_lexing
49
50 (*****************************************************************************)
51
52
53 exception Lexical of string
54
55 let tok lexbuf = Lexing.lexeme lexbuf
56
57 let tokinfo lexbuf =
58 {
59 pinfo = Ast_c.OriginTok {
60 Common.charpos = Lexing.lexeme_start lexbuf;
61 Common.str = Lexing.lexeme lexbuf;
62 (* info filled in a post-lexing phase *)
63 Common.line = -1;
64 Common.column = -1;
65 Common.file = "";
66 };
67 (* must generate a new ref each time, otherwise share *)
68 cocci_tag = ref Ast_c.emptyAnnot;
69 comments_tag = ref Ast_c.emptyComments;
70 }
71
72 (* cppext: must generate a new ref each time, otherwise share *)
73 let no_ifdef_mark () = ref (None: (int * int) option)
74
75 let tok_add_s s ii = Ast_c.rewrap_str ((Ast_c.str_of_info ii) ^ s) ii
76
77
78 (* opti: less convenient, but using a hash is faster than using a match *)
79 let keyword_table = Common.hash_of_list [
80
81 (* c: *)
82 "void", (fun ii -> Tvoid ii);
83 "char", (fun ii -> Tchar ii);
84 "short", (fun ii -> Tshort ii);
85 "int", (fun ii -> Tint ii);
86 "long", (fun ii -> Tlong ii);
87 "float", (fun ii -> Tfloat ii);
88 "double", (fun ii -> Tdouble ii);
89
90 "unsigned", (fun ii -> Tunsigned ii);
91 "signed", (fun ii -> Tsigned ii);
92
93 "auto", (fun ii -> Tauto ii);
94 "register", (fun ii -> Tregister ii);
95 "extern", (fun ii -> Textern ii);
96 "static", (fun ii -> Tstatic ii);
97
98 "const", (fun ii -> Tconst ii);
99 "volatile", (fun ii -> Tvolatile ii);
100
101 "struct", (fun ii -> Tstruct ii);
102 "union", (fun ii -> Tunion ii);
103 "enum", (fun ii -> Tenum ii);
104 "typedef", (fun ii -> Ttypedef ii);
105
106 "if", (fun ii -> Tif ii);
107 "else", (fun ii -> Telse ii);
108 "break", (fun ii -> Tbreak ii);
109 "continue", (fun ii -> Tcontinue ii);
110 "switch", (fun ii -> Tswitch ii);
111 "case", (fun ii -> Tcase ii);
112 "default", (fun ii -> Tdefault ii);
113 "for", (fun ii -> Tfor ii);
114 "do", (fun ii -> Tdo ii);
115 "while", (fun ii -> Twhile ii);
116 "return", (fun ii -> Treturn ii);
117 "goto", (fun ii -> Tgoto ii);
118
119 "sizeof", (fun ii -> Tsizeof ii);
120
121
122 (* gccext: cppext: linuxext: synonyms *)
123 "asm", (fun ii -> Tasm ii);
124 "__asm__", (fun ii -> Tasm ii);
125 "__asm", (fun ii -> Tasm ii);
126
127 "inline", (fun ii -> Tinline ii);
128 "__inline__", (fun ii -> Tinline ii);
129 "__inline", (fun ii -> Tinline ii);
130
131 "__attribute__", (fun ii -> Tattribute ii);
132 "__attribute", (fun ii -> Tattribute ii);
133
134 "typeof", (fun ii -> Ttypeof ii);
135 "__typeof__", (fun ii -> Ttypeof ii);
136 "__typeof", (fun ii -> Ttypeof ii);
137
138 (* found a lot in expanded code *)
139 "__extension__", (fun ii -> TattributeNoarg ii);
140
141
142 (* gccext: alias *)
143 "__signed__", (fun ii -> Tsigned ii);
144
145 "__const__", (fun ii -> Tconst ii);
146 "__const", (fun ii -> Tconst ii);
147
148 "__volatile__", (fun ii -> Tvolatile ii);
149 "__volatile", (fun ii -> Tvolatile ii);
150
151 (* windowsext: *)
152 "__declspec", (fun ii -> Tattribute ii);
153
154 "__stdcall", (fun ii -> TattributeNoarg ii);
155 "__cdecl", (fun ii -> TattributeNoarg ii);
156 "WINAPI", (fun ii -> TattributeNoarg ii);
157 "APIENTRY", (fun ii -> TattributeNoarg ii);
158 "CALLBACK", (fun ii -> TattributeNoarg ii);
159
160 (* c99: *)
161 (* no just "restrict" ? maybe for backward compatibility they avoided
162 * to use restrict which people may have used in their program already
163 *)
164 "__restrict", (fun ii -> Trestrict ii);
165 "__restrict__", (fun ii -> Trestrict ii);
166
167 ]
168
169 let error_radix s =
170 ("numeric " ^ s ^ " constant contains digits beyond the radix:")
171
172 (* julia: functions for figuring out the type of integers *)
173
174 let is_long_dec s int uint long ulong =
175 match !Flag_parsing_c.int_thresholds with
176 None -> int
177 | Some (_,_,uint_threshold,long_threshold,ulong_threshold) ->
178 let bn = Big_int.big_int_of_string s in
179 if Big_int.ge_big_int bn ulong_threshold
180 then ulong
181 else
182 if Big_int.ge_big_int bn long_threshold
183 then long
184 else
185 if Big_int.ge_big_int bn uint_threshold
186 then long
187 else int
188
189 let is_long_ho s int uint long ulong drop bpd count =
190 match !Flag_parsing_c.int_thresholds with
191 None -> int
192 | Some (uint_sz,ulong_sz,_,_,_) ->
193 let len = String.length s in
194 (* this assumes that all of the hex/oct digits are significant *)
195 (* drop is 2 for hex (0x) and 1 for oct (0) *)
196 let s = String.sub s drop (len - drop) in
197 let len =
198 ((len-drop) * bpd) -
199 (count (int_of_string("0x"^(String.sub s 0 1)))) in
200 if len < uint_sz
201 then int
202 else
203 if len = uint_sz
204 then uint
205 else
206 if len < ulong_sz
207 then long
208 else ulong
209
210 let is_long_oct s int uint long ulong =
211 is_long_ho s int uint long ulong 1 3
212 (* stupid, but probably more efficient than taking logs *)
213 (function 0 -> 3 | 1 -> 2 | n when n < 4 -> 1 | _ -> 0)
214 let is_long_hex s int uint long ulong =
215 is_long_ho s int uint long ulong 2 4
216 (* stupid, but probably more efficient than taking logs *)
217 (function 0 -> 4 | 1 -> 3 | n when n < 4 -> 2 | n when n < 8 -> 1
218 | _ -> 0)
219
220 let sint = (Signed,CInt)
221 let uint = (UnSigned,CInt)
222 let slong = (Signed,CLong)
223 let ulong = (UnSigned,CLong)
224
225 }
226
227 (*****************************************************************************)
228 let letter = ['A'-'Z' 'a'-'z' '_']
229 let digit = ['0'-'9']
230
231 (* not used for the moment *)
232 let punctuation = ['!' '"' '#' '%' '&' '\'' '(' ')' '*' '+' ',' '-' '.' '/' ':'
233 ';' '<' '=' '>' '?' '[' '\\' ']' '^' '{' '|' '}' '~']
234 let space = [' ' '\t' '\n' '\r' '\011' '\012' ]
235 let additionnal = [ ' ' '\b' '\t' '\011' '\n' '\r' '\007' ]
236 (* 7 = \a = bell in C. this is not the only char allowed !!
237 * ex @ and $ ` are valid too
238 *)
239
240 let cchar = (letter | digit | punctuation | additionnal)
241
242 let sp = [' ' '\t']+
243 let spopt = [' ' '\t']*
244
245 let dec = ['0'-'9']
246 let oct = ['0'-'7']
247 let hex = ['0'-'9' 'a'-'f' 'A'-'F']
248
249 let decimal = ('0' | (['1'-'9'] dec*))
250 let octal = ['0'] oct+
251 let hexa = ("0x" |"0X") hex+
252
253
254 let pent = dec+
255 let pfract = dec+
256 let sign = ['-' '+']
257 let exp = ['e''E'] sign? dec+
258 let real = pent exp | ((pent? '.' pfract | pent '.' pfract? ) exp?)
259
260 let id = letter (letter | digit) *
261
262 (*****************************************************************************)
263 rule token = parse
264
265 (* ----------------------------------------------------------------------- *)
266 (* spacing/comments *)
267 (* ----------------------------------------------------------------------- *)
268
269 (* note: this lexer generate tokens for comments!! so can not give
270 * this lexer as-is to the parsing function. The caller must preprocess
271 * it, e.g. by using techniques like cur_tok ref in parse_c.ml.
272 *
273 * update: we now also generate a separate token for newlines, so now
274 * the caller may also have to reagglomerate all those commentspace
275 * tokens if he was assuming that spaces were agglomerate in a single
276 * token.
277 *)
278
279 | ['\n'] [' ' '\t' '\r' '\011' '\012' ]*
280 (* starting a new line; the newline character followed by whitespace *)
281 { TCommentNewline (tokinfo lexbuf) }
282 | [' ' '\t' '\r' '\011' '\012' ]+
283 { TCommentSpace (tokinfo lexbuf) }
284 | "/*"
285 { let info = tokinfo lexbuf in
286 let com = comment lexbuf in
287
288 let info' = info +> tok_add_s com in
289 let s = Ast_c.str_of_info info' in
290 (* could be more flexible, use [\t ]* instead of hardcoded
291 * single space. *)
292 match s with
293 | "/* {{coccinelle:skip_start}} */" ->
294 TCommentSkipTagStart (info')
295 | "/* {{coccinelle:skip_end}} */" ->
296 TCommentSkipTagEnd (info')
297 | _ -> TComment(info')
298 }
299
300
301 (* C++ comment are allowed via gccext, but normally they are deleted by cpp.
302 * So need this here only when dont call cpp before.
303 * note that we don't keep the trailing \n; it will be in another token.
304 *)
305 | "//" [^'\r' '\n' '\011']* { TComment (tokinfo lexbuf) }
306
307 (* ----------------------------------------------------------------------- *)
308 (* cpp *)
309 (* ----------------------------------------------------------------------- *)
310
311 (* old:
312 * | '#' { endline lexbuf} // should be line, and not endline
313 * and endline = parse | '\n' { token lexbuf}
314 * | _ { endline lexbuf}
315 *)
316
317 (* less?:
318 * have found a # #else in "newfile-2.6.c", legal ? and also a #/* ...
319 * => just "#" -> token {lexbuf} (that is ignore)
320 * il y'a 1 #elif sans rien apres
321 * il y'a 1 #error sans rien apres
322 * il y'a 2 mov dede, #xxx qui genere du coup exn car
323 * entouré par des #if 0
324 * => make as for comment, call a comment_cpp that when #endif finish the
325 * comment and if other cpp stuff raise exn
326 * il y'a environ 10 #if(xxx) ou le ( est collé direct
327 * il y'a des include"" et include<
328 * il y'a 1 ` (derriere un #ifndef linux)
329 *)
330
331
332
333 (* ---------------------- *)
334 (* misc *)
335 (* ---------------------- *)
336
337 (* bugfix: I want now to keep comments for the cComment study
338 * so cant do: sp [^'\n']+ '\n'
339 * http://gcc.gnu.org/onlinedocs/gcc/Pragmas.html
340 *)
341
342 | "#" spopt "pragma" sp [^'\n']* '\n'
343 | "#" spopt "ident" sp [^'\n']* '\n'
344 | "#" spopt "line" sp [^'\n']* '\n'
345 | "#" spopt "error" sp [^'\n']* '\n'
346 | "#" spopt "warning" sp [^'\n']* '\n'
347 | "#" spopt "abort" sp [^'\n']* '\n'
348 { TCppDirectiveOther (tokinfo lexbuf) }
349
350 | "#" [' ' '\t']* '\n'
351 { TCppDirectiveOther (tokinfo lexbuf) }
352
353 (* only after cpp, ex: # 1 "include/linux/module.h" 1 *)
354 | "#" sp pent sp '"' [^ '"']* '"' (spopt pent)* spopt '\n'
355 { TCppDirectiveOther (tokinfo lexbuf) }
356
357
358
359 (* ---------------------- *)
360 (* #define, #undef *)
361 (* ---------------------- *)
362
363 (* the rest of the lexing/parsing of define is done in fix_tokens_define
364 * where we parse until a TCppEscapedNewline and generate a TDefEol
365 *)
366 | "#" [' ' '\t']* "define" { TDefine (tokinfo lexbuf) }
367
368 (* note: in some cases can have stuff after the ident as in #undef XXX 50,
369 * but I currently don't handle it cos I think it's bad code.
370 *)
371 | (("#" [' ' '\t']* "undef" [' ' '\t']+) as _undef) (id as id)
372 { let info = tokinfo lexbuf in
373 TUndef (id, info)
374 (*+> tok_add_s (cpp_eat_until_nl lexbuf))*)
375 }
376
377
378 (* ---------------------- *)
379 (* #include *)
380 (* ---------------------- *)
381
382 (* The difference between a local "" and standard <> include is computed
383 * later in parser_c.mly. So redo a little bit of lexing there; ugly but
384 * simpler to generate a single token here. *)
385 | (("#" [' ''\t']* "include" [' ' '\t']*) as includes)
386 (('"' ([^ '"']+) '"' |
387 '<' [^ '>']+ '>' |
388 ['A'-'Z''_']+
389 ) as filename)
390 { let info = tokinfo lexbuf in
391 TInclude (includes, filename, Ast_c.noInIfdef(), info)
392 }
393 (* gccext: found in glibc *)
394 | (("#" [' ''\t']* "include_next" [' ' '\t']*) as includes)
395 (('"' ([^ '"']+) '"' |
396 '<' [^ '>']+ '>' |
397 ['A'-'Z''_']+
398 ) as filename)
399 { let info = tokinfo lexbuf in
400 TInclude (includes, filename, Ast_c.noInIfdef(), info)
401 }
402
403 (* ---------------------- *)
404 (* #ifdef *)
405 (* ---------------------- *)
406
407 (* The ifdef_mark will be set later in Parsing_hacks.set_ifdef_parenthize_info
408 * when working on the ifdef view.
409 *)
410
411 (* '0'+ because sometimes it is a #if 000 *)
412 | "#" [' ' '\t']* "if" [' ' '\t']* '0'+ (* [^'\n']* '\n' *)
413 { let info = tokinfo lexbuf in
414 TIfdefBool (false, no_ifdef_mark(), info)
415 (* +> tok_add_s (cpp_eat_until_nl lexbuf)*)
416 }
417
418 | "#" [' ' '\t']* "if" [' ' '\t']* '1' (* [^'\n']* '\n' *)
419 { let info = tokinfo lexbuf in
420 TIfdefBool (true, no_ifdef_mark(), info)
421
422 }
423
424 (* DO NOT cherry pick to lexer_cplusplus !!! often used for the extern "C" { *)
425 | "#" [' ' '\t']* "if" sp "defined" sp "(" spopt "__cplusplus" spopt ")" [^'\n']* '\n'
426 { let info = tokinfo lexbuf in
427 TIfdefMisc (false, no_ifdef_mark(), info)
428 }
429
430 (* DO NOT cherry pick to lexer_cplusplus !!! *)
431 | "#" [' ' '\t']* "ifdef" [' ' '\t']* "__cplusplus" [^'\n']* '\n'
432 { let info = tokinfo lexbuf in
433 TIfdefMisc (false, no_ifdef_mark(), info)
434 }
435
436 (* in glibc *)
437 | "#" spopt ("ifdef"|"if") sp "__STDC__"
438 { let info = tokinfo lexbuf in
439 TIfdefVersion (true, no_ifdef_mark(),
440 info +> tok_add_s (cpp_eat_until_nl lexbuf))
441 }
442
443
444 (* linuxext: different possible variations (we do not manage all of them):
445
446 #if LINUX_VERSION_CODE >= KERNEL_VERSION(2,4,0)
447 #if LINUX_VERSION_CODE <= KERNEL_VERSION(2,4,2)
448 #if LINUX_VERSION_CODE < KERNEL_VERSION(2,5,0)
449 #if LINUX_VERSION_CODE > KERNEL_VERSION(2,3,0)
450 #if LINUX_VERSION_CODE < 0x020600
451 #if LINUX_VERSION_CODE >= 0x2051c
452 #if (LINUX_VERSION_CODE < KERNEL_VERSION(2,5,0))
453 #if !(LINUX_VERSION_CODE > KERNEL_VERSION(2,5,73))
454 #if STREAMER_IOCTL && (LINUX_VERSION_CODE < KERNEL_VERSION(2,5,0))
455 #if LINUX_VERSION_CODE >= KERNEL_VERSION(2,4,20) && LINUX_VERSION_CODE < KERNEL_VERSION(2,5,0)
456 #if LINUX_VERSION_CODE >= KERNEL_VERSION(2,4,20) && \
457 # if defined(MODULE) && LINUX_VERSION_CODE >= KERNEL_VERSION(2,1,30)
458 #if LINUX_VERSION_CODE > LinuxVersionCode(2,3,12)
459 #elif LINUX_VERSION_CODE >= KERNEL_VERSION(2,1,93)
460 #ifndef LINUX_VERSION_CODE
461 #if LINUX_VERSION_CODE < ASC_LINUX_VERSION(2,2,0) || \
462 (LINUX_VERSION_CODE > ASC_LINUX_VERSION(2,3,0) && \
463 LINUX_VERSION_CODE < ASC_LINUX_VERSION(2,4,0))
464 #if (KERNEL_VERSION(2,4,0) > LINUX_VERSION_CODE)
465 #if LINUX_VERSION_CODE >= ASC_LINUX_VERSION(1,3,0)
466 # if defined(MODULE) && LINUX_VERSION_CODE >= KERNEL_VERSION(2,1,30)
467
468 *)
469
470 (* linuxext: must be before the generic rules for if and ifdef *)
471 | "#" spopt "if" sp "("? "LINUX_VERSION_CODE" sp (">=" | ">") sp
472 { let info = tokinfo lexbuf in
473 TIfdefVersion (true, no_ifdef_mark(),
474 info +> tok_add_s (cpp_eat_until_nl lexbuf))
475 }
476 (* linuxext: *)
477 | "#" spopt "if" sp "!" "("? "LINUX_VERSION_CODE" sp (">=" | ">") sp
478 | "#" spopt "if" sp ['(']? "LINUX_VERSION_CODE" sp ("<=" | "<") sp
479
480 { let info = tokinfo lexbuf in
481 TIfdefVersion (false, no_ifdef_mark(),
482 info +> tok_add_s (cpp_eat_until_nl lexbuf))
483 }
484
485
486
487
488 (* can have some ifdef 0 hence the letter|digit even at beginning of word *)
489 | "#" [' ''\t']* "ifdef" [' ''\t']+ (letter|digit) ((letter|digit)*) [' ''\t']*
490 { TIfdef (no_ifdef_mark(), tokinfo lexbuf) }
491 | "#" [' ''\t']* "ifndef" [' ''\t']+ (letter|digit) ((letter|digit)*) [' ''\t']*
492 { TIfdef (no_ifdef_mark(), tokinfo lexbuf) }
493 | "#" [' ''\t']* "if" [' ' '\t']+
494 { let info = tokinfo lexbuf in
495 TIfdef (no_ifdef_mark(), info +> tok_add_s (cpp_eat_until_nl lexbuf))
496 }
497 | "#" [' ' '\t']* "if" '('
498 { let info = tokinfo lexbuf in
499 TIfdef (no_ifdef_mark(), info +> tok_add_s (cpp_eat_until_nl lexbuf))
500 }
501
502 | "#" [' ' '\t']* "elif" [' ' '\t']+
503 { let info = tokinfo lexbuf in
504 TIfdefelif (no_ifdef_mark(), info +> tok_add_s (cpp_eat_until_nl lexbuf))
505 }
506
507
508 (* bugfix: can have #endif LINUX but at the same time if I eat everything
509 * until next line, I may miss some TComment which for some tools
510 * are important such as aComment
511 *)
512 | "#" [' ' '\t']* "endif" (*[^'\n']* '\n'*) {
513 TEndif (no_ifdef_mark(), tokinfo lexbuf)
514 }
515 (* can be at eof *)
516 (*| "#" [' ' '\t']* "endif" { TEndif (tokinfo lexbuf) }*)
517
518 | "#" [' ' '\t']* "else" [' ' '\t' '\n']
519 { TIfdefelse (no_ifdef_mark(), tokinfo lexbuf) }
520
521
522
523
524 (* ---------------------- *)
525 (* #define body *)
526 (* ---------------------- *)
527
528 (* only in cpp directives normally *)
529 | "\\" '\n' { TCppEscapedNewline (tokinfo lexbuf) }
530
531 (* We must generate separate tokens for #, ## and extend the grammar.
532 * Note there can be "elaborated" idents in many different places, in
533 * expression but also in declaration, in function name. So having 3 tokens
534 * for an ident does not work well with how we add info in
535 * ast_c. Was easier to generate just one token, just one info,
536 * even if have later to reanalyse those tokens and unsplit. But then,
537 * handling C++ lead to having not just a string for ident but something
538 * more complex. Also when we want to parse elaborated function headers
539 * (e.g. void METH(foo)(int x)), we need anyway to go from a string
540 * to something more. So having also for C something more than just
541 * string for ident is natural.
542 *
543 * todo: our heuristics in parsing_hacks rely on TIdent. So maybe
544 * an easier solution would be to augment the TIdent type such as
545 * TIdent of string * info * cpp_ident_additionnal_info
546 *
547 * old:
548 * | id ([' ''\t']* "##" [' ''\t']* id)+
549 * { let info = tokinfo lexbuf in
550 * TIdent (tok lexbuf, info)
551 * }
552 * | "##" spopt id
553 * { let info = tokinfo lexbuf in
554 * TIdent (tok lexbuf, info)
555 * }
556 *
557 *)
558 (* cppext: string concatenation of idents, also ##args for variadic macro. *)
559 | "##" { TCppConcatOp (tokinfo lexbuf) }
560
561 (* cppext: stringification.
562 * bugfix: this case must be after the other cases such as #endif
563 * otherwise take precedent.
564 *)
565 | "#" spopt id
566 { let info = tokinfo lexbuf in
567 TIdent (tok lexbuf, info)
568 }
569 (* the ... next to id, e.g. arg..., works with ##, e.g. ##arg *)
570 | ((id as s) "...")
571 { TDefParamVariadic (s, tokinfo lexbuf) }
572
573
574
575
576
577 (* ----------------------------------------------------------------------- *)
578 (* C symbols *)
579 (* ----------------------------------------------------------------------- *)
580 (* stdC:
581 ... && -= >= ~ + ; ]
582 <<= &= -> >> % , < ^
583 >>= *= /= ^= & - = {
584 != ++ << |= ( . > |
585 %= += <= || ) / ? }
586 -- == ! * : [
587 recent addition: <: :> <% %>
588 only at processing: %: %:%: # ##
589 *)
590
591
592 | '[' { TOCro(tokinfo lexbuf) } | ']' { TCCro(tokinfo lexbuf) }
593 | '(' { TOPar(tokinfo lexbuf) } | ')' { TCPar(tokinfo lexbuf) }
594 | '{' { TOBrace(tokinfo lexbuf) } | '}' { TCBrace(tokinfo lexbuf) }
595
596 | '+' { TPlus(tokinfo lexbuf) } | '*' { TMul(tokinfo lexbuf) }
597 | '-' { TMinus(tokinfo lexbuf) } | '/' { TDiv(tokinfo lexbuf) }
598 | '%' { TMod(tokinfo lexbuf) }
599
600 | "++"{ TInc(tokinfo lexbuf) } | "--"{ TDec(tokinfo lexbuf) }
601
602 | "=" { TEq(tokinfo lexbuf) }
603
604 | "-=" { TAssign (OpAssign Minus, (tokinfo lexbuf))}
605 | "+=" { TAssign (OpAssign Plus, (tokinfo lexbuf))}
606 | "*=" { TAssign (OpAssign Mul, (tokinfo lexbuf))}
607 | "/=" { TAssign (OpAssign Div, (tokinfo lexbuf))}
608 | "%=" { TAssign (OpAssign Mod, (tokinfo lexbuf))}
609 | "&=" { TAssign (OpAssign And, (tokinfo lexbuf))}
610 | "|=" { TAssign (OpAssign Or, (tokinfo lexbuf)) }
611 | "^=" { TAssign (OpAssign Xor, (tokinfo lexbuf))}
612 | "<<=" {TAssign (OpAssign DecLeft, (tokinfo lexbuf)) }
613 | ">>=" {TAssign (OpAssign DecRight, (tokinfo lexbuf))}
614
615 | "==" { TEqEq(tokinfo lexbuf) } | "!=" { TNotEq(tokinfo lexbuf) }
616 | ">=" { TSupEq(tokinfo lexbuf) } | "<=" { TInfEq(tokinfo lexbuf) }
617 | "<" { TInf(tokinfo lexbuf) } | ">" { TSup(tokinfo lexbuf) }
618
619 | "&&" { TAndLog(tokinfo lexbuf) } | "||" { TOrLog(tokinfo lexbuf) }
620 | ">>" { TShr(tokinfo lexbuf) } | "<<" { TShl(tokinfo lexbuf) }
621 | "&" { TAnd(tokinfo lexbuf) } | "|" { TOr(tokinfo lexbuf) }
622 | "^" { TXor(tokinfo lexbuf) }
623 | "..." { TEllipsis(tokinfo lexbuf) }
624 | "->" { TPtrOp(tokinfo lexbuf) } | '.' { TDot(tokinfo lexbuf) }
625 | ',' { TComma(tokinfo lexbuf) }
626 | ";" { TPtVirg(tokinfo lexbuf) }
627 | "?" { TWhy(tokinfo lexbuf) } | ":" { TDotDot(tokinfo lexbuf) }
628 | "!" { TBang(tokinfo lexbuf) } | "~" { TTilde(tokinfo lexbuf) }
629
630 | "<:" { TOCro(tokinfo lexbuf) } | ":>" { TCCro(tokinfo lexbuf) }
631 | "<%" { TOBrace(tokinfo lexbuf) } | "%>" { TCBrace(tokinfo lexbuf) }
632
633
634
635 (* ----------------------------------------------------------------------- *)
636 (* C keywords and ident *)
637 (* ----------------------------------------------------------------------- *)
638
639 (* StdC: must handle at least name of length > 509, but can
640 * truncate to 31 when compare and truncate to 6 and even lowerise
641 * in the external linkage phase
642 *)
643 | letter (letter | digit) *
644 { let info = tokinfo lexbuf in
645 let s = tok lexbuf in
646 Common.profile_code "C parsing.lex_ident" (fun () ->
647 match Common.optionise (fun () -> Hashtbl.find keyword_table s)
648 with
649 | Some f -> f info
650
651 (* parse_typedef_fix.
652 * if Lexer_parser.is_typedef s
653 * then TypedefIdent (s, info)
654 * else TIdent (s, info)
655 *
656 * update: now this is no more useful, cos
657 * as we use tokens_all, it first parse all as an ident and
658 * later transform an indent in a typedef. so the typedef job is
659 * now done in parse_c.ml.
660 *)
661
662 | None -> TIdent (s, info)
663 )
664 }
665 (* gccext: apparently gcc allows dollar in variable names. found such
666 * thing a few time in linux and in glibc. No need look in keyword_table
667 * here.
668 *)
669 | (letter | '$') (letter | digit | '$') *
670 {
671 let info = tokinfo lexbuf in
672 let s = tok lexbuf in
673 pr2 ("LEXER: identifier with dollar: " ^ s);
674 TIdent (s, info)
675 }
676
677
678 (* ----------------------------------------------------------------------- *)
679 (* C constant *)
680 (* ----------------------------------------------------------------------- *)
681
682 | "'"
683 { let info = tokinfo lexbuf in
684 let s = char lexbuf in
685 TChar ((s, IsChar), (info +> tok_add_s (s ^ "'")))
686 }
687 | '"'
688 { let info = tokinfo lexbuf in
689 let s = string lexbuf in
690 TString ((s, IsChar), (info +> tok_add_s (s ^ "\"")))
691 }
692 (* wide character encoding, TODO L'toto' valid ? what is allowed ? *)
693 | 'L' "'"
694 { let info = tokinfo lexbuf in
695 let s = char lexbuf in
696 TChar ((s, IsWchar), (info +> tok_add_s (s ^ "'")))
697 }
698 | 'L' '"'
699 { let info = tokinfo lexbuf in
700 let s = string lexbuf in
701 TString ((s, IsWchar), (info +> tok_add_s (s ^ "\"")))
702 }
703
704
705 (* Take care of the order ? No because lex tries the longest match. The
706 * strange diff between decimal and octal constant semantic is not
707 * understood too by refman :) refman:11.1.4, and ritchie.
708 *)
709
710 | decimal as x
711 { TInt ((x, is_long_dec x sint slong slong ulong), tokinfo lexbuf) }
712 | hexa as x
713 { TInt ((x, is_long_hex x sint uint slong ulong), tokinfo lexbuf) }
714 | octal as x
715 { TInt ((x, is_long_oct x sint uint slong ulong), tokinfo lexbuf) }
716 | ((decimal as s) ['u' 'U']) as x
717 { TInt ((x, is_long_dec s uint uint ulong ulong), tokinfo lexbuf) }
718 | ((hexa as s) ['u' 'U']) as x
719 { TInt ((x, is_long_hex s uint uint ulong ulong), tokinfo lexbuf) }
720 | ((octal as s) ['u' 'U']) as x
721 { TInt ((x, is_long_oct s uint uint ulong ulong), tokinfo lexbuf) }
722 | (( decimal as s) ['l' 'L']) as x
723 { TInt ((x, is_long_dec s slong slong slong ulong), tokinfo lexbuf) }
724 | ((hexa as s) ['l' 'L']) as x
725 { TInt ((x, is_long_hex s slong slong slong ulong), tokinfo lexbuf) }
726 | ((octal as s) ['l' 'L']) as x
727 { TInt ((x, is_long_oct s slong slong slong ulong), tokinfo lexbuf) }
728 | ((( decimal | hexa | octal) ['l' 'L'] ['u' 'U'])
729 | (( decimal | hexa | octal) ['u' 'U'] ['l' 'L'])) as x
730 { TInt ((x, (UnSigned,CLong)), tokinfo lexbuf) }
731 | (( decimal | hexa | octal) ['l' 'L'] ['l' 'L']) as x
732 { TInt ((x, (Signed,CLongLong)), tokinfo lexbuf) }
733 | (( decimal | hexa | octal) ['u' 'U'] ['l' 'L'] ['l' 'L']) as x
734 { TInt ((x, (UnSigned,CLongLong)), tokinfo lexbuf) }
735
736 | (real ['f' 'F']) as x { TFloat ((x, CFloat), tokinfo lexbuf) }
737 | (real ['l' 'L']) as x { TFloat ((x, CLongDouble), tokinfo lexbuf) }
738 | (real as x) { TFloat ((x, CDouble), tokinfo lexbuf) }
739
740 | ['0'] ['0'-'9']+
741 { pr2 ("LEXER: " ^ error_radix "octal" ^ tok lexbuf);
742 TUnknown (tokinfo lexbuf)
743 }
744 | ("0x" |"0X") ['0'-'9' 'a'-'z' 'A'-'Z']+
745 { pr2 ("LEXER: " ^ error_radix "hexa" ^ tok lexbuf);
746 TUnknown (tokinfo lexbuf)
747 }
748
749
750 (* !!! to put after other rules !!! otherwise 0xff
751 * will be parsed as an ident.
752 *)
753 | ['0'-'9']+ letter (letter | digit) *
754 { pr2 ("LEXER: ZARB integer_string, certainly a macro:" ^ tok lexbuf);
755 TIdent (tok lexbuf, tokinfo lexbuf)
756 }
757
758 (* gccext: http://gcc.gnu.org/onlinedocs/gcc/Binary-constants.html *)
759 (*
760 | "0b" ['0'-'1'] { TInt (((tok lexbuf)<!!>(??,??)) +> int_of_stringbits) }
761 | ['0'-'1']+'b' { TInt (((tok lexbuf)<!!>(0,-2)) +> int_of_stringbits) }
762 *)
763
764
765 (*------------------------------------------------------------------------ *)
766 | eof { EOF (tokinfo lexbuf +> Ast_c.rewrap_str "") }
767
768 | _
769 {
770 if !Flag_parsing_c.verbose_lexing
771 then pr2_once ("LEXER:unrecognised symbol, in token rule:"^tok lexbuf);
772 TUnknown (tokinfo lexbuf)
773 }
774
775
776
777 (*****************************************************************************)
778 and char = parse
779 | (_ as x) "'" { String.make 1 x }
780 (* todo?: as for octal, do exception beyond radix exception ? *)
781 | (("\\" (oct | oct oct | oct oct oct)) as x "'") { x }
782 (* this rule must be after the one with octal, lex try first longest
783 * and when \7 we want an octal, not an exn.
784 *)
785 | (("\\x" ((hex | hex hex))) as x "'") { x }
786 | (("\\" (_ as v)) as x "'")
787 {
788 (match v with (* Machine specific ? *)
789 | 'n' -> () | 't' -> () | 'v' -> () | 'b' -> () | 'r' -> ()
790 | 'f' -> () | 'a' -> ()
791 | '\\' -> () | '?' -> () | '\'' -> () | '"' -> ()
792 | 'e' -> () (* linuxext: ? *)
793 | _ ->
794 pr2 ("LEXER: unrecognised symbol in char:"^tok lexbuf);
795 );
796 x
797 }
798 | _
799 { pr2 ("LEXER: unrecognised symbol in char:"^tok lexbuf);
800 tok lexbuf
801 }
802
803
804
805 (*****************************************************************************)
806
807 (* todo? factorise code with char ? but not same ending token so hard. *)
808 and string = parse
809 | '"' { "" }
810 | (_ as x) { string_of_char x^string lexbuf}
811 | ("\\" (oct | oct oct | oct oct oct)) as x { x ^ string lexbuf }
812 | ("\\x" (hex | hex hex)) as x { x ^ string lexbuf }
813 | ("\\" (_ as v)) as x
814 {
815 (match v with (* Machine specific ? *)
816 | 'n' -> () | 't' -> () | 'v' -> () | 'b' -> () | 'r' -> ()
817 | 'f' -> () | 'a' -> ()
818 | '\\' -> () | '?' -> () | '\'' -> () | '"' -> ()
819 | 'e' -> () (* linuxext: ? *)
820
821 (* old: "x" -> 10 gccext ? todo ugly, I put a fake value *)
822
823 (* cppext: can have \ for multiline in string too *)
824 | '\n' -> ()
825 | _ -> pr2 ("LEXER: unrecognised symbol in string:"^tok lexbuf);
826 );
827 x ^ string lexbuf
828 }
829
830 | eof { pr2 "LEXER: WIERD end of file in string"; ""}
831
832 (* Bug if add following code, cos match also the '"' that is needed
833 * to finish the string, and so go until end of file.
834 *)
835 (*
836 | [^ '\\']+
837 { let cs = lexbuf +> tok +> list_of_string +> List.map Char.code in
838 cs ++ string lexbuf
839 }
840 *)
841
842
843
844 (*****************************************************************************)
845
846 (* less: allow only char-'*' ? *)
847 and comment = parse
848 | "*/" { tok lexbuf }
849 (* noteopti: *)
850 | [^ '*']+ { let s = tok lexbuf in s ^ comment lexbuf }
851 | [ '*'] { let s = tok lexbuf in s ^ comment lexbuf }
852 | eof { pr2 "LEXER: end of file in comment"; "*/"}
853 | _
854 { let s = tok lexbuf in
855 pr2 ("LEXER: unrecognised symbol in comment:"^s);
856 s ^ comment lexbuf
857 }
858
859
860
861 (*****************************************************************************)
862
863 (* cpp recognize C comments, so when #define xx (yy) /* comment \n ... */
864 * then he has already erased the /* comment. So:
865 * - dont eat the start of the comment otherwise afterwards we are in the middle
866 * of a comment and so will problably get a parse error somewhere.
867 * - have to recognize comments in cpp_eat_until_nl.
868 *)
869
870 and cpp_eat_until_nl = parse
871 (* bugfix: *)
872 | "/*"
873 { let s = tok lexbuf in
874 let s2 = comment lexbuf in
875 let s3 = cpp_eat_until_nl lexbuf in
876 s ^ s2 ^ s3
877 }
878 | '\\' "\n" { let s = tok lexbuf in s ^ cpp_eat_until_nl lexbuf }
879
880 | "\n" { tok lexbuf }
881 (* noteopti:
882 * update: need also deal with comments chars now
883 *)
884 | [^ '\n' '\\' '/' '*' ]+
885 { let s = tok lexbuf in s ^ cpp_eat_until_nl lexbuf }
886 | eof { pr2 "LEXER: end of file in cpp_eat_until_nl"; ""}
887 | _ { let s = tok lexbuf in s ^ cpp_eat_until_nl lexbuf }