* frame.c (has_stack_frames): Make public.
[binutils-gdb.git] / gdb / ada-lex.l
blob995cd80d2ba6f43cfe95a90b751851dc5bfa4321
1 /* FLEX lexer for Ada expressions, for GDB.
2    Copyright (C) 1994, 1997, 1998, 2000, 2001, 2002, 2003, 2007, 2008, 2009
3    Free Software Foundation, Inc.
5 This file is part of GDB.
7 This program is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2 of the License, or
10 (at your option) any later version.
12 This program is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with this program; if not, write to the Free Software
19 Foundation, Inc., 51 Franklin Street, Fifth Floor,
20 Boston, MA 02110-1301, USA.  */
22 /*----------------------------------------------------------------------*/
24 /* The converted version of this file is to be included in ada-exp.y, */
25 /* the Ada parser for gdb.  The function yylex obtains characters from */
26 /* the global pointer lexptr.  It returns a syntactic category for */
27 /* each successive token and places a semantic value into yylval */
28 /* (ada-lval), defined by the parser.   */
30 DIG     [0-9]
31 NUM10   ({DIG}({DIG}|_)*)
32 HEXDIG  [0-9a-f]
33 NUM16   ({HEXDIG}({HEXDIG}|_)*)
34 OCTDIG  [0-7]
35 LETTER  [a-z_]
36 ID      ({LETTER}({LETTER}|{DIG})*|"<"{LETTER}({LETTER}|{DIG})*">")
37 WHITE   [ \t\n]
38 TICK    ("'"{WHITE}*)
39 GRAPHIC [a-z0-9 #&'()*+,-./:;<>=_|!$%?@\[\]\\^`{}~]
40 OPER    ([-+*/=<>&]|"<="|">="|"**"|"/="|"and"|"or"|"xor"|"not"|"mod"|"rem"|"abs")
42 EXP     (e[+-]{NUM10})
43 POSEXP  (e"+"?{NUM10})
47 #define NUMERAL_WIDTH 256
48 #define LONGEST_SIGN ((ULONGEST) 1 << (sizeof(LONGEST) * HOST_CHAR_BIT - 1))
50 /* Temporary staging for numeric literals.  */
51 static char numbuf[NUMERAL_WIDTH];
52  static void canonicalizeNumeral (char *s1, const char *);
53 static struct stoken processString (const char*, int);
54 static int processInt (const char *, const char *, const char *);
55 static int processReal (const char *);
56 static struct stoken processId (const char *, int);
57 static int processAttribute (const char *);
58 static int find_dot_all (const char *);
60 #undef YY_DECL
61 #define YY_DECL static int yylex ( void )
63 #undef YY_INPUT
64 #define YY_INPUT(BUF, RESULT, MAX_SIZE) \
65     if ( *lexptr == '\000' ) \
66       (RESULT) = YY_NULL; \
67     else \
68       { \
69         *(BUF) = *lexptr; \
70         (RESULT) = 1; \
71         lexptr += 1; \
72       }
74 static int find_dot_all (const char *);
78 %option case-insensitive interactive nodefault
80 %s BEFORE_QUAL_QUOTE
84 {WHITE}          { }
86 "--".*           { yyterminate(); }
88 {NUM10}{POSEXP}  {
89                    canonicalizeNumeral (numbuf, yytext);
90                    return processInt (NULL, numbuf, strrchr(numbuf, 'e')+1);
91                  }
93 {NUM10}          {
94                    canonicalizeNumeral (numbuf, yytext);
95                    return processInt (NULL, numbuf, NULL);
96                  }
98 {NUM10}"#"{HEXDIG}({HEXDIG}|_)*"#"{POSEXP} {
99                    canonicalizeNumeral (numbuf, yytext);
100                    return processInt (numbuf,
101                                       strchr (numbuf, '#') + 1,
102                                       strrchr(numbuf, '#') + 1);
103                  }
105 {NUM10}"#"{HEXDIG}({HEXDIG}|_)*"#" {
106                    canonicalizeNumeral (numbuf, yytext);
107                    return processInt (numbuf, strchr (numbuf, '#') + 1, NULL);
108                  }
110 "0x"{HEXDIG}+   {
111                   canonicalizeNumeral (numbuf, yytext+2);
112                   return processInt ("16#", numbuf, NULL);
113                 }
116 {NUM10}"."{NUM10}{EXP} {
117                    canonicalizeNumeral (numbuf, yytext);
118                    return processReal (numbuf);
119                 }
121 {NUM10}"."{NUM10} {
122                    canonicalizeNumeral (numbuf, yytext);
123                    return processReal (numbuf);
124                 }
126 {NUM10}"#"{NUM16}"."{NUM16}"#"{EXP} {
127                    error (_("Based real literals not implemented yet."));
128                 }
130 {NUM10}"#"{NUM16}"."{NUM16}"#" {
131                    error (_("Based real literals not implemented yet."));
132                 }
134 <INITIAL>"'"({GRAPHIC}|\")"'" {
135                    yylval.typed_val.type = type_char ();
136                    yylval.typed_val.val = yytext[1];
137                    return CHARLIT;
138                 }
140 <INITIAL>"'[\""{HEXDIG}{2}"\"]'"   {
141                    int v;
142                    yylval.typed_val.type = type_char ();
143                    sscanf (yytext+3, "%2x", &v);
144                    yylval.typed_val.val = v;
145                    return CHARLIT;
146                 }
148 \"({GRAPHIC}|"[\""({HEXDIG}{2}|\")"\"]")*\"   {
149                    yylval.sval = processString (yytext+1, yyleng-2);
150                    return STRING;
151                 }
153 \"              {
154                    error (_("ill-formed or non-terminated string literal"));
155                 }
158 if              {
159                   while (*lexptr != 'i' && *lexptr != 'I')
160                     lexptr -= 1;
161                   yyrestart(NULL);
162                   return 0;
163                 }
165         /* ADA KEYWORDS */
167 abs             { return ABS; }
168 and             { return _AND_; }
169 else            { return ELSE; }
170 in              { return IN; }
171 mod             { return MOD; }
172 new             { return NEW; }
173 not             { return NOT; }
174 null            { return NULL_PTR; }
175 or              { return OR; }
176 others          { return OTHERS; }
177 rem             { return REM; }
178 then            { return THEN; }
179 xor             { return XOR; }
181         /* BOOLEAN "KEYWORDS" */
183  /* True and False are not keywords in Ada, but rather enumeration constants.
184     However, the boolean type is no longer represented as an enum, so True
185     and False are no longer defined in symbol tables.  We compromise by
186     making them keywords (when bare). */
188 true            { return TRUEKEYWORD; }
189 false           { return FALSEKEYWORD; }
191         /* ATTRIBUTES */
193 {TICK}[a-zA-Z][a-zA-Z]+ { return processAttribute (yytext+1); }
195         /* PUNCTUATION */
197 "=>"            { return ARROW; }
198 ".."            { return DOTDOT; }
199 "**"            { return STARSTAR; }
200 ":="            { return ASSIGN; }
201 "/="            { return NOTEQUAL; }
202 "<="            { return LEQ; }
203 ">="            { return GEQ; }
205 <BEFORE_QUAL_QUOTE>"'" { BEGIN INITIAL; return '\''; }
207 [-&*+./:<>=|;\[\]] { return yytext[0]; }
209 ","             { if (paren_depth == 0 && comma_terminates)
210                     {
211                       lexptr -= 1;
212                       yyrestart(NULL);
213                       return 0;
214                     }
215                   else
216                     return ',';
217                 }
219 "("             { paren_depth += 1; return '('; }
220 ")"             { if (paren_depth == 0)
221                     {
222                       lexptr -= 1;
223                       yyrestart(NULL);
224                       return 0;
225                     }
226                   else
227                     {
228                       paren_depth -= 1;
229                       return ')';
230                     }
231                 }
233 "."{WHITE}*all  { return DOT_ALL; }
235 "."{WHITE}*{ID} {
236                   yylval.sval = processId (yytext+1, yyleng-1);
237                   return DOT_ID;
238                 }
240 {ID}({WHITE}*"."{WHITE}*({ID}|\"{OPER}\"))*(" "*"'")?  {
241                   int all_posn = find_dot_all (yytext);
243                   if (all_posn == -1 && yytext[yyleng-1] == '\'')
244                     {
245                       BEGIN BEFORE_QUAL_QUOTE;
246                       yyless (yyleng-1);
247                     }
248                   else if (all_posn >= 0)
249                     yyless (all_posn);
250                   yylval.sval = processId (yytext, yyleng);
251                   return NAME;
252                }
255         /* GDB EXPRESSION CONSTRUCTS  */
257 "'"[^']+"'"{WHITE}*:: {
258                   yyless (yyleng - 2);
259                   yylval.sval = processId (yytext, yyleng);
260                   return NAME;
261                 }
263 "::"            { return COLONCOLON; }
265 [{}@]           { return yytext[0]; }
267         /* REGISTERS AND GDB CONVENIENCE VARIABLES */
269 "$"({LETTER}|{DIG}|"$")*  {
270                   yylval.sval.ptr = yytext;
271                   yylval.sval.length = yyleng;
272                   return SPECIAL_VARIABLE;
273                 }
275         /* CATCH-ALL ERROR CASE */
277 .               { error (_("Invalid character '%s' in expression."), yytext); }
280 #include <ctype.h>
281 #include "gdb_string.h"
283 /* Initialize the lexer for processing new expression. */
285 void
286 lexer_init (FILE *inp)
288   BEGIN INITIAL;
289   yyrestart (inp);
293 /* Copy S2 to S1, removing all underscores, and downcasing all letters.  */
295 static void
296 canonicalizeNumeral (char *s1, const char *s2)
298   for (; *s2 != '\000'; s2 += 1)
299     {
300       if (*s2 != '_')
301         {
302           *s1 = tolower(*s2);
303           s1 += 1;
304         }
305     }
306   s1[0] = '\000';
309 /* Interprets the prefix of NUM that consists of digits of the given BASE
310    as an integer of that BASE, with the string EXP as an exponent.
311    Puts value in yylval, and returns INT, if the string is valid.  Causes
312    an error if the number is improperly formated.   BASE, if NULL, defaults
313    to "10", and EXP to "1".  The EXP does not contain a leading 'e' or 'E'.
314  */
316 static int
317 processInt (const char *base0, const char *num0, const char *exp0)
319   ULONGEST result;
320   long exp;
321   int base;
323   char *trailer;
325   if (base0 == NULL)
326     base = 10;
327   else
328     {
329       base = strtol (base0, (char **) NULL, 10);
330       if (base < 2 || base > 16)
331         error (_("Invalid base: %d."), base);
332     }
334   if (exp0 == NULL)
335     exp = 0;
336   else
337     exp = strtol(exp0, (char **) NULL, 10);
339   errno = 0;
340   result = strtoulst (num0, (const char **) &trailer, base);
341   if (errno == ERANGE)
342     error (_("Integer literal out of range"));
343   if (isxdigit(*trailer))
344     error (_("Invalid digit `%c' in based literal"), *trailer);
346   while (exp > 0)
347     {
348       if (result > (ULONG_MAX / base))
349         error (_("Integer literal out of range"));
350       result *= base;
351       exp -= 1;
352     }
354   if ((result >> (gdbarch_int_bit (parse_gdbarch)-1)) == 0)
355     yylval.typed_val.type = type_int ();
356   else if ((result >> (gdbarch_long_bit (parse_gdbarch)-1)) == 0)
357     yylval.typed_val.type = type_long ();
358   else if (((result >> (gdbarch_long_bit (parse_gdbarch)-1)) >> 1) == 0)
359     {
360       /* We have a number representable as an unsigned integer quantity.
361          For consistency with the C treatment, we will treat it as an
362          anonymous modular (unsigned) quantity.  Alas, the types are such
363          that we need to store .val as a signed quantity.  Sorry
364          for the mess, but C doesn't officially guarantee that a simple
365          assignment does the trick (no, it doesn't; read the reference manual).
366        */
367       yylval.typed_val.type
368         = builtin_type (parse_gdbarch)->builtin_unsigned_long;
369       if (result & LONGEST_SIGN)
370         yylval.typed_val.val =
371           (LONGEST) (result & ~LONGEST_SIGN)
372           - (LONGEST_SIGN>>1) - (LONGEST_SIGN>>1);
373       else
374         yylval.typed_val.val = (LONGEST) result;
375       return INT;
376     }
377   else
378     yylval.typed_val.type = type_long_long ();
380   yylval.typed_val.val = (LONGEST) result;
381   return INT;
384 static int
385 processReal (const char *num0)
387   sscanf (num0, "%" DOUBLEST_SCAN_FORMAT, &yylval.typed_val_float.dval);
389   yylval.typed_val_float.type = type_float ();
390   if (sizeof(DOUBLEST) >= gdbarch_double_bit (parse_gdbarch)
391                             / TARGET_CHAR_BIT)
392     yylval.typed_val_float.type = type_double ();
393   if (sizeof(DOUBLEST) >= gdbarch_long_double_bit (parse_gdbarch)
394                             / TARGET_CHAR_BIT)
395     yylval.typed_val_float.type = type_long_double ();
397   return FLOAT;
401 /* Store a canonicalized version of NAME0[0..LEN-1] in yylval.ssym.  The
402    resulting string is valid until the next call to ada_parse.  It differs
403    from NAME0 in that:
404     + Characters between '...' or <...> are transfered verbatim to 
405       yylval.ssym.
406     + <, >, and trailing "'" characters in quoted sequences are removed
407       (a leading quote is preserved to indicate that the name is not to be
408       GNAT-encoded).
409     + Unquoted whitespace is removed.
410     + Unquoted alphabetic characters are mapped to lower case.
411    Result is returned as a struct stoken, but for convenience, the string
412    is also null-terminated.  Result string valid until the next call of
413    ada_parse.
414  */
415 static struct stoken
416 processId (const char *name0, int len)
418   char *name = obstack_alloc (&temp_parse_space, len + 11);
419   int i0, i;
420   struct stoken result;
422   while (len > 0 && isspace (name0[len-1]))
423     len -= 1;
424   i = i0 = 0;
425   while (i0 < len)
426     {
427       if (isalnum (name0[i0]))
428         {
429           name[i] = tolower (name0[i0]);
430           i += 1; i0 += 1;
431         }
432       else switch (name0[i0])
433         {
434         default:
435           name[i] = name0[i0];
436           i += 1; i0 += 1;
437           break;
438         case ' ': case '\t':
439           i0 += 1;
440           break;
441         case '\'':
442           do
443             {
444               name[i] = name0[i0];
445               i += 1; i0 += 1;
446             }
447           while (i0 < len && name0[i0] != '\'');
448           i0 += 1;
449           break;
450         case '<':
451           i0 += 1;
452           while (i0 < len && name0[i0] != '>')
453             {
454               name[i] = name0[i0];
455               i += 1; i0 += 1;
456             }
457           i0 += 1;
458           break;
459         }
460     }
461   name[i] = '\000';
463   result.ptr = name;
464   result.length = i;
465   return result;
468 /* Return TEXT[0..LEN-1], a string literal without surrounding quotes,
469    with special hex character notations replaced with characters. 
470    Result valid until the next call to ada_parse.  */
472 static struct stoken
473 processString (const char *text, int len)
475   const char *p;
476   char *q;
477   const char *lim = text + len;
478   struct stoken result;
480   q = result.ptr = obstack_alloc (&temp_parse_space, len);
481   p = text;
482   while (p < lim)
483     {
484       if (p[0] == '[' && p[1] == '"' && p+2 < lim)
485          {
486            if (p[2] == '"')  /* "...["""]... */
487              {
488                *q = '"';
489                p += 4;
490              }
491            else
492              {
493                int chr;
494                sscanf (p+2, "%2x", &chr);
495                *q = (char) chr;
496                p += 5;
497              }
498          }
499        else
500          *q = *p;
501        q += 1;
502        p += 1;
503      }
504   result.length = q - result.ptr;
505   return result;
508 /* Returns the position within STR of the '.' in a
509    '.{WHITE}*all' component of a dotted name, or -1 if there is none.
510    Note: we actually don't need this routine, since 'all' can never be an
511    Ada identifier.  Thus, looking up foo.all or foo.all.x as a name
512    must fail, and will eventually be interpreted as (foo).all or
513    (foo).all.x.  However, this does avoid an extraneous lookup. */
515 static int
516 find_dot_all (const char *str)
518   int i;
519   for (i = 0; str[i] != '\000'; i += 1)
520     {
521       if (str[i] == '.')
522         {
523           int i0 = i;
524           do
525             i += 1;
526           while (isspace (str[i]));
527           if (strncmp (str+i, "all", 3) == 0
528               && ! isalnum (str[i+3]) && str[i+3] != '_')
529             return i0;
530         }
531     }
532   return -1;
535 /* Returns non-zero iff string SUBSEQ matches a subsequence of STR, ignoring
536    case.  */
538 static int
539 subseqMatch (const char *subseq, const char *str)
541   if (subseq[0] == '\0')
542     return 1;
543   else if (str[0] == '\0')
544     return 0;
545   else if (tolower (subseq[0]) == tolower (str[0]))
546     return subseqMatch (subseq+1, str+1) || subseqMatch (subseq, str+1);
547   else
548     return subseqMatch (subseq, str+1);
552 static struct { const char *name; int code; }
553 attributes[] = {
554   { "address", TICK_ADDRESS },
555   { "unchecked_access", TICK_ACCESS },
556   { "unrestricted_access", TICK_ACCESS },
557   { "access", TICK_ACCESS },
558   { "first", TICK_FIRST },
559   { "last", TICK_LAST },
560   { "length", TICK_LENGTH },
561   { "max", TICK_MAX },
562   { "min", TICK_MIN },
563   { "modulus", TICK_MODULUS },
564   { "pos", TICK_POS },
565   { "range", TICK_RANGE },
566   { "size", TICK_SIZE },
567   { "tag", TICK_TAG },
568   { "val", TICK_VAL },
569   { NULL, -1 }
572 /* Return the syntactic code corresponding to the attribute name or
573    abbreviation STR.  */
575 static int
576 processAttribute (const char *str)
578   int i, k;
580   for (i = 0; attributes[i].code != -1; i += 1)
581     if (strcasecmp (str, attributes[i].name) == 0)
582       return attributes[i].code;
584   for (i = 0, k = -1; attributes[i].code != -1; i += 1)
585     if (subseqMatch (str, attributes[i].name))
586       {
587         if (k == -1)
588           k = i;
589         else
590           error (_("ambiguous attribute name: `%s'"), str);
591       }
592   if (k == -1)
593     error (_("unrecognized attribute: `%s'"), str);
595   return attributes[k].code;
599 yywrap(void)
601   return 1;
604 /* Dummy definition to suppress warnings about unused static definitions. */
605 typedef void (*dummy_function) ();
606 dummy_function ada_flex_use[] = 
608   (dummy_function) yyunput