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