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