]> andersk Git - splint.git/blob - src/cscanner.l
*** empty log message ***
[splint.git] / src / cscanner.l
1 /*;-*-C-*-; 
2 ** Copyright (c) Massachusetts Institute of Technology 1994-1998.
3 **          All Rights Reserved.
4 **          Unpublished rights reserved under the copyright laws of
5 **          the United States.
6 **
7 ** THIS MATERIAL IS PROVIDED AS IS, WITH ABSOLUTELY NO WARRANTY EXPRESSED
8 ** OR IMPLIED.  ANY USE IS AT YOUR OWN RISK.
9 **
10 ** This code is distributed freely and may be used freely under the 
11 ** following conditions:
12 **
13 **     1. This notice may not be removed or altered.
14 **
15 **     2. Works derived from this code are not distributed for
16 **        commercial gain without explicit permission from MIT 
17 **        (for permission contact lclint-request@sds.lcs.mit.edu).
18 */
19 /*
20  * Modified by Herbert 08/19/97:
21  * - added #include for IBM's OS/2 compiler.
22  * - fixed weird bug with lookup of tmp files (OS/2 and MSDOS only).
23  */
24
25 /*
26  * Modified by Mike Smith 
27  * Corrected missing 'line' in scanf() calls in handleSpecial().
28  * Without this, I get an error when LCLint hits a '#line' directive
29  * in the pre-pre-processed source files. For safety, I have made these
30  * conditional on OS2 and MSDOS because I don't understand why noone else
31  * has seen this problem.
32  *
33  * Modified by Mike Smith, 4th June 1997
34  * Finally resolved the #line problem.  The scanf() calls have been fixed to
35  * allow the following #line forms:-
36  *
37  *        #line 123 "filename"
38  *        #line 123
39  *        # 123 "filename"
40  *        # 123
41  *
42  * The last two are generated by the GNU pre-processor, apparently
43  */
44
45 Digit                   [0-9]
46 Letter                  [a-zA-Z_$]
47 H                       [a-fA-F0-9]
48 E                       [Ee][+-]?{Digit}+
49 U                       (u|U)
50 L                       (l|L)
51 FS                      (f|F|l|L)
52 IS                      (u|U|l|L)*
53 ULSuffix                ({U}{L}|{L}{U})
54
55 %{
56 /*
57 ** based on original C lexer by Nate Osgood
58 **    from hacrat@catfish.lcs.mit.edu Mon Jun 14 13:06:32 1993
59 **
60 */
61
62 # include "lclintMacros.nf"
63 # include <unistd.h>
64 # include "basic.h"
65
66 # include "cgrammar.h"
67 # include "cgrammar_tokens.h"
68
69 # include "fileIdList.h"
70 # include "portab.h"
71
72 # if defined(OS2) && defined(__IBMC__)
73    /* needed for isatty()... */
74 # include <io.h>
75 # endif
76
77 static bool lastWasString = FALSE;
78 static char savechar = '\0';
79
80 /*@notfunction@*/
81 # define yyinput() (incColumn (), getc (yyin))
82
83 static /*@owned@*/ cstring lastidprocessed = cstring_undefined;
84 static int lminput (void);
85 static int tokLength = 0;
86 static bool inSpecPart = FALSE;
87 static bool continueLine = FALSE;
88
89 static int ninput (void);
90 static char processChar (void);
91 static double processFloat (void);
92 static /*@only@*/ exprNode processString (void);
93 static long processDec (void);
94 static long processHex (void);
95 static long processOctal (void);
96 static int processIdentifier (/*@only@*/ cstring)
97    /*@globals undef lastidprocessed@*/ ;
98 static bool processHashIdentifier (/*@only@*/ cstring)
99    /*@globals undef lastidprocessed@*/ ;
100
101 static int processSpec (int);
102 static bool handleSpecial (char *);
103 static int handleLlSpecial (void);
104 static void handleMacro (void);
105 static bool processMacro (void);
106 static /*@only@*/ cstring makeIdentifier (char *);
107
108 /* yes, this is exported! */
109 bool g_expectingTypeName = TRUE; /* beginning of file can be type name! */
110
111 static bool expectingMetaStateName = FALSE;
112
113 static int returnInt (ctype, long);
114 static int returnFloat (ctype, double);
115 static int returnChar (char);
116 static void setTokLength (int) /*@modifies g_currentloc@*/ ;
117 static void setTokLengthT (size_t) /*@modifies g_currentloc@*/ ;
118
119 static void advanceLine (void)
120 {
121   tokLength = 0;
122   beginLine ();
123 }
124     
125 /*@-allmacros@*/
126 # define RETURN_INT(c,i) \
127   do { lastWasString = FALSE; \
128        return (returnInt (c, i)); } while (FALSE)
129
130 # define RETURN_FLOAT(c,f) \
131   do { lastWasString = FALSE; \
132        return (returnFloat (c, f)); \
133        } while (FALSE)
134
135 # define RETURN_CHAR(c) \
136   do { lastWasString = FALSE; \
137        return (returnChar (c)); \
138      } while (FALSE)
139
140 # define RETURN_TOK(t) \
141   do { yylval.tok = lltok_create (t, fileloc_decColumn (g_currentloc, tokLength)); \
142        tokLength = 0; \
143        lastWasString = FALSE; \
144        return (t); } while (FALSE)
145
146 # define RETURN_TYPE(t, ct) \
147   do { yylval.ctyp = ct; tokLength = 0; return (t); } while (FALSE)
148
149 /* don't fileloc_decColumn (g_currentloc, tokLength));  
150    the string could have \n's in it!
151 */
152
153 # define RETURN_STRING(c) \
154  do { yylval.expr = exprNode_stringLiteral (c, fileloc_decColumn (g_currentloc, tokLength)); \
155       tokLength = 0; \
156       lastWasString = TRUE; \
157       return (CCONSTANT); } while (FALSE)
158
159 # define RETURN_EXPR(e) \
160  do { yylval.expr = e; \
161       tokLength = 0; \
162       lastWasString = TRUE; \
163       return (CCONSTANT); } while (FALSE)
164
165 /*@=allmacros@*/
166
167 static void setTokLength (int len) 
168 {
169   addColumn (len);
170   tokLength = len;
171 }
172
173 static void setTokLengthT (size_t len)
174 {
175   setTokLength (size_toInt (len));
176 }
177
178 # include "flex.head"
179
180 /*@-unrecog@*/ /*@i5343@*/
181
182 %}
183
184 %%
185
186 "/*"            { llfatalbug (cstring_makeLiteral ("Comment in pre-processor output")); }
187
188 "#"{Letter}({Letter}|{Digit})*  { 
189                  context_saveLocation (); 
190                  setTokLength (longUnsigned_toInt (mstring_length (yytext))); 
191
192                  if (processHashIdentifier (makeIdentifier (yytext + 1)))
193                    {
194                      if (lastWasString)
195                        {
196                          /* was nothing! */ /*@i32@*/
197                          RETURN_STRING (cstring_makeLiteral ("\"\""));
198                        }
199                      else
200                        {
201                          RETURN_STRING (cstring_makeLiteral ("\"\""));
202                        }
203                    }
204                  else
205                    { 
206                      if (handleSpecial (yytext)) 
207                        { 
208                          setTokLength (1); 
209                          RETURN_TOK (0); 
210                        }
211                    }
212                 } 
213 "#"             { if (handleSpecial (yytext)) 
214                     { 
215                        setTokLength (1); RETURN_TOK (0); 
216                      }
217                 }
218 "..."           { setTokLength (3); RETURN_TOK (CTOK_ELIPSIS); }
219 "break"         { setTokLength (5); RETURN_TOK (BREAK); }
220 "case"          { setTokLength (4); RETURN_TOK (CASE); }
221 "continue"      { setTokLength (8); RETURN_TOK (CONTINUE); }
222 "default"       { setTokLength (7); RETURN_TOK (DEFAULT); }
223 "do"            { setTokLength (2); RETURN_TOK (DO); }
224 "else"          { setTokLength (4); RETURN_TOK (CELSE); }
225 "for"           { setTokLength (3); RETURN_TOK (CFOR); }
226 "goto"          { setTokLength (4); RETURN_TOK (GOTO); }
227 "if"            { setTokLength (2); RETURN_TOK (CIF); }
228 "return"        { setTokLength (6); RETURN_TOK (RETURN); }
229 "sizeof"        { setTokLength (6); RETURN_TOK (CSIZEOF); }
230 "offsetof"      { setTokLength (8); RETURN_TOK (COFFSETOF); }
231 "switch"        { setTokLength (6); RETURN_TOK (SWITCH); }
232 "while"         { setTokLength (5); RETURN_TOK (WHILE); }
233 "va_arg"        { setTokLength (6); RETURN_TOK (VA_ARG); }   
234 "va_dcl"        { setTokLength (6); RETURN_TOK (VA_DCL); }   
235 "inline"        { 
236                   /* gcc extension...this might not be appropriate */
237                   setTokLength (6); RETURN_TOK (QINLINE); }
238
239 "struct"        { setTokLength (6); RETURN_TOK (CSTRUCT); }  
240 "typedef"       { setTokLength (7); RETURN_TOK (CTYPEDEF); }
241
242 "union"         { setTokLength (5); RETURN_TOK (CUNION); }
243 "enum"          { setTokLength (4); RETURN_TOK (CENUM); }
244
245 "void"          { setTokLength (4); RETURN_TYPE (CVOID, ctype_void); }
246 "int"           { setTokLength (3); RETURN_TYPE (CINT, ctype_int); }
247 "double"        { setTokLength (6); RETURN_TYPE (CDOUBLE, ctype_double); }
248 "char"          { setTokLength (4); RETURN_TYPE (CGCHAR, ctype_char); }
249 "float"         { setTokLength (5); RETURN_TYPE (CGFLOAT, ctype_float); }
250
251 "long"          { setTokLength (4); RETURN_TOK (QLONG); }
252 "short"         { setTokLength (5); RETURN_TOK (QSHORT); }
253 "unsigned"      { setTokLength (8); RETURN_TOK (QUNSIGNED); }
254 "signed"        { setTokLength (6); RETURN_TOK (QSIGNED); }
255
256 "volatile"      { setTokLength (8); RETURN_TOK (QVOLATILE); }
257 "const"         { setTokLength (5); RETURN_TOK (QCONST); }
258
259                         /* some systems expect this! [gack!] */ 
260 "__const"       { setTokLength (7); RETURN_TOK (QCONST); }
261
262 "extern"        { setTokLength (6); RETURN_TOK (QEXTERN); }
263 "auto"          { setTokLength (4); RETURN_TOK (QAUTO); }
264 "register"      { setTokLength (8); RETURN_TOK (QREGISTER); }
265 "static"        { setTokLength (6); RETURN_TOK (QSTATIC); }
266
267 \"(\\.|[^\\"])*\"([ \t\n]*\"(\\.|[^\\"])*\")* { RETURN_EXPR (processString ()); }
268 L\"(\\.|[^\\"])*\"([ \t\n]*\"(\\.|[^\\"])*\")* { RETURN_EXPR (processString ()); }
269 "out"                   { return (processSpec (QOUT)); }
270 "in"                    { return (processSpec (QIN)); }
271 "partial"               { return (processSpec (QPARTIAL)); }
272 "special"               { return (processSpec (QSPECIAL)); }
273 "anytype"               { return (processSpec (QANYTYPE)); }
274 "integraltype"          { return (processSpec (QINTEGRALTYPE)); }
275 "unsignedintegraltype"  { return (processSpec (QUNSIGNEDINTEGRALTYPE)); }
276 "signedintegraltype"    { return (processSpec (QSIGNEDINTEGRALTYPE)); }
277 "keep"                  { return (processSpec (QKEEP)); }
278 "null"                  { return (processSpec (QNULL)); } 
279 "notnull"               { return (processSpec (QNOTNULL)); } 
280 "isnull"                { return (processSpec (QISNULL)); } 
281 "truenull"              { return (processSpec (QTRUENULL)); } 
282 "falsenull"             { return (processSpec (QFALSENULL)); } 
283 "relnull"               { return (processSpec (QRELNULL)); }
284 "reldef"                { return (processSpec (QRELDEF)); }
285 "exposed"               { return (processSpec (QEXPOSED)); }
286 "newref"                { return (processSpec (QNEWREF)); }
287 "tempref"               { return (processSpec (QTEMPREF)); }
288 "killref"               { return (processSpec (QKILLREF)); }
289 "refcounted"            { return (processSpec (QREFCOUNTED)); }
290 "checked"               { return (processSpec (QCHECKED)); }
291 "checkmod"              { return (processSpec (QCHECKMOD)); }
292 "checkedstrict"         { return (processSpec (QCHECKEDSTRICT)); }
293 "unchecked"             { return (processSpec (QUNCHECKED)); }
294 "only"                  { return (processSpec (QONLY)); }
295 "owned"                 { return (processSpec (QOWNED)); }
296 "observer"              { return (processSpec (QOBSERVER)); }
297 "dependent"             { return (processSpec (QDEPENDENT)); }
298 "unused"                { return (processSpec (QUNUSED)); }
299 "external"              { return (processSpec (QEXTERNAL)); }
300 "sef"                   { return (processSpec (QSEF)); }
301 "shared"                { return (processSpec (QSHARED)); }
302 "yield"                 { return (processSpec (QYIELD)); }
303 "undef"                 { return (processSpec (QUNDEF)); }
304 "killed"                { return (processSpec (QKILLED)); }
305 "nullterminated"        { return (processSpec (QNULLTERMINATED));}
306 "MaxSet"                { return (processSpec (QMAXSET));}
307 "MaxRead"               { return (processSpec (QMAXREAD));}
308 "maxSet"                { return (processSpec (QMAXSET));}
309 "maxRead"               { return (processSpec (QMAXREAD));}
310
311 {Letter}({Letter}|{Digit})* { int tok; 
312                               context_saveLocation (); 
313                               setTokLength (longUnsigned_toInt (mstring_length (yytext))); 
314                               tok = processIdentifier (makeIdentifier (yytext)); 
315                               if (tok != BADTOK)
316                                 {
317                                   return (tok);
318                                 }
319                             }
320 0[xX]{H}+               { setTokLengthT (mstring_length (yytext)); 
321                           RETURN_INT (ctype_int, processHex ());  /* evs 2000-05-17 was ctype_uint */
322                         }
323 0[xX]{H}+{L}            { setTokLengthT (mstring_length (yytext)); 
324                           RETURN_INT (ctype_lint, processHex ()); }
325 0[xX]{H}+{L}{L}         { setTokLengthT (mstring_length (yytext)); 
326                           RETURN_INT (ctype_llint, processHex ()); }
327 0[xX]{H}+{U}            { setTokLengthT (mstring_length (yytext)); 
328                           RETURN_INT (ctype_uint, processHex ()); }
329 0[xX]{H}+{ULSuffix}     { setTokLengthT (mstring_length (yytext)); 
330                           RETURN_INT (ctype_ulint, processHex ()); }
331 0[xX]{H}+{U}{L}{L}      { setTokLengthT (mstring_length (yytext)); 
332                           RETURN_INT (ctype_ullint, processHex ()); }
333 0[xX]{H}+{L}{L}{U}      { setTokLengthT (mstring_length (yytext)); 
334                           RETURN_INT (ctype_ullint, processHex ()); }
335 0{Digit}+               { setTokLengthT (mstring_length (yytext)); 
336                           RETURN_INT (ctype_int, processOctal ()); } 
337 0{Digit}+{U}            { setTokLengthT (mstring_length (yytext)); 
338                           RETURN_INT (ctype_uint, processOctal ()); } 
339 0{Digit}+{L}            { setTokLengthT (mstring_length (yytext)); 
340                           RETURN_INT (ctype_lint, processOctal ()); } 
341 0{Digit}+{L}{L}         { setTokLengthT (mstring_length (yytext)); 
342                           RETURN_INT (ctype_llint, processOctal ()); } 
343 0{Digit}+{ULSuffix}     { setTokLengthT (mstring_length (yytext)); 
344                           RETURN_INT (ctype_ulint, processOctal ()); } 
345 0{Digit}+{U}{L}{L}      { setTokLengthT (mstring_length (yytext)); 
346                           RETURN_INT (ctype_ullint, processOctal ()); } 
347 0{Digit}+{L}{L}{U}      { setTokLengthT (mstring_length (yytext)); 
348                           RETURN_INT (ctype_ullint, processOctal ()); } 
349 {Digit}+               { setTokLengthT (mstring_length (yytext)); 
350                          RETURN_INT (ctype_int, processDec ()); } 
351 {Digit}+{U}            { setTokLengthT (mstring_length (yytext)); 
352                          RETURN_INT (ctype_uint, processDec ()); } 
353 {Digit}+{L}            { setTokLengthT (mstring_length (yytext)); 
354                          RETURN_INT (ctype_lint, processDec ()); } 
355 {Digit}+{L}{L}         { setTokLengthT (mstring_length (yytext)); 
356                          RETURN_INT (ctype_llint, processDec ()); } 
357 {Digit}+{ULSuffix}     { setTokLengthT (mstring_length (yytext)); 
358                          RETURN_INT (ctype_ulint, processDec ()); } 
359 {Digit}+{U}{L}{L}      { setTokLengthT (mstring_length (yytext)); 
360                          RETURN_INT (ctype_ullint, processDec ()); } 
361 {Digit}+{L}{L}{U}      { setTokLengthT (mstring_length (yytext)); 
362                          RETURN_INT (ctype_ullint, processDec ()); } 
363 '(\\.|[^\\'])+'        { setTokLengthT (mstring_length (yytext)); 
364                          RETURN_CHAR (processChar ()); }
365 L'(\\.|[^\\'])+'       { setTokLengthT (mstring_length (yytext)); 
366                          RETURN_CHAR (processChar ()); }
367 {Digit}+{E}[fF]        { setTokLengthT (mstring_length (yytext)); 
368                          RETURN_FLOAT (ctype_float, processFloat ()); }
369 {Digit}+{E}[lL]        { setTokLengthT (mstring_length (yytext)); 
370                          RETURN_FLOAT (ctype_ldouble, processFloat ()); }
371 {Digit}+{E}            { setTokLengthT (mstring_length (yytext)); 
372                          RETURN_FLOAT (ctype_double, processFloat ()); }
373
374 {Digit}*"."{Digit}+({E})?[fF] { setTokLengthT (mstring_length (yytext)); 
375                                 RETURN_FLOAT (ctype_float, processFloat ()); }
376 {Digit}*"."{Digit}+({E})?[lL] { setTokLengthT (mstring_length (yytext)); 
377                                 RETURN_FLOAT (ctype_ldouble, processFloat ()); }
378 {Digit}*"."{Digit}+({E})?     { setTokLengthT (mstring_length (yytext)); 
379                                 RETURN_FLOAT (ctype_double, processFloat ()); }
380
381 {Digit}+"."{Digit}*({E})?[fF]   { setTokLengthT (mstring_length (yytext)); 
382                                   RETURN_FLOAT (ctype_float, processFloat ()); }
383 {Digit}+"."{Digit}*({E})?[lL]   { setTokLengthT (mstring_length (yytext)); 
384                                   RETURN_FLOAT (ctype_ldouble, processFloat ()); }
385 {Digit}+"."{Digit}*({E})?       { setTokLengthT (mstring_length (yytext)); 
386                                   RETURN_FLOAT (ctype_double, processFloat ()); }
387
388 ">>="           { setTokLength (3); RETURN_TOK (RIGHT_ASSIGN); }
389 "<<="           { setTokLength (3); RETURN_TOK (LEFT_ASSIGN); }
390 "+="            { setTokLength (2); RETURN_TOK (ADD_ASSIGN); }
391 "-="            { setTokLength (2); RETURN_TOK (SUB_ASSIGN); }
392 "*="            { setTokLength (2); RETURN_TOK (MUL_ASSIGN); }
393 "/="            { setTokLength (2); RETURN_TOK (DIV_ASSIGN); }
394 "%="            { setTokLength (2); RETURN_TOK (MOD_ASSIGN); }
395 "&="            { setTokLength (2); RETURN_TOK (AND_ASSIGN); }
396 "^="            { setTokLength (2); RETURN_TOK (XOR_ASSIGN); }
397 "|="            { setTokLength (2); RETURN_TOK (OR_ASSIGN); }
398 ">>"            { setTokLength (2); RETURN_TOK (RIGHT_OP); }
399 "<<"            { setTokLength (2); RETURN_TOK (LEFT_OP); }
400 "++"            { setTokLength (2); RETURN_TOK (INC_OP); }
401 "--"            { setTokLength (2); RETURN_TOK (DEC_OP); }
402 "->"            { setTokLength (2); RETURN_TOK (ARROW_OP); }
403 "&&"            { setTokLength (2); RETURN_TOK (AND_OP); }
404 "||"            { setTokLength (2); RETURN_TOK (OR_OP); }
405 "<="            { setTokLength (2); RETURN_TOK (LE_OP); }
406 ">="            { setTokLength (2); RETURN_TOK (GE_OP); }
407 "=="            { setTokLength (2); RETURN_TOK (EQ_OP); }
408 "!="            { setTokLength (2); RETURN_TOK (NE_OP); }
409 ";"             { setTokLength (1); RETURN_TOK (TSEMI); }
410 "{"             { setTokLength (1); RETURN_TOK (TLBRACE); }
411 "}"             { setTokLength (1); RETURN_TOK (TRBRACE); }
412 ","             { setTokLength (1); RETURN_TOK (TCOMMA); }
413 ":"             { setTokLength (1); RETURN_TOK (TCOLON); }
414 "="             { setTokLength (1); RETURN_TOK (TASSIGN); }
415 "("             { setTokLength (1); RETURN_TOK (TLPAREN); }
416 ")"             { setTokLength (1); RETURN_TOK (TRPAREN); }
417 "["             { setTokLength (1); RETURN_TOK (TLSQBR); }
418 "]"             { setTokLength (1); RETURN_TOK (TRSQBR); }
419 "."             { setTokLength (1); RETURN_TOK (TDOT); }
420 "&"             { setTokLength (1); RETURN_TOK (TAMPERSAND); }
421 "!"             { setTokLength (1); RETURN_TOK (TEXCL); }
422
423
424 "~"             { setTokLength (1); RETURN_TOK (TTILDE); }
425 "-"             { setTokLength (1); RETURN_TOK (TMINUS); }
426 "+"             { setTokLength (1); RETURN_TOK (TPLUS); }
427 "*"             { setTokLength (1); RETURN_TOK (TMULT); }
428 "/"             { setTokLength (1); RETURN_TOK (TDIV); }
429 "%"             { setTokLength (1); RETURN_TOK (TPERCENT); }
430 "<"             { setTokLength (1); RETURN_TOK (TLT); }
431 ">"             { setTokLength (1); RETURN_TOK (TGT); }
432 "^"             { setTokLength (1); RETURN_TOK (TCIRC); }
433 "|"             { setTokLength (1); RETURN_TOK (TBAR); }
434 "?"             { setTokLength (1); RETURN_TOK (TQUEST); }
435
436
437 "/\\"           { setTokLength (1); RETURN_TOK (TCAND); }
438
439
440 [ \t\v\f]       { incColumn (); }
441 \n              { context_incLineno ();
442                   if (continueLine)
443                     {
444                       continueLine = FALSE;
445                     }
446                  else 
447                    {
448                      if (context_inMacro ())
449                        {
450                          /* Don't use RETURN_TOK */
451                          yylval.tok = lltok_create (TENDMACRO, g_currentloc);
452                          lastWasString = FALSE;
453                          return (TENDMACRO);
454                        }  
455                    }
456                 }
457 "@@MR@@"        { setTokLength (6); 
458                   
459                   if (processMacro ()) {
460                     if (context_inIterDef ()) 
461                       { 
462                         RETURN_TOK (LLMACROITER); 
463                       }
464                     if (context_inIterEnd ())
465                       {
466                         RETURN_TOK (LLMACROEND); 
467                       }
468                     if (context_inMacro ())
469                       {
470                         RETURN_TOK (LLMACRO); 
471                       }
472                   }
473                 }
474 "@QLMR"         { if (context_inHeader () || context_inFunction ())
475                     { 
476                       handleMacro ();
477                     }
478                   else
479                     {
480                       int nspchar = ninput ();
481                       int nspaces;
482
483                       /* 
484                       ** This is a hack to get the column number correct.
485                       */
486
487                       llassert (nspchar >= '0' && nspchar <= '9');
488                       
489                       nspaces = nspchar - '0';
490
491                       setTokLength (5 + nspaces); 
492                       
493                       if (processMacro ()) 
494                         {
495                           if (context_inIterDef ()) 
496                             {
497                               RETURN_TOK (LLMACROITER); 
498                             }
499                           if (context_inIterEnd ())
500                             {
501                               RETURN_TOK (LLMACROEND); 
502                             }
503                           if (context_inMacro ())
504                             { 
505                               RETURN_TOK (LLMACRO); 
506                             }
507                         }
508                     }
509                 }
510 "@.CT"          { setTokLength (4); lldiagmsg (ctype_unparseTable ()); }
511 "@.FA"          { setTokLength (4); lldiagmsg (message ("Access types: %q", typeIdSet_unparse (context_fileAccessTypes ()))); }
512 "@.F"           { setTokLength (3); 
513                   lldiagmsg (message ("%q: *** marker ***", fileloc_unparse (g_currentloc)));
514                 }
515 "@.L"           { setTokLength (3); usymtab_printLocal (); }
516 "@.A"           { setTokLength (3); lldiagmsg (usymtab_unparseAliases ()); }
517 "@.C"           { setTokLength (3); lldiagmsg (context_unparse ()); }
518 "@.W"           { setTokLength (3); lldiagmsg (context_unparseClauses ()); }
519 "@.G"           { setTokLength (3); usymtab_printGuards (); }
520 "@.S"           { setTokLength (3); usymtab_printOut (); }
521 "@.X"           { setTokLength (3); usymtab_printAll (); }
522 "@.Z"           { setTokLength (3); usymtab_printComplete (); }
523 "@.T"           { setTokLength (3); usymtab_printTypes (); }
524 "@.K"           { setTokLength (3); lldiagmsg (usymtab_unparseStack ()); }
525 "@.M"           { setTokLength (3); 
526                   lldiagmsg (message ("Can modify: %q", 
527                                   sRefSet_unparse (context_modList ()))); 
528                 }
529 "%{"            { /* BEFORE_COMMENT_MARKER */
530                   int tok; 
531                   incColumn (); incColumn ();
532                   tok = handleLlSpecial (); 
533
534                   if (tok != BADTOK)
535                     {
536                       if (tok == CANNOTATION) {
537                         return (tok);
538                       } else {
539                         /* Beware - this bashes yylval! */
540                         RETURN_TOK (tok); 
541                       }
542                     }
543                 }
544 "%}"            { /* AFTER_COMMENT_MARKER */ 
545                   setTokLength (2);
546                   inSpecPart = FALSE;
547                   RETURN_TOK (QENDMACRO); }
548 "\\"            { incColumn (); continueLine = TRUE; }
549 .               { incColumn (); 
550                   if ((int) *yytext == 13 ) {
551                      ;
552                   } else {
553                     voptgenerror
554                       (FLG_SYNTAX, 
555                        message ("Invalid character (ascii: %d), skipping character",
556                                 (int)(*yytext)),
557                        g_currentloc);
558                   }
559                 }
560 %%
561
562 struct skeyword
563 {
564   /*@null@*/ /*@observer@*/ char *name;
565   int token;
566 } ;
567
568 /*
569 ** These tokens are followed by syntax that is parsed by the 
570 ** grammar proper.
571 */
572
573 struct skeyword s_parsetable[] = {
574   { "modifies", QMODIFIES } ,
575   { "globals", QGLOBALS } ,
576   { "alt", QALT } ,
577   { "warn", QWARN } ,
578   { "constant", QCONSTANT } ,
579   { "function", QFUNCTION } ,
580   { "iter", QITER } ,
581   { "defines", QDEFINES } ,
582   { "uses", QUSES } ,
583   { "allocates", QALLOCATES } ,
584   { "sets", QSETS } ,
585   { "releases", QRELEASES } ,
586   { "pre", QPRECLAUSE } ,
587   { "post", QPOSTCLAUSE } ,
588   { "setBufferSize", QSETBUFFERSIZE},
589   { "setStringLength", QSETSTRINGLENGTH},
590   { "testinRange", QTESTINRANGE},
591   { "requires", QPRECLAUSE } ,
592   { "ensures", QPOSTCLAUSE } ,
593   { NULL, BADTOK } 
594 } ;
595
596 /*
597 ** These tokens are either stand-alone tokens, or followed by 
598 ** token-specific text.
599 */
600
601 struct skeyword s_keytable[] = {
602   { "anytype", QANYTYPE } ,
603   { "integraltype", QINTEGRALTYPE } ,
604   { "unsignedintegraltype", QUNSIGNEDINTEGRALTYPE } ,
605   { "signedintegraltype", QSIGNEDINTEGRALTYPE } ,
606   { "out", QOUT } ,
607   { "in", QIN } ,
608   { "only", QONLY } , 
609   { "owned", QOWNED } ,
610   { "dependent", QDEPENDENT } ,
611   { "partial", QPARTIAL } ,
612   { "special", QSPECIAL } ,
613   { "truenull", QTRUENULL } ,
614   { "falsenull", QFALSENULL } ,
615   { "keep", QKEEP } ,
616   { "kept", QKEPT } ,
617   { "notnull", QNOTNULL } ,
618   { "abstract", QABSTRACT } ,
619   { "concrete", QCONCRETE } ,
620   { "mutable", QMUTABLE } ,
621   { "immutable", QIMMUTABLE } ,
622   { "unused", QUNUSED } ,
623   { "external", QEXTERNAL } ,
624   { "sef", QSEF } ,
625   { "unique", QUNIQUE } ,
626   { "returned", QRETURNED } ,
627   { "exposed", QEXPOSED } ,
628   { "refcounted", QREFCOUNTED } ,
629   { "refs", QREFS } ,
630   { "newref", QNEWREF } ,
631   { "tempref", QTEMPREF } ,
632   { "killref", QKILLREF } ,
633   { "null", QNULL } ,
634   { "relnull", QRELNULL } ,
635   { "nullterminated", QNULLTERMINATED }, 
636   { "setBufferSize", QSETBUFFERSIZE },
637   { "testInRange", QTESTINRANGE},
638   { "MaxSet", QMAXSET},
639   { "MaxRead", QMAXREAD},
640   { "reldef", QRELDEF } ,
641   { "observer", QOBSERVER } ,
642   { "exits", QEXITS } ,
643   { "mayexit", QMAYEXIT } ,
644   { "trueexit", QTRUEEXIT } ,
645   { "falseexit", QFALSEEXIT } ,
646   { "neverexit", QNEVEREXIT } ,
647   { "temp", QTEMP } ,
648   { "shared", QSHARED } ,
649   { "ref", QREF } ,
650   { "unchecked", QUNCHECKED } ,
651   { "checked", QCHECKED } ,
652   { "checkmod", QCHECKMOD } ,
653   { "checkedstrict", QCHECKEDSTRICT } ,
654   { "innercontinue", QINNERCONTINUE } ,
655   { "innerbreak", QINNERBREAK } ,
656   { "loopbreak", QLOOPBREAK } ,
657   { "switchbreak", QSWITCHBREAK } ,
658   { "safebreak", QSAFEBREAK } , 
659   { "fallthrough", QFALLTHROUGH } ,
660   { "l_fallthrou", QLINTFALLTHROUGH } , 
661   { "l_fallth", QLINTFALLTHRU } ,
662   { "notreached", QNOTREACHED } ,
663   { "l_notreach", QLINTNOTREACHED } ,
664   { "printflike", QPRINTFLIKE } ,
665   { "l_printfli", QLINTPRINTFLIKE } ,
666   { "scanflike", QSCANFLIKE } ,
667   { "messagelike", QMESSAGELIKE } ,
668   { "l_argsus", QARGSUSED } ,
669   { NULL, BADTOK } 
670 } ;
671
672 /*
673 ** would be better if these weren't hard coded...
674 */
675
676 static bool isArtificial (cstring s)
677 {
678   return (cstring_equalLit (s, "modifies") 
679           || cstring_equalLit (s, "globals") 
680           || cstring_equalLit (s, "warn")
681           || cstring_equalLit (s, "alt"));
682 }
683
684 void swallowMacro (void)
685 {
686   int i;
687   bool skipnext = FALSE;
688
689   while ((i = lminput ()) != EOF)
690     {
691       char c = (char) i;
692       
693       
694       if (c == '\\')
695         {
696           skipnext = TRUE;
697         }
698       else if (c == '\n')
699         {
700           if (skipnext)
701             {
702               skipnext = FALSE;
703             }
704           else
705             {
706               reader_checkUngetc (i, yyin);
707               return;
708             }
709         }
710     }
711
712   if (i != EOF)
713     {
714       reader_checkUngetc (i, yyin);
715     }
716 }
717
718 static int commentMarkerToken (cstring s)
719 {
720   int i = 0;
721   
722   while (s_parsetable[i].name != NULL) 
723     {
724       DPRINTF (("Try :%s:%s:", s, s_parsetable[i].name));
725
726       if (cstring_equalLit (s, s_parsetable[i].name))
727         {
728           return s_parsetable[i].token;
729         }
730
731       i++;
732     }
733
734   return BADTOK;
735 }
736
737 static int tokenMacroCode (cstring s)
738 {
739   int i = 0;
740   
741   while (s_keytable[i].name != NULL) 
742     {
743       if (cstring_equalLit (s, s_keytable[i].name)) 
744         {
745           if (s_keytable[i].token == QLINTFALLTHROUGH) 
746             {
747               voptgenerror
748                 (FLG_WARNLINTCOMMENTS,
749                  cstring_makeLiteral
750                  ("Traditional lint comment /*FALLTHROUGH*/ used.  "
751                   "This is interpreted by "
752                   "LCLint in the same way as most Unix lints, but it is "
753                   "preferable to replace it with the /*@fallthrough@*/ "
754                   "semantic comment"),
755                  g_currentloc);
756               return QFALLTHROUGH;            
757             }
758           else if (s_keytable[i].token == QLINTFALLTHRU)
759             {
760               voptgenerror 
761                 (FLG_WARNLINTCOMMENTS,
762                  cstring_makeLiteral
763                  ("Traditional lint comment /*FALLTHRU*/ used.  "
764                   "This is interpreted by "
765                   "LCLint in the same way as most Unix lints, but it is "
766                   "preferable to replace it with the /*@fallthrough@*/ "
767                   "semantic comment"),
768                  g_currentloc);
769               return QFALLTHROUGH;
770             }
771           else if (s_keytable[i].token == QLINTNOTREACHED)
772             {
773               voptgenerror 
774                 (FLG_WARNLINTCOMMENTS,
775                  cstring_makeLiteral
776                  ("Traditional lint comment /*NOTREACHED*/ used.  "
777                   "This is interpreted by "
778                   "LCLint in the same way as most Unix lints, but it is "
779                   "preferable to replace it with the /*@notreached@*/ "
780                   "semantic comment."),
781                  g_currentloc);
782               
783               return QNOTREACHED;
784             }
785           else if (s_keytable[i].token == QPRINTFLIKE)
786             {
787               setSpecialFunction (qual_createPrintfLike ());
788               return SKIPTOK;
789             }
790           else if (s_keytable[i].token == QLINTPRINTFLIKE)
791             {         
792               voptgenerror 
793                 (FLG_WARNLINTCOMMENTS,
794                  cstring_makeLiteral
795                  ("Traditional lint comment /*PRINTFLIKE*/ used.  "
796                   "This is interpreted by "
797                   "LCLint in the same way as most Unix lints, but it is "
798                   "preferable to replace it with either /*@printflike@*/, "
799                   "/*@scanflike@*/ or /*@messagelike@*/."),
800                  g_currentloc);
801               
802               setSpecialFunction (qual_createPrintfLike ());
803               return SKIPTOK;
804             }
805           else if (s_keytable[i].token == QSCANFLIKE)
806             {
807               setSpecialFunction (qual_createScanfLike ());
808               return SKIPTOK;
809             }
810           else if (s_keytable[i].token == QMESSAGELIKE)
811             {
812               setSpecialFunction (qual_createMessageLike ());
813               return SKIPTOK;
814             }
815           else if (s_keytable[i].token == QARGSUSED)
816             {
817               voptgenerror
818                 (FLG_WARNLINTCOMMENTS,
819                  cstring_makeLiteral
820                  ("Traditional lint comment /*ARGSUSED*/ used.  "
821                   "This is interpreted by "
822                   "LCLint in the same way as most Unix lints, but it is "
823                   "preferable to use /*@unused@*/ annotations on "
824                   "the unused parameters."),
825                  g_currentloc);
826               
827               setArgsUsed ();
828               return SKIPTOK;
829             }
830           
831           return s_keytable[i].token;
832         }
833       
834       i++;
835     }
836   
837   return BADTOK;
838 }
839
840 static int lminput ()
841 {
842   if (savechar == '\0')
843     {
844       incColumn ();
845       return (input ());
846     }
847   else
848     {
849       int save = (int) savechar;
850       savechar = '\0';
851       return save;
852     }
853 }
854
855 static void lmsavechar (char c)
856 {
857   if (savechar == '\0') savechar = c;
858   else
859     {
860       llbuglit ("lmsavechar: override");
861     }
862 }
863
864 static int returnFloat (ctype ct, double f)
865 {
866   yylval.expr = exprNode_floatLiteral (f, ct, cstring_fromChars (yytext), 
867                                        fileloc_decColumn (g_currentloc, tokLength));
868   tokLength = 0; 
869   return (CCONSTANT);
870 }
871
872 static int returnInt (ctype ct, long i)
873 {
874   ctype c = ct;
875
876   if (ctype_equal (ct, ctype_int))
877     {
878       if (i == 0)
879         {
880           c = context_typeofZero ();
881         }
882       else if (i == 1)
883         {
884           c = context_typeofOne ();
885         }
886     }
887   
888   yylval.expr = exprNode_numLiteral (c, cstring_fromChars (yytext), 
889                                      fileloc_decColumn (g_currentloc, tokLength), i);   
890   tokLength = 0; 
891   return (CCONSTANT);
892 }
893
894 static int returnChar (char c)
895 {
896   yylval.expr = exprNode_charLiteral (c, cstring_fromChars (yytext), 
897                                       fileloc_decColumn (g_currentloc, tokLength));
898   tokLength = 0; 
899   return (CCONSTANT);
900 }
901
902 static int ninput ()  
903 {
904   int c = lminput ();
905
906   if (c != EOF && ((char)c == '\n'))
907     {
908       context_incLineno ();
909     }
910
911   return c;
912 }
913
914 static char macro_nextChar ()
915 {
916   static bool in_quote = FALSE, in_escape = FALSE, in_char = FALSE;
917   int ic;
918   char c;
919
920   ic = lminput ();
921   c = char_fromInt (ic);
922   
923   if (!in_quote && !in_char && (c == '\\' || c == BEFORE_COMMENT_MARKER[0]))
924     {
925       if (c == '\\')
926         {
927           while ((c = char_fromInt (lminput ())) != '\0' && c != '\n')
928             {
929               ; /* skip to newline */
930             }
931           
932           context_incLineno ();
933           
934           if (c != '\0')
935             {
936               return macro_nextChar ();
937             }
938           else 
939             {
940               return c;
941             }
942         }
943       else /* if (c == '@') */
944         {
945           llassert (FALSE); /*@i23@*/
946           if (handleLlSpecial () != BADTOK)
947             {
948               llerrorlit (FLG_SYNTAX, "Macro cannot use special syntax");
949             }
950
951           return macro_nextChar ();
952         }
953     }
954   else if (!in_escape && c == '\"')
955     {
956       in_quote = !in_quote;
957     }
958   else if (!in_escape && c == '\'')
959     {
960       in_char = !in_char;
961     }
962   else if ((in_quote || in_char) && c == '\\')
963     {
964       in_escape = !in_escape;
965     }
966   else if ((in_quote || in_char) && in_escape)
967     {
968       in_escape = FALSE;
969     }
970   else if (!in_quote && c == '/')
971     {
972       char c2;
973       
974       if ((c2 = char_fromInt (lminput ())) == '*')
975         {
976           while (c2 != '\0')
977             {
978               while ((c2 = char_fromInt (lminput ())) != '\0'
979                      && c2 != '\n' && c2 != '*')
980                 {
981                   ;
982                 }
983               
984               if (c2 == '*')
985                 {
986                   while ((c2 = char_fromInt (lminput ())) != '\0' 
987                          && c2 == '*')
988                     {
989                       ;
990                     }
991
992                   if (c2 == '/')
993                     {
994                       goto outofcomment;
995                     }
996                 }
997               else 
998                 {
999                   llfatalerror (cstring_makeLiteral ("Macro: bad comment!"));
1000                 }
1001             }
1002         outofcomment:
1003           return macro_nextChar ();
1004         }
1005       else
1006         {
1007           /*** putchar does not work!  why?  puts to stdio...??! ***/
1008           lmsavechar (c2);
1009         }
1010     }
1011   return c;
1012 }
1013
1014 /*
1015 ** keeps semantic comments
1016 */
1017
1018 static char macro_nextCharC ()
1019 {
1020   static bool in_quote = FALSE, in_escape = FALSE, in_char = FALSE;
1021   char c;
1022
1023   c = char_fromInt (lminput ());
1024
1025   if (!in_quote && !in_char && c == '\\')
1026     {
1027       while ((c = char_fromInt (lminput ())) != '\0' && c != '\n')
1028         {
1029           ; /* skip to newline */
1030         }
1031       
1032       context_incLineno ();
1033       
1034       if (c != '\0')
1035         {
1036           return macro_nextCharC ();
1037         }
1038       else
1039         {
1040           return c;
1041         }
1042     }
1043   else if (!in_escape && c == '\"')
1044     {
1045       in_quote = !in_quote;
1046     }
1047   else if (!in_escape && c == '\'')
1048     {
1049       in_char = !in_char;
1050     }
1051   else if ((in_quote || in_char) && c == '\\')
1052     {
1053       in_escape = !in_escape;
1054     }
1055   else if ((in_quote || in_char) && in_escape)
1056     {
1057       in_escape = FALSE;
1058     }
1059   else if (!in_quote && c == '/')
1060     {
1061       char c2;
1062       
1063       if ((c2 = char_fromInt (lminput ())) == '*')
1064         {
1065           while (c2 != '\0')
1066             {
1067               while ((c2 = char_fromInt (lminput ())) != '\0' 
1068                      && c2 != '\n' && c2 != '*')
1069                 {
1070                   ;
1071                 }
1072               
1073               if (c2 == '*')
1074                 {
1075                   while ((c2 = char_fromInt (lminput ())) != '\0'
1076                          && c2 == '*')
1077                     {
1078                       ;
1079                     }
1080
1081                   if (c2 == '/') 
1082                     {
1083                       goto outofcomment;
1084                     }
1085                 }
1086               else 
1087                 {
1088                   llfatalerror (cstring_makeLiteral ("Macro: bad comment!"));
1089                 }
1090             }
1091         outofcomment:
1092           return macro_nextCharC ();
1093         }
1094       else
1095         {
1096           lmsavechar (c2);
1097         }
1098     }
1099   return c;
1100 }
1101
1102 /*
1103 ** skips whitespace (handles line continuations)
1104 ** returns first non-whitespace character
1105 */
1106
1107 static char skip_whitespace ()
1108 {
1109   char c;
1110
1111   while ((c = macro_nextChar ()) == ' ' || c == '\t')
1112     {
1113       ;
1114     }
1115
1116   return c;
1117 }
1118
1119 static void handleMacro ()
1120 {
1121   cstring mac = cstring_undefined;
1122   int macrocode;
1123   char c;
1124
1125   while (currentColumn () > 2)
1126     {
1127       mac = cstring_appendChar (mac, ' ');
1128       setTokLength (-1);
1129     }
1130
1131   c = macro_nextCharC ();
1132
1133   if (c >= '0' && c <= '9')
1134     {
1135       int i;
1136
1137       for (i = 0; i < ((c - '0') + 1); i++)
1138         {
1139           mac = cstring_appendChar (mac, ' ');
1140         }
1141     }
1142   else
1143     {
1144       BADBRANCH;
1145     }
1146
1147   while (((c = macro_nextCharC ()) != '\0') && (c != '\n'))
1148     {
1149       mac = cstring_appendChar (mac, c);
1150     }
1151
1152   
1153   macrocode = tokenMacroCode (mac);
1154
1155   if (macrocode == BADTOK && !isArtificial (mac))
1156     {
1157       context_addMacroCache (mac);
1158     }
1159   else
1160     {
1161       cstring_free (mac);
1162     }
1163
1164   if (c == '\n')
1165     {
1166       context_incLineno ();
1167     }
1168 }
1169
1170 static bool processMacro (void)
1171 {
1172   uentry e2;
1173   ctype ct;
1174   int noparams = 0;
1175   cstring fname = cstring_undefined;
1176   bool res = TRUE;
1177   bool isspecfcn = FALSE;
1178   bool isiter = FALSE;
1179   bool skipparam = FALSE;
1180   bool isenditer = FALSE;
1181   bool unknownm = FALSE;
1182   bool hasParams = FALSE;
1183   bool emptyMacro = FALSE;
1184   char c = skip_whitespace ();
1185   fileloc loc = fileloc_noColumn (g_currentloc);
1186
1187   /* are both of these necessary?  what do they mean? */
1188   uentryList specparams = uentryList_undefined;
1189   uentryList pn = uentryList_undefined;
1190
1191   context_resetMacroMissingParams ();
1192
1193   if (c == '\0' || c == '\n')
1194     {
1195       llcontbug (cstring_makeLiteral ("Bad macro"));
1196       fileloc_free (loc);
1197       return FALSE;
1198     }
1199   
1200   fname = cstring_appendChar (fname, c);  
1201
1202   while ((c = macro_nextChar ()) != '(' && c != '\0'
1203          && c != ' ' && c != '\t' && c != '\n')
1204     {
1205       fname = cstring_appendChar (fname, c);
1206     }
1207
1208   if (c == ' ' || c == '\t' || c == '\n')
1209     {
1210       char oldc = c;
1211
1212       if (c != '\n')
1213         {
1214           while (c == ' ' || c == '\t')
1215             {
1216               c = macro_nextChar ();
1217             }
1218           unput (c);
1219         }
1220
1221       if (c == '\n')
1222         {
1223           emptyMacro = TRUE;
1224           unput (c);
1225         }
1226
1227       c = oldc;
1228     }
1229
1230   hasParams = (c == '(');
1231
1232   
1233   if (usymtab_exists (fname))
1234     {
1235       e2 = usymtab_lookupExpose (fname);
1236       ct = uentry_getType (e2);
1237
1238       if (uentry_isCodeDefined (e2) 
1239           && fileloc_isUser (uentry_whereDefined (e2)))
1240         {
1241           if (optgenerror 
1242               (FLG_MACROREDEF,
1243                message ("Macro %s already defined", fname),
1244                loc))
1245             {
1246               uentry_showWhereDefined (e2);
1247               uentry_clearDefined (e2);
1248             }
1249
1250           if (uentry_isFunction (e2))
1251             {
1252               uentry_setType (e2, ctype_unknown);
1253               ct = ctype_unknown;
1254               unknownm = TRUE;
1255               context_enterUnknownMacro (e2); 
1256             }
1257           else
1258             {
1259               context_enterConstantMacro (e2);
1260             }
1261         }
1262       else
1263         {
1264           if (uentry_isForward (e2) && uentry_isFunction (e2))
1265             {
1266               unknownm = TRUE;
1267
1268               voptgenerror 
1269                 (FLG_MACROFCNDECL,
1270                  message
1271                  ("Parameterized macro has no prototype or specification: %s ", 
1272                   fname),
1273                  loc);
1274               
1275               ct = ctype_unknown;
1276               uentry_setType (e2, ctype_unknown);
1277               uentry_setFunctionDefined (e2, loc); 
1278               uentry_setUsed (e2, fileloc_undefined);
1279               context_enterUnknownMacro (e2); 
1280             }
1281           else
1282             {
1283               if (uentry_isIter (e2))
1284                 {
1285                   isiter = TRUE;
1286                   specparams = uentry_getParams (e2);
1287                   noparams = uentryList_size (specparams);
1288                   uentry_setDefined (e2, loc);
1289                   context_enterIterDef (e2); 
1290                 }
1291               else if (uentry_isEndIter (e2))
1292                 {
1293                   isenditer = TRUE;
1294                   uentry_setDefined (e2, loc);
1295                   context_enterIterEnd (e2); /* don't care about it now */
1296                   /* but should parse like an iter! */
1297                 }
1298               else if (uentry_isConstant (e2))
1299                 {
1300                   if (hasParams)
1301                     {
1302                       voptgenerror 
1303                         (FLG_INCONDEFS, 
1304                          message ("Constant %s implemented as parameterized macro",
1305                                   fname),
1306                          g_currentloc);
1307                       
1308                       uentry_showWhereSpecified (e2);
1309                       uentry_setType (e2, ctype_unknown);
1310                       uentry_makeConstantFunction (e2);
1311                       uentry_setDefined (e2, g_currentloc);
1312                       uentry_setFunctionDefined (e2, g_currentloc);
1313                       context_enterUnknownMacro (e2); 
1314                     }
1315                   else
1316                     {
1317                       if (!uentry_isSpecified (e2))
1318                         {
1319                           fileloc oloc = uentry_whereDeclared (e2);
1320
1321                           if (fileloc_isLib (oloc))
1322                             {
1323                               ;
1324                             }
1325                           else if (fileloc_isUndefined (oloc)
1326                                    || fileloc_isPreproc (oloc))
1327                             {
1328                               if (!emptyMacro)
1329                                 {
1330                                   voptgenerror
1331                                     (FLG_MACROCONSTDECL,
1332                                      message 
1333                                      ("Macro constant %q not declared",
1334                                       uentry_getName (e2)),
1335                                      loc);                       
1336                                 }
1337                             }
1338                           else if (!fileloc_withinLines (oloc, loc, 2))
1339                             { /* bogus!  will give errors if there is too much whitespace */
1340                               voptgenerror
1341                                 (FLG_SYNTAX,
1342                                  message 
1343                                  ("Macro constant name %s does not match name in "
1344                                   "previous constant declaration.  This constant "
1345                                   "is declared at %q", fname, 
1346                                   fileloc_unparse (oloc)),
1347                                  loc);
1348                             }
1349                         }
1350
1351                       context_enterConstantMacro (e2);        
1352                       cstring_free (fname);
1353                       fileloc_free (loc);
1354                       return res;
1355                     }
1356
1357                 }
1358               else if (ctype_isFunction (ct))
1359                 {
1360                   isspecfcn = TRUE;
1361                   specparams = ctype_argsFunction (ct);
1362                   noparams = uentryList_size (specparams);
1363                   
1364                   uentry_setFunctionDefined (e2, loc); 
1365                   context_enterMacro (e2);
1366                 }
1367               else if (uentry_isVar (e2))
1368                 {
1369                   if (hasParams)
1370                     {
1371                       voptgenerror
1372                         (FLG_INCONDEFS,
1373                          message ("Variable %s implemented as parameterized macro", 
1374                                   fname),
1375                          loc);
1376
1377                       uentry_showWhereSpecified (e2);
1378                       uentry_setType (e2, ctype_unknown);
1379                       uentry_makeVarFunction (e2);
1380                       uentry_setDefined (e2, g_currentloc);
1381                       uentry_setFunctionDefined (e2, g_currentloc);
1382                       context_enterUnknownMacro (e2); 
1383                     }
1384                   else
1385                     {
1386                       uentry ucons = uentry_makeConstant (fname,
1387                                                           ctype_unknown,
1388                                                           loc);
1389                       if (uentry_isExpandedMacro (e2))
1390                         {
1391                           ; /* okay */
1392                         }
1393                       else
1394                         {
1395                           if (optgenerror 
1396                               (FLG_INCONDEFS,
1397                                message ("Variable %s implemented by a macro",
1398                                         fname),
1399                                loc))
1400                             {
1401                               uentry_showWhereSpecified (e2);
1402                             }
1403                         }
1404
1405                       uentry_setDefined (e2, loc);
1406                       uentry_setUsed (ucons, loc);
1407
1408                       context_enterConstantMacro (ucons);
1409                       uentry_markOwned (ucons);
1410                       cstring_free (fname);
1411                       return res;
1412                     }
1413                 }
1414               else
1415                 {
1416                   if (uentry_isDatatype (e2))
1417                     {
1418                       vgenhinterror 
1419                         (FLG_SYNTAX,
1420                          message ("Type implemented as macro: %x", 
1421                                   uentry_getName (e2)),
1422                          message ("A type is implemented using a macro definition.  A "
1423                                   "typedef should be used instead."),
1424                          g_currentloc);
1425
1426                       swallowMacro ();
1427                       /* Must exit scope (not sure why a new scope was entered?) */
1428                       usymtab_quietExitScope (g_currentloc);
1429                       uentry_setDefined (e2, g_currentloc);
1430                       res = FALSE;
1431                     }
1432                   else
1433                     {
1434                       llcontbug 
1435                         (message ("Unexpanded macro not function or constant: %q", 
1436                                   uentry_unparse (e2)));
1437                       uentry_setType (e2, ctype_unknown);
1438                       
1439                       if (hasParams)
1440                         {
1441                           uentry_makeVarFunction (e2);
1442                           uentry_setDefined (e2, g_currentloc);
1443                           uentry_setFunctionDefined (e2, g_currentloc);
1444                           context_enterUnknownMacro (e2); 
1445                         }
1446                     }
1447                 }
1448             }
1449         }
1450     }
1451   else
1452     {
1453       uentry ce;
1454
1455       voptgenerror 
1456         (FLG_MACROMATCHNAME,
1457          message ("Unexpanded macro %s does not match name of a constant "
1458                   "or iter declaration.  The name used in the control "
1459                   "comment on the previous line should match.  "
1460                   "(Assuming macro defines a constant.)", 
1461                   fname),
1462          loc);
1463
1464
1465       ce = uentry_makeConstant (fname, ctype_unknown, fileloc_undefined);      
1466       uentry_setUsed (ce, loc); /* perhaps bogus? */
1467       e2 = usymtab_supEntryReturn (ce);
1468       
1469       context_enterConstantMacro (e2);        
1470       cstring_free (fname);
1471       fileloc_free (loc);
1472       return res;
1473     }
1474   
1475   /* in macros, ( must follow immediatetly after name */
1476   
1477   if (hasParams)
1478     {
1479       int paramno = 0;
1480       
1481       c = skip_whitespace ();
1482
1483       while (c != ')' && c != '\0')
1484         {
1485           uentry  param;
1486           bool    suppress = context_inSuppressRegion ();
1487           cstring paramname = cstring_undefined;
1488
1489           /*
1490           ** save the parameter location
1491           */
1492
1493           decColumn ();
1494           context_saveLocation ();
1495           incColumn ();
1496
1497           while (c != ' ' && c != '\t' && c != ',' && c != '\0' && c != ')')
1498             {
1499               paramname = cstring_appendChar (paramname, c);
1500               c = macro_nextChar ();
1501             }
1502           
1503           if (c == ' ' || c == '\t') c = skip_whitespace ();
1504
1505           if (c == ',')
1506             {
1507               c = macro_nextChar ();
1508               if (c == ' ' || c == '\t') c = skip_whitespace ();
1509             }
1510           
1511           if (c == '\0')
1512             {
1513               llfatalerror (cstring_makeLiteral
1514                             ("Bad macro syntax: uentryList"));
1515             }
1516           
1517           if ((isspecfcn || isiter) && (paramno < noparams)
1518               && !uentry_isElipsisMarker (uentryList_getN 
1519                                           (specparams, paramno)))
1520             {
1521               fileloc sloc = context_getSaveLocation ();
1522               uentry decl = uentryList_getN (specparams, paramno);
1523               sRef sr;
1524               
1525               param = uentry_nameCopy (paramname, decl);
1526
1527                               
1528               uentry_setParam (param);
1529               sr = sRef_makeParam (paramno, uentry_getType (param), stateInfo_makeLoc (sloc));
1530
1531               if (sRef_getNullState (sr) == NS_ABSNULL)
1532                 {
1533                   ctype pt = ctype_realType (uentry_getType (param));
1534
1535                   if (ctype_isUser (pt))
1536                     {
1537                       uentry te = usymtab_getTypeEntrySafe (ctype_typeId (pt));
1538                       
1539                       if (uentry_isValid (te))
1540                         {
1541                           sRef_setStateFromUentry (sr, te);
1542                         }
1543                     }
1544                   else
1545                     {
1546                       sRef_setNullState (sr, NS_UNKNOWN, sloc);
1547                     }
1548                 }
1549
1550               uentry_setSref (param, sr);
1551               uentry_setDeclaredForceOnly (param, sloc);
1552
1553               skipparam = isiter && uentry_isOut (uentryList_getN (specparams, paramno));
1554             }
1555           else
1556             {
1557               fileloc sloc = context_getSaveLocation ();
1558
1559               param = uentry_makeVariableSrefParam 
1560                 (paramname, ctype_unknown, fileloc_copy (sloc), 
1561                  sRef_makeParam (paramno, ctype_unknown, stateInfo_makeLoc (sloc)));
1562               cstring_free (paramname);
1563
1564               sRef_setPosNull  (uentry_getSref (param), sloc);
1565               uentry_setDeclaredForce (param, sloc);
1566
1567               skipparam = FALSE;
1568               fileloc_free (sloc);
1569             }
1570
1571           if (!skipparam)
1572             {
1573               llassert (!uentry_isElipsisMarker (param));
1574
1575               if (!suppress)
1576                 {
1577                   sRef_makeUnsafe (uentry_getSref (param));
1578                 }
1579               
1580               pn = uentryList_add (pn, uentry_copy (param));
1581               usymtab_supEntry (param);
1582             }
1583           else
1584             {
1585               /* don't add param */
1586               uentry_free (param);
1587             }
1588
1589           if (c == ',') 
1590             {
1591               (void) macro_nextChar ();
1592               c = skip_whitespace ();
1593             }
1594
1595           paramno++;
1596         }
1597       
1598       if (c == ')')
1599         {
1600           if (isspecfcn || isiter)
1601             {
1602               if (paramno != noparams && noparams >= 0)
1603                 {
1604                   advanceLine ();
1605
1606                   voptgenerror 
1607                     (FLG_INCONDEFS,
1608                      message ("Macro %s specified with %d args, defined with %d", 
1609                               fname, noparams, paramno),
1610                      g_currentloc);
1611
1612                   uentry_showWhereSpecified (e2);
1613                   uentry_resetParams (e2, pn);
1614                 }
1615             }
1616           else
1617             {
1618               uentry_resetParams (e2, pn);
1619             }
1620         }
1621     }
1622   else
1623     {
1624       /*
1625       ** the form should be:
1626       **
1627       ** # define newname oldname
1628       ** where oldname refers to a function matching the specification
1629       ** of newname.
1630       */
1631
1632       if (unknownm)
1633         {
1634           sRef_setGlobalScope ();
1635           usymtab_supGlobalEntry (uentry_makeVariableLoc (fname, ctype_unknown));
1636           sRef_clearGlobalScope ();
1637         }
1638       else
1639         {
1640           context_setMacroMissingParams ();
1641         }
1642     }
1643   
1644   
1645   /* context_setuentryList (pn); */
1646   usymtab_enterScope ();
1647
1648   fileloc_free (loc);
1649   cstring_free (fname);
1650
1651   return res;
1652 }
1653
1654 static bool handleSpecial (char *yyt)
1655 {
1656   char *l = mstring_create (MAX_NAME_LENGTH);
1657   static bool reportcpp = FALSE;
1658   int lineno = 0;
1659   char c;
1660   char *ol;
1661   cstring olc;
1662   
1663   strcpy (l, yyt + 1);
1664
1665   /* Need to safe original l for deallocating. */
1666   ol = l;
1667
1668   l += strlen (yyt) - 1;
1669   
1670   while ((c = char_fromInt (lminput ())) != '\n' && c != '\0')
1671     {
1672       *l++ = c;
1673     }
1674
1675   *l = '\0';
1676   olc = cstring_fromChars (ol);
1677   
1678   if (cstring_equalPrefix (olc, "pragma"))
1679     {
1680       char *pname = mstring_create (longUnsigned_fromInt (MAX_PRAGMA_LEN));
1681       char *opname = pname;
1682       char *ptr = ol + 6; /* pragma is six characters, plus space */
1683       int len = 0;
1684       
1685       
1686       /* skip whitespace */
1687       while (((c = *ptr) != '\0') && isspace (c))
1688         {
1689           ptr++;
1690         }
1691
1692       
1693       while (((c = *ptr) != '\0') && !isspace (c))
1694         {
1695           len++;
1696
1697           if (len > MAX_PRAGMA_LEN)
1698             {
1699               break;
1700             }
1701
1702           ptr++;
1703           *pname++ = c;
1704         }
1705
1706       *pname = '\0';
1707       
1708       if (len == PRAGMA_LEN_EXPAND 
1709           && mstring_equal (opname, PRAGMA_EXPAND))
1710         {
1711           cstring exname = cstring_undefined;
1712           uentry ue;
1713           
1714           ptr++; 
1715           while (((c = *ptr) != '\0') && !isspace (c))
1716             {
1717               exname = cstring_appendChar (exname, c);
1718               ptr++;
1719             }
1720              
1721           
1722           ue = usymtab_lookupExposeGlob (exname);
1723           
1724           if (uentry_isExpandedMacro (ue))
1725             {
1726               if (fileloc_isPreproc (uentry_whereDefined (ue)))
1727                 {
1728                   fileloc_setColumn (g_currentloc, 1);
1729                   uentry_setDefined (ue, g_currentloc);
1730                 }
1731             }
1732
1733           cstring_free (exname);
1734         }
1735     }
1736   else if (cstring_equalPrefix (olc, "ident"))
1737     {
1738       /* Some pre-processors will leave these in the code.  Ignore rest of line */
1739     }
1740   /*
1741   ** Yuk...Win32 filenames can have spaces in them...we need to read
1742   ** to the matching end quote.
1743   */
1744   else if ((sscanf (ol, "line %d \"", &lineno) == 1)
1745            || (sscanf (ol, " %d \"", &lineno) == 1))
1746     {
1747       char *tmp = ol;
1748       cstring fname;
1749       fileId fid;
1750
1751       /*@access cstring@*/
1752       while (*tmp != '\"' && *tmp != '\0')
1753         {
1754           tmp++;
1755         }
1756
1757       llassert (*tmp == '\"');
1758
1759       tmp++;
1760
1761       fname = tmp;
1762       
1763       while (*tmp != '\"' && *tmp != '\0')
1764         {
1765           tmp++;
1766         }
1767
1768       llassert (*tmp == '\"');
1769
1770       *tmp = '\0';
1771
1772 # if defined(OS2) || defined(MSDOS) || defined(WIN32)
1773
1774       /*
1775       ** DOS-like path delimiters get delivered in pairs, something like 
1776       ** \"..\\\\file.h\", so we have to make it normal again. We do NOT
1777       ** remove the pre dirs yet as we usually specify tmp paths relative
1778       ** to the current directory, so tmp files would not get found in
1779       ** the hash table.  If this method fails we try it again later. 
1780       */
1781
1782       {
1783         char *stmp = fname;
1784         
1785         /*
1786         ** Skip past the drive marker.
1787         */
1788         
1789         if (strchr (stmp, ':') != NULL)
1790           {
1791             stmp = strchr (stmp, ':') + 1;
1792           }
1793         
1794         while ((stmp = strchr (stmp, CONNECTCHAR)) != NULL )
1795           {
1796             if (*(stmp+1) == CONNECTCHAR)
1797               {
1798                 memmove (stmp, stmp+1, strlen (stmp));
1799               }
1800             
1801             stmp++;
1802           }
1803         
1804         fid = fileTable_lookupBase (context_fileTable (), fname);
1805         if (!(fileId_isValid (fid)))
1806           {
1807             fname = removePreDirs (fname);
1808             fid = fileTable_lookupBase (context_fileTable (), fname);
1809           }
1810       }
1811 # else  /* !defined(OS2) && !defined(MSDOS) */
1812       fname = removePreDirs (fname);
1813       fid = fileTable_lookupBase (context_fileTable (), fname);      
1814 # endif /* !defined(OS2) && !defined(MSDOS) */
1815       
1816       if (!(fileId_isValid (fid)))
1817         {
1818           if (context_inXHFile ())
1819             {
1820               fid = fileTable_addXHFile (context_fileTable (), fname);
1821             }
1822           else if (isHeaderFile (fname))
1823             {
1824               fid = fileTable_addHeaderFile (context_fileTable (), fname);
1825             }
1826           else
1827             {
1828               fid = fileTable_addFile (context_fileTable (), fname);
1829             }
1830         }
1831       
1832       setFileLine (fid, lineno);
1833       /*@noaccess cstring@*/
1834     }
1835   else if ((sscanf (ol, "line %d", &lineno) == 1) 
1836            || (sscanf (ol, " %d", &lineno) == 1))
1837     {
1838       setLine (lineno); /* next line is <cr> */
1839     }
1840   else
1841     {
1842       if (mstring_equal (ol, "")) {
1843         DPRINTF (("Empty pp command!"));
1844         /*
1845         ** evs 2000-05-16: This is a horrible kludge, to get around a bug (well, difficulty) in the pre-processor.
1846         ** We handle a plain # in the input file, by echoing it, and ignoring it in the post-pp-file.
1847         */
1848         mstring_free (ol);
1849         return FALSE;
1850       } else {
1851         if (!reportcpp)
1852           {
1853             
1854           } else {
1855             llbug (message ("File contains preprocessor command: #%s", 
1856                             cstring_fromChars (ol)));
1857             reportcpp = TRUE;
1858           }
1859       }
1860       
1861       sfree (ol);
1862       return TRUE;
1863     }
1864
1865   sfree (ol);
1866   return FALSE;
1867 }
1868   
1869 static int handleLlSpecial ()
1870
1871   int ic; 
1872   char c;
1873   char *s = mstring_createEmpty ();
1874   char *os; 
1875   int tok;
1876   int charsread = 0;
1877   fileloc loc;
1878
1879   loc = fileloc_copy (g_currentloc);
1880   DPRINTF (("Handle special: %s", fileloc_unparse (loc)));
1881
1882   while (((ic = ninput ()) != 0) && isalpha (ic))
1883     {
1884       c = (char) ic;
1885       s = mstring_append (s, c);
1886       charsread++;
1887     }
1888
1889   DPRINTF (("Read: %s / %s", s, fileloc_unparse (g_currentloc)));
1890   os = s;
1891
1892   if (charsread == 0 && ic == (int) AFTER_COMMENT_MARKER[0])
1893     {
1894       ic = ninput ();
1895
1896       llassert (ic == AFTER_COMMENT_MARKER[1]);
1897             
1898       if (*s == '\0')
1899         {
1900           sfree (os);
1901           fileloc_free (loc);
1902           return QNOMODS; /* special token no modifications token */
1903         }
1904     }
1905   
1906   DPRINTF (("Coment marker: %s", os));
1907   tok = commentMarkerToken (cstring_fromChars (os));
1908
1909   if (tok != BADTOK)
1910     {
1911       tokLength = charsread;
1912       sfree (os);
1913       inSpecPart = TRUE;
1914       fileloc_free (loc);
1915       return tok;
1916     }
1917
1918   DPRINTF (("Not a comment marker..."));
1919   /* Add rest of the comment */
1920   
1921   if (ic != 0 && ic != EOF)
1922     {
1923       c = (char) ic;
1924       
1925       s = mstring_append (s, c);
1926       charsread++;
1927
1928       while (((ic = ninput ()) != 0) && (ic != EOF)
1929              && (ic != AFTER_COMMENT_MARKER[0]))
1930         {
1931           c = (char) ic;
1932           s = mstring_append (s, c);
1933           charsread++;
1934         }
1935     }
1936
1937   DPRINTF (("Read: %s / %s", s, fileloc_unparse (g_currentloc)));
1938
1939   if (ic == AFTER_COMMENT_MARKER[0]) 
1940     {
1941       int nc = ninput ();
1942       llassert ((char) nc ==  AFTER_COMMENT_MARKER[1]);
1943       charsread++;
1944     }
1945
1946   os = s;
1947
1948   while (*s == ' ' || *s == '\t' || *s == '\n') 
1949     {
1950       s++;
1951     }
1952
1953   if (*s == '-' || *s == '+' || *s == '=') /* setting flags */
1954     {
1955       c = *s;
1956
1957       while (c == '-' || c == '+' || c == '=')
1958         {
1959           ynm set = ynm_fromCodeChar (c);
1960           cstring thisflag;
1961
1962           s++;
1963           
1964           thisflag = cstring_fromChars (s);
1965           
1966           while ((c = *s) != '\0' && (c != '-') && (c != '=')
1967                  && (c != '+') && (c != ' ') && (c != '\t') && (c != '\n'))
1968             {
1969               s++;
1970             }
1971
1972           *s = '\0';
1973
1974           if (!context_getFlag (FLG_NOCOMMENTS))
1975             {
1976               cstring flagname = thisflag;
1977               flagcode fflag = identifyFlag (flagname);
1978                 
1979               if (flagcode_isSkip (fflag))
1980                 {
1981                   ;
1982                 }
1983               else if (flagcode_isInvalid (fflag))
1984                 {
1985                   if (isMode (flagname))
1986                     {
1987                       if (ynm_isMaybe (set))
1988                         {
1989                           llerror
1990                             (FLG_BADFLAG, 
1991                              message 
1992                              ("Semantic comment attempts to restore flag %s.  "
1993                               "A mode flag cannot be restored.",
1994                               flagname));
1995                         }
1996                       else
1997                         {
1998                           context_setMode (flagname);
1999                         }
2000                     }
2001                   else
2002                     {
2003                       voptgenerror
2004                         (FLG_UNRECOGFLAGCOMMENTS,
2005                          message ("Unrecognized option in semantic comment: %s", 
2006                                   flagname),
2007                          g_currentloc);
2008                     }
2009                 }
2010               else if (flagcode_isGlobalFlag (fflag))
2011                 {
2012                   voptgenerror
2013                     (FLG_BADFLAG, 
2014                      message 
2015                      ("Semantic comment attempts to set global flag %s.  "
2016                       "A global flag cannot be set locally.",
2017                       flagname),
2018                      g_currentloc);
2019                 }
2020               else
2021                 {
2022                   context_fileSetFlag (fflag, set);
2023                   
2024                   if (flagcode_hasArgument (fflag))
2025                     {
2026                       if (ynm_isMaybe (set))
2027                         {
2028                           voptgenerror
2029                             (FLG_BADFLAG, 
2030                              message 
2031                              ("Semantic comment attempts to restore flag %s.  "
2032                               "A flag for setting a value cannot be restored.",
2033                               flagname),
2034                              g_currentloc);
2035                         }
2036                       else
2037                         { /* cut-and-pastied from llmain...blecch */
2038                           cstring extra = cstring_undefined;
2039                           char *rest;
2040                           char *orest;
2041                           char rchar;
2042                           
2043                           *s = c;
2044                           rest = mstring_copy (s);
2045                           orest = rest;
2046                           *s = '\0';
2047                           
2048                           while ((rchar = *rest) != '\0'
2049                                  && (isspace (rchar)))
2050                             {
2051                               rest++;
2052                               s++;
2053                             }
2054                           
2055                           while ((rchar = *rest) != '\0'
2056                                  && !isspace (rchar))
2057                             {
2058                               extra = cstring_appendChar (extra, rchar);
2059                               rest++; 
2060                               s++;
2061                             }
2062                           
2063                           sfree (orest);
2064                           
2065                           if (cstring_isUndefined (extra))
2066                             {
2067                               llerror 
2068                                 (FLG_BADFLAG,
2069                                  message
2070                                  ("Flag %s (in semantic comment) must be followed by an argument",
2071                                   flagcode_unparse (fflag)));
2072                             }
2073                           else
2074                             {
2075                               s--;
2076                               
2077                               if (flagcode_hasValue (fflag))
2078                                 {
2079                                   setValueFlag (fflag, extra);
2080                                 }
2081                               else if (flagcode_hasString (fflag))
2082                                 {
2083                                   setStringFlag (fflag, extra);
2084                                 }
2085                               else
2086                                 {
2087                                   BADEXIT;
2088                                 }
2089                             }
2090                         }
2091                     }
2092                 }
2093             }
2094           else
2095             {
2096               ;
2097             }
2098
2099           *s = c;
2100           while ((c == ' ') || (c == '\t') || (c == '\n'))
2101             {
2102               c = *(++s);
2103             }
2104         } 
2105
2106       if (context_inHeader () && !isArtificial (cstring_fromChars (os)))
2107         {
2108           DPRINTF (("Here adding comment: %s", os));
2109           context_addComment (cstring_fromCharsNew (os));
2110         }
2111       else
2112         {
2113           ;
2114         }
2115     }
2116   else
2117     {
2118       char *t = s;
2119       int macrocode;
2120       char tchar = '\0';
2121       annotationInfo ainfo;
2122
2123       while (*s != '\0' && *s != ' ' && *s != '\t' && *s != '\n') 
2124         {
2125           s++;
2126         }
2127
2128       if (*s != '\0') 
2129         {
2130           tchar = *s;
2131           *s = '\0';
2132           s++;
2133         }
2134       
2135       t = cstring_toCharsSafe (cstring_downcase (cstring_fromChars (t)));
2136       macrocode = tokenMacroCode (cstring_fromChars (t));
2137
2138       if (macrocode != BADTOK)
2139         {
2140           tokLength = mstring_length (t);
2141           
2142           sfree (t);
2143           sfree (os);
2144           fileloc_free (loc);
2145
2146           if (macrocode == SKIPTOK)
2147             {
2148               return BADTOK;
2149             }
2150
2151           return macrocode;
2152         }
2153       
2154       ainfo = context_lookupAnnotation (cstring_fromChars (os));
2155       
2156       if (annotationInfo_isDefined (ainfo)) {
2157         DPRINTF (("Found annotation: %s", annotationInfo_unparse (ainfo)));
2158         /*@i324@*/ yylval.annotation = ainfo;
2159         tokLength = 0;
2160         sfree (os);
2161         sfree (t);
2162         fileloc_free (loc);
2163         return CANNOTATION;
2164       } 
2165
2166       if (context_inHeader ())
2167         {
2168           if (tchar != '\0')
2169             {
2170               *(s-1) = tchar;
2171             }
2172           
2173           if ((context_inMacro () || context_inGlobalContext ())
2174               && macrocode != SKIPTOK
2175               && !isArtificial (cstring_fromChars (os))) 
2176             {
2177               DPRINTF (("Add comment: %s", os));
2178               context_addComment (cstring_fromCharsNew (os));
2179             }
2180           else
2181             {
2182               ; 
2183             }
2184           
2185           if (tchar != '\0')
2186             {
2187               *(s-1) = '\0';
2188             }
2189         }
2190
2191       if (mstring_equal (t, "ignore"))
2192         {
2193           if (!context_getFlag (FLG_NOCOMMENTS))
2194             {
2195               context_enterSuppressRegion ();
2196             }
2197         }
2198       else if ((*t == 'i' || *t == 't')
2199                && (*(t + 1) == '\0'))
2200         {
2201           if (!context_getFlag (FLG_NOCOMMENTS)
2202               && (*t == 'i' || context_getFlag (FLG_TMPCOMMENTS)))
2203             {
2204               context_enterSuppressLine (-1); /* infinite suppression */
2205             }
2206         }
2207       else if (((*t == 'i') || (*t == 't'))
2208                && ((*(t + 1) >= '0' && *(t + 1) <= '9')))
2209         {
2210           bool tmpcomment = (*t == 't');
2211           int val = -1; 
2212           char *tt = t; /* don't mangle t, since it is free'd */
2213           char lc = *(++tt);
2214
2215           if (lc >= '0' && lc <= '9')
2216             {
2217               val = (int)(lc - '0');
2218               
2219               lc = *(++tt);       
2220               while (lc >= '0' && lc <= '9')
2221                 {
2222                   val *= 10;
2223                   val += lc - '0';
2224                   lc = *(++tt);
2225                 }
2226             }
2227
2228           
2229           if (!context_getFlag (FLG_NOCOMMENTS)
2230               && (!tmpcomment || context_getFlag (FLG_TMPCOMMENTS)))
2231             {
2232               context_enterSuppressLine (val);
2233             }
2234         }
2235       else if (mstring_equal (t, "end"))
2236         {
2237           if (!context_getFlag (FLG_NOCOMMENTS))
2238             {
2239               context_exitSuppressRegion ();
2240             }
2241         }
2242       else if (mstring_equal (t, "notfunction"))
2243         {
2244          ; /* handled by pcpp */
2245         }
2246       else if (mstring_equal (t, "access"))
2247         {
2248           cstring tname;
2249           
2250           while (TRUE)
2251             {
2252               while ((c = *s) && (c == ' ' || c == '\t' || c == '\n'))
2253                 {
2254                   s++;
2255                 }
2256               
2257               if (c == '\0')
2258                 {
2259                    break;
2260                 }
2261
2262               tname = cstring_fromChars (s);
2263               
2264               while ((c = *s) != '\0' && c != ' ' 
2265                      && c != '\t' && c != '\n' && c != ',') 
2266                 {
2267                   s++;
2268                 }
2269
2270               *s = '\0';
2271
2272               DPRINTF (("Access %s", tname));
2273
2274               if (!context_getFlag (FLG_NOCOMMENTS) 
2275                   && !context_getFlag (FLG_NOACCESS))
2276                 {
2277                   if (usymtab_existsType (tname))
2278                     {
2279                       typeId uid = usymtab_getTypeId (tname);
2280                       uentry ue = usymtab_getTypeEntry (uid);
2281
2282                       if (uentry_isAbstractDatatype (ue))
2283                         {
2284                           context_addFileAccessType (uid);
2285                           DPRINTF (("Adding access to: %s / %d", tname, uid));
2286                         }
2287                       else
2288                         {
2289                           voptgenerror
2290                             (FLG_COMMENTERROR,
2291                              message
2292                              ("Non-abstract type %s used in access comment",
2293                               tname),
2294                              g_currentloc);
2295                         }
2296                     }
2297                   else
2298                     {
2299                       if (!(context_inSuppressRegion ()
2300                             || context_inSuppressZone (g_currentloc)))
2301                         {
2302                           voptgenerror
2303                             (FLG_COMMENTERROR,
2304                              message
2305                              ("Unrecognized type %s used in access comment",
2306                               tname),
2307                              g_currentloc);
2308                         }
2309                     }
2310                 }
2311               
2312               if (c != '\0') 
2313                 {
2314                   s++;
2315                 }
2316               
2317               if (c != ',' && c != ' ')
2318                 {
2319                   break;
2320                 }
2321             }
2322         }
2323       else if (mstring_equal (t, "noaccess"))
2324         {
2325           cstring tname;
2326           char lc;
2327           
2328           while (TRUE)
2329             {
2330               while ((lc = *s) && (lc == ' ' || lc == '\t' || lc == '\n')) 
2331                 {
2332                   s++;
2333                 }
2334               
2335               if (lc == '\0')
2336                 {
2337                  break;
2338                 }
2339
2340               tname = cstring_fromChars (s);
2341               
2342               while ((lc = *s) != '\0' && lc != ' ' && lc != '\t' 
2343                      && lc != '\n' && lc != ',') 
2344                 {
2345                   s++;
2346                 }
2347
2348               *s = '\0';
2349
2350               if (!context_getFlag (FLG_NOCOMMENTS) 
2351                   && !context_getFlag (FLG_NOACCESS))
2352                 {
2353                   if (usymtab_existsType (tname))
2354                     {
2355                       typeId tuid = usymtab_getTypeId (tname);
2356                       
2357                       if (context_couldHaveAccess (tuid))
2358                         {
2359                           DPRINTF (("Removing access: %s", tname));
2360                           context_removeFileAccessType (tuid);
2361                         }
2362                       else
2363                         {
2364                           if (!(context_inSuppressRegion () 
2365                                 || context_inSuppressZone (g_currentloc)))
2366                             {
2367                               uentry ue = usymtab_getTypeEntry (tuid);
2368                               
2369                               if (uentry_isAbstractDatatype (ue))
2370                                 {
2371                                   voptgenerror
2372                                     (FLG_COMMENTERROR,
2373                                      message
2374                                      ("Non-accessible abstract type %s used in noaccess comment",
2375                                       tname),
2376                                      g_currentloc);
2377                                 }
2378                               else
2379                                 {
2380                                   voptgenerror
2381                                     (FLG_COMMENTERROR,
2382                                      message
2383                                      ("Non-abstract type %s used in noaccess comment",
2384                                       tname),
2385                                      g_currentloc);
2386                                 }
2387                             }
2388                         }
2389                     }
2390                   else
2391                     {
2392                       if (!(context_inSuppressRegion () 
2393                             || context_inSuppressZone (g_currentloc)))
2394                         {
2395                           voptgenerror
2396                             (FLG_COMMENTERROR,
2397                              message
2398                              ("Unrecognized type %s used in noaccess comment",
2399                               tname),
2400                              g_currentloc);
2401                         }
2402                     }
2403                 }
2404               
2405               if (lc != '\0') 
2406                 {
2407                   s++;
2408                 }
2409               
2410               if (lc != ',' && lc != ' ')
2411                 {
2412                   break;
2413                 }
2414             }
2415         }
2416       else
2417         {
2418           voptgenerror (FLG_UNRECOGCOMMENTS, 
2419                         message ("Semantic comment unrecognized: %s", 
2420                                  cstring_fromChars (os)), loc);
2421         }
2422
2423       sfree (t);
2424     }
2425   
2426   sfree (os);
2427   fileloc_free (loc);
2428   return BADTOK;
2429 }
2430
2431 static /*@only@*/ cstring makeIdentifier (char *s)
2432 {
2433   char *c = mstring_create (size_toInt (strlen (s)) + 1);
2434   cstring id = cstring_fromChars (c);
2435
2436   while (isalnum (*s) || (*s == '_') || (*s == '$')) 
2437     {
2438       *c++ = *s++;
2439     }
2440
2441   *c = '\0';
2442   return (id);
2443 }
2444
2445 /*@observer@*/ /*@dependent@*/ uentry coerceId (cstring cn)
2446 {
2447   if (!(usymtab_exists (cn)))
2448     {
2449       fileloc loc = fileloc_createExternal ();
2450       
2451       /*
2452       ** We need to put this in a global scope, otherwise the sRef will be deallocated.
2453       */
2454       
2455       uentry ce = uentry_makeUnrecognized (cn, loc);
2456       
2457       if (!context_inIterEnd ())
2458         {
2459           voptgenerror 
2460             (FLG_SYSTEMUNRECOG, 
2461              message ("Unrecognized (possibly system) identifier: %q", 
2462                       uentry_getName (ce)), 
2463              g_currentloc);
2464         }
2465       
2466       return ce;
2467     }
2468   
2469   return (usymtab_lookup (cn));
2470 }
2471
2472 /*
2473 ** like, coerceId, but doesn't supercede for iters
2474 */
2475
2476 /*@observer@*/ uentry coerceIterId (cstring cn)
2477 {
2478   if (!(usymtab_exists (cn)))
2479     {
2480       return uentry_undefined;
2481     }
2482   
2483   return (usymtab_lookup (cn));
2484 }
2485
2486 /*@observer@*/ cstring LastIdentifier ()
2487 {
2488   return (lastidprocessed);
2489 }
2490
2491 static int processIdentifier (cstring id)
2492 {
2493   uentry le;
2494
2495   if (context_getFlag (FLG_GRAMMAR))
2496     {
2497       lldiagmsg (message ("Process identifier: %s", id));
2498     }
2499
2500   context_clearJustPopped ();
2501   lastidprocessed = id; 
2502
2503   if (context_inFunctionHeader ())
2504     {
2505       int tok = commentMarkerToken (id);
2506       DPRINTF (("in function decl..."));
2507
2508       if (tok != BADTOK)
2509         {
2510           return tok;
2511         }
2512       else 
2513         {
2514           tok = tokenMacroCode (id);
2515
2516           if (tok != BADTOK)
2517             {
2518               return tok;
2519             }
2520           else 
2521             {
2522               annotationInfo ainfo;
2523
2524               if (expectingMetaStateName) 
2525                 {
2526                   metaStateInfo msinfo = context_lookupMetaStateInfo (id);
2527
2528                   if (metaStateInfo_isDefined (msinfo))
2529                     {
2530                       yylval.msinfo = msinfo;
2531                       return METASTATE_NAME;
2532                     }
2533                   else
2534                     {
2535                       DPRINTF (("Not meta state name: %s", cstring_toCharsSafe (id)));
2536                     }
2537                 }
2538               
2539               ainfo = context_lookupAnnotation (id);
2540               
2541               if (annotationInfo_isDefined (ainfo)) 
2542                 {
2543                   DPRINTF (("Found annotation: %s", annotationInfo_unparse (ainfo)));
2544                   /*@i324@*/ yylval.annotation = ainfo;
2545                   return CANNOTATION;
2546                 }
2547               else
2548                 {
2549                   DPRINTF (("Not annotation: %s", id));
2550                 }
2551             }
2552         }
2553     }
2554
2555   /* Consider handling: Defined by C99 as static const char __func__[] */
2556
2557   if (context_getFlag (FLG_GNUEXTENSIONS))
2558     {
2559       int tok = BADTOK;
2560       
2561       if (cstring_equalLit (id, "__stdcall")
2562           || cstring_equalLit (id, "__cdecl")
2563           || cstring_equalLit (id, "__extension__"))
2564         {
2565           return BADTOK;
2566         }
2567       else if (cstring_equalLit (id, "__volatile__"))
2568         {
2569           tok = QVOLATILE;
2570         }
2571       else if (cstring_equalLit (id, "__signed"))
2572         {
2573           tok = QSIGNED;
2574         }
2575       else if (cstring_equalLit (id, "__unsigned"))
2576         {
2577           tok = QUNSIGNED;
2578         }
2579       else if (cstring_equalLit (id, "__const__"))
2580         {
2581           tok = QCONST;
2582         }
2583       else if (cstring_equalLit (id, "__alignof__")) 
2584         {
2585           tok = CALIGNOF; /* alignof is parsed like sizeof */
2586         }
2587       else if (cstring_equalLit (id, "__FUNCTION__")
2588                || cstring_equalLit (id, "__PRETTY_FUNCTION__")) 
2589         {
2590           /* These tokens hold the name of the current function as strings */
2591           yylval.expr = exprNode_stringLiteral (id, fileloc_copy (g_currentloc));
2592           tokLength = 0;
2593           lastWasString = TRUE;
2594           tok = CCONSTANT;
2595           return tok;
2596         }
2597       else if (cstring_equalLit (id, "__attribute__")
2598                || cstring_equalLit (id, "__asm__")
2599                || cstring_equalLit (id, "_asm")
2600                || cstring_equalLit (id, "__asm")
2601                || cstring_equalLit (id, "__declspec"))
2602         {
2603           int depth = 0;
2604           bool useparens = FALSE;
2605           bool usebraces = FALSE;
2606           bool inquote = FALSE;
2607           bool inescape = FALSE;
2608           int ic;
2609
2610           while ((ic = input ()) != EOF)
2611             {
2612                               
2613               if (inescape)
2614                 {
2615                   inescape = FALSE;
2616                 }
2617               else if (ic == '\\')
2618                 {
2619                   inescape = TRUE;
2620                 }
2621               else if (ic == '\"')
2622                 {
2623                   inquote = !inquote;
2624                 }
2625               else if (!inquote)
2626                 {
2627                   if (ic == '(')
2628                     {
2629                       if (!useparens)
2630                         {
2631                           if (!usebraces)
2632                             {
2633                               useparens = TRUE;
2634                             }
2635                         }
2636
2637                       if (useparens)
2638                         {
2639                           depth++;
2640                         }
2641                     }
2642                   else if (ic == '{')
2643                     {
2644                       if (!usebraces)
2645                         {
2646                           if (!useparens)
2647                             {
2648                               usebraces = TRUE;
2649                             }
2650                         }
2651
2652                       if (usebraces)
2653                         {
2654                           depth++;
2655                         }
2656                     }
2657                   else if (ic == ')' && useparens)
2658                     {
2659                       depth--;
2660                       if (depth == 0) break;
2661                     }
2662                   else if (ic == '}' && usebraces)
2663                     {
2664                       depth--;
2665                       if (depth == 0) break;
2666                     }
2667                   else if (ic == '}' 
2668                            && !usebraces && !useparens
2669                            && cstring_equalLit (id, "__asm"))
2670                     {
2671                       /*
2672                       ** We need this because some MS VC++ include files
2673                       ** have __asm mov ... }
2674                       ** Its a kludge, but otherwise would need to parse
2675                       ** the asm code!
2676                       */ 
2677                       return TRBRACE;
2678                     }
2679                 }
2680
2681               if (ic == '\n')
2682                 {
2683                   context_incLineno ();
2684
2685                   if (cstring_equalLit (id, "__asm")
2686                       && !useparens && !usebraces)
2687                     {
2688                       break;
2689                     }
2690                 }
2691             }
2692           
2693           llassert ((useparens && ic == ')')
2694                     || (usebraces && ic == '}')
2695                     || (!useparens && !usebraces));
2696
2697           return BADTOK;
2698         }
2699       else if (cstring_equalLit (id, "inline")
2700                || cstring_equalLit (id, "__inline")
2701                || cstring_equalLit (id, "_inline")
2702                || cstring_equalLit (id, "__inline__"))
2703         {
2704           tok = QINLINE;
2705         }
2706       
2707       if (tok != BADTOK)
2708         {
2709           RETURN_TOK (tok);
2710         }
2711     }
2712
2713   le = usymtab_lookupSafe (id);
2714
2715   /*@-dependenttrans@*/
2716   
2717   if (uentry_isIter (le))
2718     {
2719       /*@i32@*/ yylval.entry = le;
2720       return (ITER_NAME);
2721     }
2722   else if (uentry_isEndIter (le))
2723     {
2724       /*@i32@*/ yylval.entry = le;
2725       return (ITER_ENDNAME);
2726     }
2727   else if (uentry_isUndefined (le))
2728     {
2729       yylval.cname = id;
2730
2731       /* avoid parse errors for certain system built ins */
2732
2733       if (g_expectingTypeName && (cstring_firstChar (id) == '_')
2734           && (cstring_secondChar (id) == '_'))
2735         {
2736           return (TYPE_NAME_OR_ID);
2737         }
2738
2739       return (NEW_IDENTIFIER);
2740     }
2741   else if (!uentry_isDeclared (le) && !uentry_isCodeDefined (le))
2742     {
2743       if (uentry_isDatatype (le))
2744         {
2745           yylval.cname = id;
2746           return (NEW_IDENTIFIER);
2747         }
2748       else
2749         {
2750           /*@i32@*/ yylval.entry = le;            
2751           return (IDENTIFIER); 
2752         }
2753     }
2754   else if (uentry_isDatatype (le))
2755     {
2756       if (!g_expectingTypeName)
2757         {
2758           yylval.cname = id;
2759
2760           return (NEW_IDENTIFIER);
2761         }
2762       else
2763         {
2764           yylval.ctyp = uentry_getAbstractType (le);
2765           
2766           uentry_setUsed (le, g_currentloc);
2767           return (TYPE_NAME);
2768         }
2769     }
2770   else
2771     {
2772       /*@i32@*/ yylval.entry = le;            
2773       return (IDENTIFIER); 
2774     }
2775
2776   /*@=dependenttrans@*/
2777 }
2778
2779 static bool processHashIdentifier (/*@only@*/ cstring id)
2780 {
2781   if (context_inMacro () || context_inIterDef () ||
2782       context_inIterEnd ())
2783     {
2784       uentry le;
2785       
2786       context_clearJustPopped ();
2787
2788       lastidprocessed = id; 
2789       le = usymtab_lookupSafe (id);
2790
2791       if (uentry_isParam (le) || uentry_isRefParam (le))
2792         {
2793           return TRUE;
2794         }
2795       else
2796         {
2797           return FALSE;
2798         }
2799     }
2800   else
2801     {
2802       cstring_free (id);
2803       return FALSE;
2804     }
2805 }
2806
2807
2808 static /*@only@*/ exprNode processString ()
2809 {
2810   exprNode res;
2811   fileloc loc;
2812   char *nl = strchr (yytext, '\n');
2813   cstring ns = cstring_fromCharsNew (yytext);
2814
2815   if (nl == NULL)
2816     {
2817       loc = fileloc_copy (g_currentloc);
2818       addColumn (cstring_length (ns));
2819     }
2820   else
2821     {
2822       char *lastnl = nl;
2823
2824       loc = fileloc_copy (g_currentloc);
2825
2826       context_incLineno ();
2827       
2828       while ((nl = strchr ((nl + 1), '\n')) != NULL)
2829         {
2830           context_incLineno ();
2831           lastnl = nl;
2832         }
2833     }
2834
2835     
2836   res = exprNode_stringLiteral (ns, loc);
2837   return (res);
2838 }
2839
2840 static 
2841 char processChar ()
2842 {
2843   char fchar;
2844   char next;
2845
2846   llassert (*yytext != '\0');
2847   fchar = *(yytext + 1);
2848   if (fchar != '\\') return fchar;
2849   
2850   next = *(yytext + 2);
2851   
2852   switch (next)
2853     {
2854     case 'n': return '\n';
2855     case 't': return '\t';
2856     case '\"': return '\"';
2857     case '\'': return '\'';
2858     case '\\': return '\\';
2859     default: return '\0';
2860     }
2861 }
2862
2863 static
2864 double processFloat ()
2865 {
2866   double ret = atof (yytext);
2867
2868     return (ret);
2869 }
2870
2871 static
2872 long processHex ()
2873 {
2874   int index = 2;
2875   long val = 0;
2876
2877   llassert (yytext[0] == '0'
2878             && (yytext[1] == 'X' || yytext[1] == 'x'));
2879
2880   while (yytext[index] != '\0') {
2881     int tval;
2882     char c = yytext[index];
2883
2884     if (c >= '0' && c <= '9') {
2885       tval = (int) c - (int) '0';
2886     } else if (c >= 'A' && c <= 'F') {
2887       tval = (int) c - (int) 'A' + 10;
2888     } else if (c >= 'a' && c <= 'f') {
2889       tval = (int) c - (int) 'a' + 10;
2890     } else if (c == 'U' || c == 'L' || c == 'u' || c == 'l') {
2891       index++;
2892       while (yytext[index] != '\0') {
2893         if (c == 'U' || c == 'L' || c == 'u' || c == 'l') {
2894           ;
2895         } else {
2896           voptgenerror
2897             (FLG_SYNTAX, 
2898              message ("Invalid character (%c) following specifier in hex constant: %s",
2899                       c, cstring_fromChars (yytext)),
2900              g_currentloc);
2901         }
2902         index++;
2903       }
2904
2905       break;
2906     } else {
2907       voptgenerror
2908         (FLG_SYNTAX, 
2909          message ("Invalid character (%c) in hex constant: %s",
2910                   c, cstring_fromChars (yytext)),
2911          g_currentloc);
2912       break;
2913     }
2914
2915     val = (val * 16) + tval;
2916     index++;
2917   }
2918
2919   DPRINTF (("Hex constant: %s = %ld", yytext, val));
2920   return val;
2921 }
2922
2923 static
2924 long processOctal ()
2925 {
2926   int index = 1;
2927   long val = 0;
2928
2929   llassert (yytext[0] == '0' && yytext[1] != 'X' && yytext[1] != 'x');
2930     
2931   while (yytext[index] != '\0') {
2932     int tval;
2933     char c = yytext[index];
2934     
2935     if (c >= '0' && c <= '7') {
2936       tval = (int) c - (int) '0';
2937     } else {
2938       voptgenerror
2939         (FLG_SYNTAX, 
2940          message ("Invalid character (%c) in octal constant: %s",
2941                   c, cstring_fromChars (yytext)),
2942          g_currentloc);
2943       break;
2944     }
2945
2946     val = (val * 8) + tval;
2947     index++;
2948   }
2949
2950   DPRINTF (("Octal constant: %s = %ld", yytext, val));
2951   return val;
2952 }
2953
2954 static
2955 long processDec ()
2956 {
2957   return (atol (yytext));
2958 }
2959
2960 static int
2961 processSpec (int tok)
2962 {
2963   size_t length = strlen (yytext);
2964
2965   
2966   if (inSpecPart)
2967     {
2968       setTokLengthT (length);
2969       RETURN_TOK (tok);
2970     }
2971   else
2972     {
2973       
2974       context_saveLocation ();
2975       setTokLengthT (length);
2976       return (processIdentifier (makeIdentifier (yytext)));
2977     }
2978 }
2979
2980 void cscanner_expectingMetaStateName ()
2981 {
2982   llassert (!expectingMetaStateName);
2983   llassert (context_inFunctionHeader ());
2984   expectingMetaStateName = TRUE;
2985 }
2986
2987 void cscanner_clearExpectingMetaStateName ()
2988 {
2989   llassert (expectingMetaStateName);
2990   expectingMetaStateName = FALSE;
2991 }
This page took 0.278541 seconds and 5 git commands to generate.