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