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