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