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