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