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