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