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