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