Initial revision
[fw/sdcc] / src / SDCC.lex
1 /*-----------------------------------------------------------------------
2   SDCC.lex - lexical analyser for use with sdcc ( a freeware compiler for
3   8/16 bit microcontrollers)
4   Written by : Sandeep Dutta . sandeep.dutta@usa.net (1997)
5   
6   This program is free software; you can redistribute it and/or modify it
7   under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10    
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15    
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19     
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!  
23 -------------------------------------------------------------------------*/
24
25 D        [0-9]
26 L        [a-zA-Z_]
27 H        [a-fA-F0-9]
28 E        [Ee][+-]?{D}+
29 FS       (f|F|l|L)
30 IS       (u|U|l|L)*
31 %{
32
33 #include <stdio.h>
34 #include <string.h>
35 #include <ctype.h>
36 #include "SDCCglobl.h"
37 #include "SDCCsymt.h"
38 #include "SDCCval.h"
39 #include "SDCCast.h"
40 #include "SDCCy.h"
41 #include "SDCChasht.h"
42 #include "SDCCmem.h"
43     
44 char *stringLiteral();
45 char *currFname;
46
47 extern int lineno                       ;
48 extern char *filename ;
49 extern char *fullSrcFileName ;
50 int   yylineno = 1               ;
51 void count()                     ;
52 void comment();
53 int process_pragma(char *);
54 #undef yywrap
55
56 int yywrap YY_PROTO((void))
57 {
58    return(1);
59 }
60
61 char asmbuff[MAX_INLINEASM]                     ;
62 char *asmp ;
63 extern int check_type           (          );
64 extern int checkCurrFile        (char *);
65 extern int processPragma        (char *);
66 extern int printListing         (int   );
67 struct optimize save_optimize ;
68 struct options  save_options  ;
69
70  enum {
71      P_SAVE = 1,
72      P_RESTORE ,
73      P_NOINDUCTION,
74      P_NOINVARIANT,
75      P_INDUCTION ,
76      P_STACKAUTO ,
77      P_NOJTBOUND ,
78      P_NOOVERLAY ,
79      P_NOGCSE    ,
80      P_CALLEE_SAVES,
81      P_EXCLUDE   ,
82      P_LOOPREV
83  };
84
85 %}
86 %x asm
87 %%
88 "_asm"        {  count(); asmp = asmbuff ;BEGIN(asm) ;}
89 <asm>"_endasm" { count()                ; 
90                   *asmp = '\0'                          ; 
91                   strcpy(yylval.yyinline,asmbuff)               ; 
92                   BEGIN(INITIAL)        ;
93                   return (INLINEASM)                    ; }
94 <asm>.         { *asmp++ = yytext[0]    ; }
95 <asm>\n        { count(); *asmp++ = '\n' ;}
96 "/*"           { comment(); }
97 "at"           { count(); return(AT)  ; }
98 "auto"      { count(); return(AUTO); }
99 "bit"          { count(); return(BIT) ; }
100 "break"      { count(); return(BREAK); }
101 "case"       { count(); return(CASE); }
102 "char"         { count(); return(CHAR); }
103 "code"         { count(); return(CODE); }
104 "const"        { count(); return(CONST); }
105 "continue"     { count(); return(CONTINUE); }
106 "critical"     { count(); return(CRITICAL); } 
107 "data"         { count(); return(DATA);   }
108 "default"      { count(); return(DEFAULT); }
109 "do"           { count(); return(DO); }
110 "double"       { count(); werror(W_DOUBLE_UNSUPPORTED);return(FLOAT); }
111 "else"         { count(); return(ELSE); }
112 "enum"         { count(); return(ENUM); }
113 "extern"       { count(); return(EXTERN); }
114 "far"          { count(); return(XDATA);  }
115 "float"        { count(); return(FLOAT); }
116 "for"          { count(); return(FOR); }
117 "goto"         { count(); return(GOTO); }
118 "idata"        { count(); return(IDATA);}
119 "if"           { count(); return(IF); }
120 "int"          { count(); return(INT); }
121 "interrupt"    { count(); return(INTERRUPT);}
122 "long"         { count(); return(LONG); }
123 "near"             { count(); return(DATA);}
124 "pdata"        { count(); return(PDATA); }
125 "reentrant"    { count(); return(REENTRANT);}
126 "register"     { count(); return(REGISTER); }
127 "return"       { count(); return(RETURN); }
128 "sfr"          { count(); return(SFR)   ; }
129 "sbit"         { count(); return(SBIT)  ; }
130 "short"        { count(); return(SHORT); }
131 "signed"       { count(); return(SIGNED); }
132 "sizeof"       { count(); return(SIZEOF); }
133 "static"       { count(); return(STATIC); }
134 "struct"       { count(); return(STRUCT); }
135 "switch"       { count(); return(SWITCH); }
136 "typedef"      { count(); return(TYPEDEF); }
137 "union"        { count(); return(UNION); }
138 "unsigned"     { count(); return(UNSIGNED); }
139 "void"         { count(); return(VOID); }
140 "volatile"     { count(); return(VOLATILE); }
141 "using"        { count(); return(USING); }
142 "while"        { count(); return(WHILE); }
143 "xdata"        { count(); return(XDATA); }
144 "_data"            { count(); return(_NEAR); }
145 "_code"            { count(); return(_CODE); }
146 "_generic"         { count(); return(_GENERIC); }
147 "_near"            { count(); return(_NEAR); }
148 "_xdata"       { count(); return(_XDATA);}
149 "_pdata" { count () ; return(_PDATA); }
150 "_idata" { count () ; return(_IDATA); }
151 "..."              { count(); return(VAR_ARGS);}
152 {L}({L}|{D})*  { count(); return(check_type()); }
153 0[xX]{H}+{IS}? { count(); yylval.val = constVal(yytext); return(CONSTANT); }
154 0{D}+{IS}?     { count(); yylval.val = constVal(yytext); return(CONSTANT); }
155 {D}+{IS}?      { count(); yylval.val = constVal(yytext); return(CONSTANT); }
156 '(\\.|[^\\'])+' { count();yylval.val = charVal (yytext); return(CONSTANT); }
157 {D}+{E}{FS}?   { count(); yylval.val = constFloatVal(yytext);return(CONSTANT); }
158 {D}*"."{D}+({E})?{FS}?  { count(); yylval.val = constFloatVal(yytext);return(CONSTANT); }
159 {D}+"."{D}*({E})?{FS}?  { count(); yylval.val = constFloatVal(yytext);return(CONSTANT); }
160 \"             { count(); yylval.val=strVal(stringLiteral()); return(STRING_LITERAL);}
161 ">>=" { count(); yylval.yyint = RIGHT_ASSIGN ; return(RIGHT_ASSIGN); }
162 "<<=" { count(); yylval.yyint = LEFT_ASSIGN  ; return(LEFT_ASSIGN) ; }
163 "+="  { count(); yylval.yyint = ADD_ASSIGN   ; return(ADD_ASSIGN)  ; }
164 "-="  { count(); yylval.yyint = SUB_ASSIGN   ; return(SUB_ASSIGN)  ; }
165 "*="  { count(); yylval.yyint = MUL_ASSIGN   ; return(MUL_ASSIGN)  ; }
166 "/="  { count(); yylval.yyint = DIV_ASSIGN   ; return(DIV_ASSIGN)  ; }
167 "%="  { count(); yylval.yyint = MOD_ASSIGN   ; return(MOD_ASSIGN)  ; }
168 "&="  { count(); yylval.yyint = AND_ASSIGN   ; return(AND_ASSIGN)  ; }
169 "^="  { count(); yylval.yyint = XOR_ASSIGN   ; return(XOR_ASSIGN)  ; }
170 "|="  { count(); yylval.yyint = OR_ASSIGN    ; return(OR_ASSIGN)   ; }
171 ">>"           { count(); return(RIGHT_OP); }
172 "<<"           { count(); return(LEFT_OP); }
173 "++"           { count(); return(INC_OP); }
174 "--"           { count(); return(DEC_OP); }
175 "->"           { count(); return(PTR_OP); }
176 "&&"           { count(); return(AND_OP); }
177 "||"           { count(); return(OR_OP); }
178 "<="           { count(); return(LE_OP); }
179 ">="           { count(); return(GE_OP); }
180 "=="           { count(); return(EQ_OP); }
181 "!="           { count(); return(NE_OP); }
182 ";"            { count(); return(';'); }
183 "{"                        { count()    ; NestLevel++ ;  return('{'); }
184 "}"                        { count(); NestLevel--; return('}'); }
185 ","            { count(); return(','); }
186 ":"            { count(); return(':'); }
187 "="            { count(); return('='); }
188 "("            { count(); return('('); }
189 ")"            { count(); return(')'); }
190 "["            { count(); return('['); }
191 "]"            { count(); return(']'); }
192 "."            { count(); return('.'); }
193 "&"            { count(); return('&'); }
194 "!"            { count(); return('!'); }
195 "~"            { count(); return('~'); }
196 "-"            { count(); return('-'); }
197 "+"            { count(); return('+'); }
198 "*"            { count(); return('*'); }
199 "/"            { count(); return('/'); }
200 "%"            { count(); return('%'); }
201 "<"            { count(); return('<'); }
202 ">"            { count(); return('>'); }
203 "^"            { count(); return('^'); }
204 "|"            { count(); return('|'); }
205 "?"            { count(); return('?'); }
206 ^#line.*"\n"       { count(); checkCurrFile(yytext); }
207 ^#pragma.*"\n"   { count(); process_pragma(yytext); }
208
209 ^[^(]+"("[0-9]+") : error"[^\n]+ { werror(E_PRE_PROC_FAILED,yytext);count(); }
210 ^[^(]+"("[0-9]+") : warning"[^\n]+ { werror(W_PRE_PROC_WARNING,yytext);count(); }
211 "\r\n"             { count(); }
212 "\n"               { count(); }
213 [ \t\v\f]      { count(); }
214 .                          { count()    ; }
215 %%
216    
217 int checkCurrFile ( char *s)
218 {
219     char lineNum[10]                    ;
220     int  lNum                           ;
221     char *tptr                          ;
222        
223     /* first check if this is a #line */
224     if ( strncmp(s,"#line",5) )
225         return  0                               ;
226     
227     /* get to the line number */
228     while (!isdigit(*s))
229         s++ ;
230     tptr = lineNum ;
231     while (isdigit(*s))
232         *tptr++ = *s++ ;
233     *tptr = '\0'; 
234     sscanf(lineNum,"%d",&lNum);
235     
236     /* now see if we have a file name */
237     while (*s != '\"' && *s) 
238         s++ ;
239     
240     /* if we don't have a filename then */
241     /* set the current line number to   */
242     /* line number if printFlag is on   */
243     if (!*s) {          
244         yylineno = lNum ;
245         return 0;
246     }
247     
248     /* if we have a filename then check */
249     /* if it is "standard in" if yes then */
250     /* get the currentfile name info    */
251     s++ ;
252
253     if ( strncmp(s,fullSrcFileName,strlen(fullSrcFileName)) == 0) {
254             yylineno = lNum - 2;                                        
255             currFname = fullSrcFileName ;
256     }  else {
257         char *sb = s;
258         /* mark the end of the filename */
259         while (*s != '"') s++;
260         *s = '\0';
261         ALLOC_ATOMIC(currFname,strlen(sb)+1);
262         strcpy(currFname,sb);
263         yylineno = lNum - 2;
264     }
265     filename = currFname ;
266     return 0;
267 }
268     
269 void comment()
270 {
271         char c, c1;
272
273 loop:
274         while ((c = input()) != '*' && c != 0)
275                 if ( c == '\n')
276                         yylineno++ ;
277
278         if ((c1 = input()) != '/' && c != 0)  {
279                 if ( c1 == '\n' )
280                         yylineno++ ;
281
282                 unput(c1);
283                 goto loop;
284    }
285
286 }
287    
288    
289
290 int column = 0;
291 int plineIdx=0;
292
293 void count()
294 {
295         int i;
296         for (i = 0; yytext[i] != '\0'; i++)   {                         
297                 if (yytext[i] == '\n')      {         
298                    column = 0;
299                    lineno = ++yylineno ;
300                 }
301                 else 
302                         if (yytext[i] == '\t')
303                                 column += 8 - (column % 8);
304                         else
305                                 column++;
306    }
307          
308    /* ECHO; */
309 }
310
311 int check_type()
312 {
313         /* check if it is in the typedef table */
314         if (findSym(TypedefTab,NULL,yytext)) {
315                 strcpy(yylval.yychar,yytext);
316                 return (TYPE_NAME) ;
317         }
318         else   {
319                 strcpy (yylval.yychar,yytext);
320                 return(IDENTIFIER);
321         }
322 }
323
324 char strLitBuff[2048]                   ;
325
326 char *stringLiteral ()
327 {
328        int ch;
329        char *str = strLitBuff                   ;
330        
331        *str++ = '\"'                    ;
332        /* put into the buffer till we hit the */
333        /* first \" */
334        while (1) {
335
336           ch = input()                  ;
337           if (!ch)          break       ; /* end of input */
338           /* if it is a \ then everything allowed */
339           if (ch == '\\') {
340              *str++ = ch     ; /* backslash in place */
341              *str++ = input()           ; /* following char in place */
342              continue                   ;      /* carry on */
343              }
344              
345          /* if new line we have a new line break */
346          if (ch == '\n') break          ;
347          
348          /* if this is a quote then we have work to do */
349          /* find the next non whitespace character     */
350          /* if that is a double quote then carry on    */
351          if (ch == '\"') {
352          
353              while ((ch = input()) && isspace(ch)) ;
354              if (!ch) break             ; 
355              if (ch != '\"') {
356                   unput(ch)                     ;
357                   break                 ;
358                   }
359                   
360                   continue              ;
361         }
362         *str++  = ch;     
363      }  
364      *str++ = '\"'                      ;
365      *str = '\0';
366      return strLitBuff                  ;
367 }
368
369 void doPragma (int op, char *cp)
370 {
371     switch (op) {
372     case P_SAVE:
373         memcpy(&save_options,&options,sizeof(options));
374         memcpy(&save_optimize,&optimize,sizeof(optimize));
375         break;
376     case P_RESTORE:
377         memcpy(&options,&save_options,sizeof(options));
378         memcpy(&optimize,&save_optimize,sizeof(optimize));
379         break;
380     case P_NOINDUCTION:
381         optimize.loopInduction = 0 ;
382         break;
383     case P_NOINVARIANT:
384         optimize.loopInvariant = 0 ;
385         break;
386     case P_INDUCTION:
387         optimize.loopInduction = 1 ;
388         break;
389     case P_STACKAUTO:
390         options.stackAuto = 1;
391         break;
392     case P_NOJTBOUND:
393         optimize.noJTabBoundary = 1;
394         break;
395     case P_NOGCSE:
396         optimize.global_cse = 0;
397         break;
398     case P_NOOVERLAY:
399         options.noOverlay = 1;
400         break;
401     case P_CALLEE_SAVES:
402         {
403             int i=0;
404             /* append to the functions already listed
405                in callee-saves */
406             for (; options.calleeSaves[i] ;i++);
407             parseWithComma(&options.calleeSaves[i],strdup(cp));
408         }
409         break;
410     case P_EXCLUDE:
411         parseWithComma(options.excludeRegs,strdup(cp));
412         break;
413     case P_LOOPREV:
414         optimize.noLoopReverse = 1;
415         break;
416     }
417 }
418
419 int process_pragma(char *s)
420 {
421     char *cp ;
422     /* find the pragma */
423     while (strncmp(s,"#pragma",7))
424         s++;
425     s += 7;
426     
427     /* look for the directive */
428     while(isspace(*s)) s++;
429
430     cp = s;
431     /* look for the end of the directive */
432     while ((! isspace(*s)) && 
433            (*s != '\n')) 
434         s++ ;    
435
436     /* now compare and do what needs to be done */
437     if (strncmp(cp,PRAGMA_SAVE,strlen(PRAGMA_SAVE)) == 0) {
438         doPragma(P_SAVE,cp+strlen(PRAGMA_SAVE));
439         return 0;
440     }
441
442     if (strncmp(cp,PRAGMA_RESTORE,strlen(PRAGMA_RESTORE)) == 0) {
443         doPragma (P_RESTORE,cp+strlen(PRAGMA_RESTORE));
444         return 0;
445     }
446
447     if (strncmp(cp,PRAGMA_NOINDUCTION,strlen(PRAGMA_NOINDUCTION)) == 0) {
448         doPragma (P_NOINDUCTION,cp+strlen(PRAGMA_NOINDUCTION))  ;
449         return 0;
450     }
451
452     if (strncmp(cp,PRAGMA_NOINVARIANT,strlen(PRAGMA_NOINVARIANT)) == 0) {
453         doPragma (P_NOINVARIANT,NULL)   ;
454         return 0;
455     }
456
457     if (strncmp(cp,PRAGMA_INDUCTION,strlen(PRAGMA_INDUCTION)) == 0) {
458         doPragma (P_INDUCTION,NULL)     ;
459         return 0;
460     }
461
462     if (strncmp(cp,PRAGMA_STACKAUTO,strlen(PRAGMA_STACKAUTO)) == 0) {
463         doPragma (P_STACKAUTO,NULL);
464         return 0;
465     }
466
467     if (strncmp(cp,PRAGMA_NOJTBOUND,strlen(PRAGMA_NOJTBOUND)) == 0) {
468         doPragma (P_NOJTBOUND,NULL);
469         return 0;
470     }
471
472     if (strncmp(cp,PRAGMA_NOGCSE,strlen(PRAGMA_NOGCSE)) == 0) {
473         doPragma (P_NOGCSE,NULL);
474         return 0;
475     }
476
477     if (strncmp(cp,PRAGMA_NOOVERLAY,strlen(PRAGMA_NOOVERLAY)) == 0) {
478         doPragma (P_NOOVERLAY,NULL);
479         return 0;
480     }
481     
482     if (strncmp(cp,PRAGMA_CALLEESAVES,strlen(PRAGMA_CALLEESAVES)) == 0) {
483         doPragma(P_CALLEE_SAVES,cp+strlen(PRAGMA_CALLEESAVES));
484         return 0;
485     }
486     
487     if (strncmp(cp,PRAGMA_EXCLUDE,strlen(PRAGMA_EXCLUDE)) == 0) {
488         doPragma(P_EXCLUDE,cp+strlen(PRAGMA_EXCLUDE));
489         return 0;
490     }
491
492     if (strncmp(cp,PRAGMA_NOLOOPREV,strlen(PRAGMA_NOLOOPREV)) == 0) {
493         doPragma(P_EXCLUDE,NULL);
494         return 0;
495     }
496
497     werror(W_UNKNOWN_PRAGMA,cp);
498     return 0;
499 }