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