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