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