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