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