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