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