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