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