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