]> git.ipfire.org Git - thirdparty/binutils-gdb.git/blob - gdb/p-exp.y
2000-06-14 Pierre Muller <muller@ics.u-strasbg.fr>
[thirdparty/binutils-gdb.git] / gdb / p-exp.y
1 /* YACC parser for Pascal expressions, for GDB.
2 Copyright (C) 2000
3 Free Software Foundation, Inc.
4
5 This file is part of GDB.
6
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.
11
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.
16
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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
20
21 /* This file is derived from c-exp.y */
22
23 /* Parse a Pascal expression from text in a string,
24 and return the result as a struct expression pointer.
25 That structure contains arithmetic operations in reverse polish,
26 with constants represented by operations that are followed by special data.
27 See expression.h for the details of the format.
28 What is important here is that it can be built up sequentially
29 during the process of parsing; the lower levels of the tree always
30 come first in the result.
31
32 Note that malloc's and realloc's in this file are transformed to
33 xmalloc and xrealloc respectively by the same sed command in the
34 makefile that remaps any other malloc/realloc inserted by the parser
35 generator. Doing this with #defines and trying to control the interaction
36 with include files (<malloc.h> and <stdlib.h> for example) just became
37 too messy, particularly when such includes can be inserted at random
38 times by the parser generator. */
39
40 /* FIXME: there are still 21 shift/reduce conflicts
41 Other known bugs or limitations:
42 - pascal string operations are not supported at all.
43 - there are some problems with boolean types.
44 - Pascal type hexadecimal constants are not supported
45 because they conflict with the internal variables format.
46 Probably also lots of other problems, less well defined PM */
47 %{
48
49 #include "defs.h"
50 #include "gdb_string.h"
51 #include <ctype.h>
52 #include "expression.h"
53 #include "value.h"
54 #include "parser-defs.h"
55 #include "language.h"
56 #include "p-lang.h"
57 #include "bfd.h" /* Required by objfiles.h. */
58 #include "symfile.h" /* Required by objfiles.h. */
59 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
60
61 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
62 as well as gratuitiously global symbol names, so we can have multiple
63 yacc generated parsers in gdb. Note that these are only the variables
64 produced by yacc. If other parser generators (bison, byacc, etc) produce
65 additional global names that conflict at link time, then those parser
66 generators need to be fixed instead of adding those names to this list. */
67
68 #define yymaxdepth pascal_maxdepth
69 #define yyparse pascal_parse
70 #define yylex pascal_lex
71 #define yyerror pascal_error
72 #define yylval pascal_lval
73 #define yychar pascal_char
74 #define yydebug pascal_debug
75 #define yypact pascal_pact
76 #define yyr1 pascal_r1
77 #define yyr2 pascal_r2
78 #define yydef pascal_def
79 #define yychk pascal_chk
80 #define yypgo pascal_pgo
81 #define yyact pascal_act
82 #define yyexca pascal_exca
83 #define yyerrflag pascal_errflag
84 #define yynerrs pascal_nerrs
85 #define yyps pascal_ps
86 #define yypv pascal_pv
87 #define yys pascal_s
88 #define yy_yys pascal_yys
89 #define yystate pascal_state
90 #define yytmp pascal_tmp
91 #define yyv pascal_v
92 #define yy_yyv pascal_yyv
93 #define yyval pascal_val
94 #define yylloc pascal_lloc
95 #define yyreds pascal_reds /* With YYDEBUG defined */
96 #define yytoks pascal_toks /* With YYDEBUG defined */
97 #define yylhs pascal_yylhs
98 #define yylen pascal_yylen
99 #define yydefred pascal_yydefred
100 #define yydgoto pascal_yydgoto
101 #define yysindex pascal_yysindex
102 #define yyrindex pascal_yyrindex
103 #define yygindex pascal_yygindex
104 #define yytable pascal_yytable
105 #define yycheck pascal_yycheck
106
107 #ifndef YYDEBUG
108 #define YYDEBUG 0 /* Default to no yydebug support */
109 #endif
110
111 int yyparse (void);
112
113 static int yylex (void);
114
115 void
116 yyerror (char *);
117
118 static char * uptok (char *, int);
119 %}
120
121 /* Although the yacc "value" of an expression is not used,
122 since the result is stored in the structure being created,
123 other node types do have values. */
124
125 %union
126 {
127 LONGEST lval;
128 struct {
129 LONGEST val;
130 struct type *type;
131 } typed_val_int;
132 struct {
133 DOUBLEST dval;
134 struct type *type;
135 } typed_val_float;
136 struct symbol *sym;
137 struct type *tval;
138 struct stoken sval;
139 struct ttype tsym;
140 struct symtoken ssym;
141 int voidval;
142 struct block *bval;
143 enum exp_opcode opcode;
144 struct internalvar *ivar;
145
146 struct type **tvec;
147 int *ivec;
148 }
149
150 %{
151 /* YYSTYPE gets defined by %union */
152 static int
153 parse_number (char *, int, int, YYSTYPE *);
154 %}
155
156 %type <voidval> exp exp1 type_exp start variable qualified_name
157 %type <tval> type typebase
158 /* %type <bval> block */
159
160 /* Fancy type parsing. */
161 %type <tval> ptype
162
163 %token <typed_val_int> INT
164 %token <typed_val_float> FLOAT
165
166 /* Both NAME and TYPENAME tokens represent symbols in the input,
167 and both convey their data as strings.
168 But a TYPENAME is a string that happens to be defined as a typedef
169 or builtin type name (such as int or char)
170 and a NAME is any other symbol.
171 Contexts where this distinction is not important can use the
172 nonterminal "name", which matches either NAME or TYPENAME. */
173
174 %token <sval> STRING
175 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
176 %token <tsym> TYPENAME
177 %type <sval> name
178 %type <ssym> name_not_typename
179
180 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
181 but which would parse as a valid number in the current input radix.
182 E.g. "c" when input_radix==16. Depending on the parse, it will be
183 turned into a name or into a number. */
184
185 %token <ssym> NAME_OR_INT
186
187 %token STRUCT CLASS SIZEOF COLONCOLON
188 %token ERROR
189
190 /* Special type cases, put in to allow the parser to distinguish different
191 legal basetypes. */
192
193 %token <voidval> VARIABLE
194
195
196 /* Object pascal */
197 %token THIS
198 %token <lval> TRUE FALSE
199
200 %left ','
201 %left ABOVE_COMMA
202 %right ASSIGN
203 %left NOT
204 %left OR
205 %left XOR
206 %left ANDAND
207 %left '=' NOTEQUAL
208 %left '<' '>' LEQ GEQ
209 %left LSH RSH DIV MOD
210 %left '@'
211 %left '+' '-'
212 %left '*' '/'
213 %right UNARY INCREMENT DECREMENT
214 %right ARROW '.' '[' '('
215 %token <ssym> BLOCKNAME
216 %type <bval> block
217 %left COLONCOLON
218
219 \f
220 %%
221
222 start : exp1
223 | type_exp
224 ;
225
226 type_exp: type
227 { write_exp_elt_opcode(OP_TYPE);
228 write_exp_elt_type($1);
229 write_exp_elt_opcode(OP_TYPE);}
230 ;
231
232 /* Expressions, including the comma operator. */
233 exp1 : exp
234 | exp1 ',' exp
235 { write_exp_elt_opcode (BINOP_COMMA); }
236 ;
237
238 /* Expressions, not including the comma operator. */
239 exp : exp '^' %prec UNARY
240 { write_exp_elt_opcode (UNOP_IND); }
241
242 exp : '@' exp %prec UNARY
243 { write_exp_elt_opcode (UNOP_ADDR); }
244
245 exp : '-' exp %prec UNARY
246 { write_exp_elt_opcode (UNOP_NEG); }
247 ;
248
249 exp : NOT exp %prec UNARY
250 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
251 ;
252
253 exp : INCREMENT '(' exp ')' %prec UNARY
254 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
255 ;
256
257 exp : DECREMENT '(' exp ')' %prec UNARY
258 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
259 ;
260
261 exp : exp '.' name
262 { write_exp_elt_opcode (STRUCTOP_STRUCT);
263 write_exp_string ($3);
264 write_exp_elt_opcode (STRUCTOP_STRUCT); }
265 ;
266
267 exp : exp '[' exp1 ']'
268 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
269 ;
270
271 exp : exp '('
272 /* This is to save the value of arglist_len
273 being accumulated by an outer function call. */
274 { start_arglist (); }
275 arglist ')' %prec ARROW
276 { write_exp_elt_opcode (OP_FUNCALL);
277 write_exp_elt_longcst ((LONGEST) end_arglist ());
278 write_exp_elt_opcode (OP_FUNCALL); }
279 ;
280
281 arglist :
282 | exp
283 { arglist_len = 1; }
284 | arglist ',' exp %prec ABOVE_COMMA
285 { arglist_len++; }
286 ;
287
288 exp : type '(' exp ')' %prec UNARY
289 { write_exp_elt_opcode (UNOP_CAST);
290 write_exp_elt_type ($1);
291 write_exp_elt_opcode (UNOP_CAST); }
292 ;
293
294 exp : '(' exp1 ')'
295 { }
296 ;
297
298 /* Binary operators in order of decreasing precedence. */
299
300 exp : exp '*' exp
301 { write_exp_elt_opcode (BINOP_MUL); }
302 ;
303
304 exp : exp '/' exp
305 { write_exp_elt_opcode (BINOP_DIV); }
306 ;
307
308 exp : exp DIV exp
309 { write_exp_elt_opcode (BINOP_INTDIV); }
310 ;
311
312 exp : exp MOD exp
313 { write_exp_elt_opcode (BINOP_REM); }
314 ;
315
316 exp : exp '+' exp
317 { write_exp_elt_opcode (BINOP_ADD); }
318 ;
319
320 exp : exp '-' exp
321 { write_exp_elt_opcode (BINOP_SUB); }
322 ;
323
324 exp : exp LSH exp
325 { write_exp_elt_opcode (BINOP_LSH); }
326 ;
327
328 exp : exp RSH exp
329 { write_exp_elt_opcode (BINOP_RSH); }
330 ;
331
332 exp : exp '=' exp
333 { write_exp_elt_opcode (BINOP_EQUAL); }
334 ;
335
336 exp : exp NOTEQUAL exp
337 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
338 ;
339
340 exp : exp LEQ exp
341 { write_exp_elt_opcode (BINOP_LEQ); }
342 ;
343
344 exp : exp GEQ exp
345 { write_exp_elt_opcode (BINOP_GEQ); }
346 ;
347
348 exp : exp '<' exp
349 { write_exp_elt_opcode (BINOP_LESS); }
350 ;
351
352 exp : exp '>' exp
353 { write_exp_elt_opcode (BINOP_GTR); }
354 ;
355
356 exp : exp ANDAND exp
357 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
358 ;
359
360 exp : exp XOR exp
361 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
362 ;
363
364 exp : exp OR exp
365 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
366 ;
367
368 exp : exp ASSIGN exp
369 { write_exp_elt_opcode (BINOP_ASSIGN); }
370 ;
371
372 exp : TRUE
373 { write_exp_elt_opcode (OP_BOOL);
374 write_exp_elt_longcst ((LONGEST) $1);
375 write_exp_elt_opcode (OP_BOOL); }
376 ;
377
378 exp : FALSE
379 { write_exp_elt_opcode (OP_BOOL);
380 write_exp_elt_longcst ((LONGEST) $1);
381 write_exp_elt_opcode (OP_BOOL); }
382 ;
383
384 exp : INT
385 { write_exp_elt_opcode (OP_LONG);
386 write_exp_elt_type ($1.type);
387 write_exp_elt_longcst ((LONGEST)($1.val));
388 write_exp_elt_opcode (OP_LONG); }
389 ;
390
391 exp : NAME_OR_INT
392 { YYSTYPE val;
393 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
394 write_exp_elt_opcode (OP_LONG);
395 write_exp_elt_type (val.typed_val_int.type);
396 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
397 write_exp_elt_opcode (OP_LONG);
398 }
399 ;
400
401
402 exp : FLOAT
403 { write_exp_elt_opcode (OP_DOUBLE);
404 write_exp_elt_type ($1.type);
405 write_exp_elt_dblcst ($1.dval);
406 write_exp_elt_opcode (OP_DOUBLE); }
407 ;
408
409 exp : variable
410 ;
411
412 exp : VARIABLE
413 /* Already written by write_dollar_variable. */
414 ;
415
416 exp : SIZEOF '(' type ')' %prec UNARY
417 { write_exp_elt_opcode (OP_LONG);
418 write_exp_elt_type (builtin_type_int);
419 CHECK_TYPEDEF ($3);
420 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
421 write_exp_elt_opcode (OP_LONG); }
422 ;
423
424 exp : STRING
425 { /* C strings are converted into array constants with
426 an explicit null byte added at the end. Thus
427 the array upper bound is the string length.
428 There is no such thing in C as a completely empty
429 string. */
430 char *sp = $1.ptr; int count = $1.length;
431 while (count-- > 0)
432 {
433 write_exp_elt_opcode (OP_LONG);
434 write_exp_elt_type (builtin_type_char);
435 write_exp_elt_longcst ((LONGEST)(*sp++));
436 write_exp_elt_opcode (OP_LONG);
437 }
438 write_exp_elt_opcode (OP_LONG);
439 write_exp_elt_type (builtin_type_char);
440 write_exp_elt_longcst ((LONGEST)'\0');
441 write_exp_elt_opcode (OP_LONG);
442 write_exp_elt_opcode (OP_ARRAY);
443 write_exp_elt_longcst ((LONGEST) 0);
444 write_exp_elt_longcst ((LONGEST) ($1.length));
445 write_exp_elt_opcode (OP_ARRAY); }
446 ;
447
448 /* Object pascal */
449 exp : THIS
450 { write_exp_elt_opcode (OP_THIS);
451 write_exp_elt_opcode (OP_THIS); }
452 ;
453
454 /* end of object pascal. */
455
456 block : BLOCKNAME
457 {
458 if ($1.sym != 0)
459 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
460 else
461 {
462 struct symtab *tem =
463 lookup_symtab (copy_name ($1.stoken));
464 if (tem)
465 $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK);
466 else
467 error ("No file or function \"%s\".",
468 copy_name ($1.stoken));
469 }
470 }
471 ;
472
473 block : block COLONCOLON name
474 { struct symbol *tem
475 = lookup_symbol (copy_name ($3), $1,
476 VAR_NAMESPACE, (int *) NULL,
477 (struct symtab **) NULL);
478 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
479 error ("No function \"%s\" in specified context.",
480 copy_name ($3));
481 $$ = SYMBOL_BLOCK_VALUE (tem); }
482 ;
483
484 variable: block COLONCOLON name
485 { struct symbol *sym;
486 sym = lookup_symbol (copy_name ($3), $1,
487 VAR_NAMESPACE, (int *) NULL,
488 (struct symtab **) NULL);
489 if (sym == 0)
490 error ("No symbol \"%s\" in specified context.",
491 copy_name ($3));
492
493 write_exp_elt_opcode (OP_VAR_VALUE);
494 /* block_found is set by lookup_symbol. */
495 write_exp_elt_block (block_found);
496 write_exp_elt_sym (sym);
497 write_exp_elt_opcode (OP_VAR_VALUE); }
498 ;
499
500 qualified_name: typebase COLONCOLON name
501 {
502 struct type *type = $1;
503 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
504 && TYPE_CODE (type) != TYPE_CODE_UNION)
505 error ("`%s' is not defined as an aggregate type.",
506 TYPE_NAME (type));
507
508 write_exp_elt_opcode (OP_SCOPE);
509 write_exp_elt_type (type);
510 write_exp_string ($3);
511 write_exp_elt_opcode (OP_SCOPE);
512 }
513 ;
514
515 variable: qualified_name
516 | COLONCOLON name
517 {
518 char *name = copy_name ($2);
519 struct symbol *sym;
520 struct minimal_symbol *msymbol;
521
522 sym =
523 lookup_symbol (name, (const struct block *) NULL,
524 VAR_NAMESPACE, (int *) NULL,
525 (struct symtab **) NULL);
526 if (sym)
527 {
528 write_exp_elt_opcode (OP_VAR_VALUE);
529 write_exp_elt_block (NULL);
530 write_exp_elt_sym (sym);
531 write_exp_elt_opcode (OP_VAR_VALUE);
532 break;
533 }
534
535 msymbol = lookup_minimal_symbol (name, NULL, NULL);
536 if (msymbol != NULL)
537 {
538 write_exp_msymbol (msymbol,
539 lookup_function_type (builtin_type_int),
540 builtin_type_int);
541 }
542 else
543 if (!have_full_symbols () && !have_partial_symbols ())
544 error ("No symbol table is loaded. Use the \"file\" command.");
545 else
546 error ("No symbol \"%s\" in current context.", name);
547 }
548 ;
549
550 variable: name_not_typename
551 { struct symbol *sym = $1.sym;
552
553 if (sym)
554 {
555 if (symbol_read_needs_frame (sym))
556 {
557 if (innermost_block == 0 ||
558 contained_in (block_found,
559 innermost_block))
560 innermost_block = block_found;
561 }
562
563 write_exp_elt_opcode (OP_VAR_VALUE);
564 /* We want to use the selected frame, not
565 another more inner frame which happens to
566 be in the same block. */
567 write_exp_elt_block (NULL);
568 write_exp_elt_sym (sym);
569 write_exp_elt_opcode (OP_VAR_VALUE);
570 }
571 else if ($1.is_a_field_of_this)
572 {
573 /* Object pascal: it hangs off of `this'. Must
574 not inadvertently convert from a method call
575 to data ref. */
576 if (innermost_block == 0 ||
577 contained_in (block_found, innermost_block))
578 innermost_block = block_found;
579 write_exp_elt_opcode (OP_THIS);
580 write_exp_elt_opcode (OP_THIS);
581 write_exp_elt_opcode (STRUCTOP_PTR);
582 write_exp_string ($1.stoken);
583 write_exp_elt_opcode (STRUCTOP_PTR);
584 }
585 else
586 {
587 struct minimal_symbol *msymbol;
588 register char *arg = copy_name ($1.stoken);
589
590 msymbol =
591 lookup_minimal_symbol (arg, NULL, NULL);
592 if (msymbol != NULL)
593 {
594 write_exp_msymbol (msymbol,
595 lookup_function_type (builtin_type_int),
596 builtin_type_int);
597 }
598 else if (!have_full_symbols () && !have_partial_symbols ())
599 error ("No symbol table is loaded. Use the \"file\" command.");
600 else
601 error ("No symbol \"%s\" in current context.",
602 copy_name ($1.stoken));
603 }
604 }
605 ;
606
607
608 ptype : typebase
609 ;
610
611 /* We used to try to recognize more pointer to member types here, but
612 that didn't work (shift/reduce conflicts meant that these rules never
613 got executed). The problem is that
614 int (foo::bar::baz::bizzle)
615 is a function type but
616 int (foo::bar::baz::bizzle::*)
617 is a pointer to member type. Stroustrup loses again! */
618
619 type : ptype
620 | typebase COLONCOLON '*'
621 { $$ = lookup_member_type (builtin_type_int, $1); }
622 ;
623
624 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
625 : TYPENAME
626 { $$ = $1.type; }
627 | STRUCT name
628 { $$ = lookup_struct (copy_name ($2),
629 expression_context_block); }
630 | CLASS name
631 { $$ = lookup_struct (copy_name ($2),
632 expression_context_block); }
633 /* "const" and "volatile" are curently ignored. A type qualifier
634 after the type is handled in the ptype rule. I think these could
635 be too. */
636 ;
637
638 name : NAME { $$ = $1.stoken; }
639 | BLOCKNAME { $$ = $1.stoken; }
640 | TYPENAME { $$ = $1.stoken; }
641 | NAME_OR_INT { $$ = $1.stoken; }
642 ;
643
644 name_not_typename : NAME
645 | BLOCKNAME
646 /* These would be useful if name_not_typename was useful, but it is just
647 a fake for "variable", so these cause reduce/reduce conflicts because
648 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
649 =exp) or just an exp. If name_not_typename was ever used in an lvalue
650 context where only a name could occur, this might be useful.
651 | NAME_OR_INT
652 */
653 ;
654
655 %%
656
657 /* Take care of parsing a number (anything that starts with a digit).
658 Set yylval and return the token type; update lexptr.
659 LEN is the number of characters in it. */
660
661 /*** Needs some error checking for the float case ***/
662
663 static int
664 parse_number (p, len, parsed_float, putithere)
665 register char *p;
666 register int len;
667 int parsed_float;
668 YYSTYPE *putithere;
669 {
670 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
671 here, and we do kind of silly things like cast to unsigned. */
672 register LONGEST n = 0;
673 register LONGEST prevn = 0;
674 ULONGEST un;
675
676 register int i = 0;
677 register int c;
678 register int base = input_radix;
679 int unsigned_p = 0;
680
681 /* Number of "L" suffixes encountered. */
682 int long_p = 0;
683
684 /* We have found a "L" or "U" suffix. */
685 int found_suffix = 0;
686
687 ULONGEST high_bit;
688 struct type *signed_type;
689 struct type *unsigned_type;
690
691 if (parsed_float)
692 {
693 /* It's a float since it contains a point or an exponent. */
694 char c;
695 int num = 0; /* number of tokens scanned by scanf */
696 char saved_char = p[len];
697
698 p[len] = 0; /* null-terminate the token */
699 if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
700 num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
701 else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
702 num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
703 else
704 {
705 #ifdef SCANF_HAS_LONG_DOUBLE
706 num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
707 #else
708 /* Scan it into a double, then assign it to the long double.
709 This at least wins with values representable in the range
710 of doubles. */
711 double temp;
712 num = sscanf (p, "%lg%c", &temp,&c);
713 putithere->typed_val_float.dval = temp;
714 #endif
715 }
716 p[len] = saved_char; /* restore the input stream */
717 if (num != 1) /* check scanf found ONLY a float ... */
718 return ERROR;
719 /* See if it has `f' or `l' suffix (float or long double). */
720
721 c = tolower (p[len - 1]);
722
723 if (c == 'f')
724 putithere->typed_val_float.type = builtin_type_float;
725 else if (c == 'l')
726 putithere->typed_val_float.type = builtin_type_long_double;
727 else if (isdigit (c) || c == '.')
728 putithere->typed_val_float.type = builtin_type_double;
729 else
730 return ERROR;
731
732 return FLOAT;
733 }
734
735 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
736 if (p[0] == '0')
737 switch (p[1])
738 {
739 case 'x':
740 case 'X':
741 if (len >= 3)
742 {
743 p += 2;
744 base = 16;
745 len -= 2;
746 }
747 break;
748
749 case 't':
750 case 'T':
751 case 'd':
752 case 'D':
753 if (len >= 3)
754 {
755 p += 2;
756 base = 10;
757 len -= 2;
758 }
759 break;
760
761 default:
762 base = 8;
763 break;
764 }
765
766 while (len-- > 0)
767 {
768 c = *p++;
769 if (c >= 'A' && c <= 'Z')
770 c += 'a' - 'A';
771 if (c != 'l' && c != 'u')
772 n *= base;
773 if (c >= '0' && c <= '9')
774 {
775 if (found_suffix)
776 return ERROR;
777 n += i = c - '0';
778 }
779 else
780 {
781 if (base > 10 && c >= 'a' && c <= 'f')
782 {
783 if (found_suffix)
784 return ERROR;
785 n += i = c - 'a' + 10;
786 }
787 else if (c == 'l')
788 {
789 ++long_p;
790 found_suffix = 1;
791 }
792 else if (c == 'u')
793 {
794 unsigned_p = 1;
795 found_suffix = 1;
796 }
797 else
798 return ERROR; /* Char not a digit */
799 }
800 if (i >= base)
801 return ERROR; /* Invalid digit in this base */
802
803 /* Portably test for overflow (only works for nonzero values, so make
804 a second check for zero). FIXME: Can't we just make n and prevn
805 unsigned and avoid this? */
806 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
807 unsigned_p = 1; /* Try something unsigned */
808
809 /* Portably test for unsigned overflow.
810 FIXME: This check is wrong; for example it doesn't find overflow
811 on 0x123456789 when LONGEST is 32 bits. */
812 if (c != 'l' && c != 'u' && n != 0)
813 {
814 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
815 error ("Numeric constant too large.");
816 }
817 prevn = n;
818 }
819
820 /* An integer constant is an int, a long, or a long long. An L
821 suffix forces it to be long; an LL suffix forces it to be long
822 long. If not forced to a larger size, it gets the first type of
823 the above that it fits in. To figure out whether it fits, we
824 shift it right and see whether anything remains. Note that we
825 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
826 operation, because many compilers will warn about such a shift
827 (which always produces a zero result). Sometimes TARGET_INT_BIT
828 or TARGET_LONG_BIT will be that big, sometimes not. To deal with
829 the case where it is we just always shift the value more than
830 once, with fewer bits each time. */
831
832 un = (ULONGEST)n >> 2;
833 if (long_p == 0
834 && (un >> (TARGET_INT_BIT - 2)) == 0)
835 {
836 high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
837
838 /* A large decimal (not hex or octal) constant (between INT_MAX
839 and UINT_MAX) is a long or unsigned long, according to ANSI,
840 never an unsigned int, but this code treats it as unsigned
841 int. This probably should be fixed. GCC gives a warning on
842 such constants. */
843
844 unsigned_type = builtin_type_unsigned_int;
845 signed_type = builtin_type_int;
846 }
847 else if (long_p <= 1
848 && (un >> (TARGET_LONG_BIT - 2)) == 0)
849 {
850 high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
851 unsigned_type = builtin_type_unsigned_long;
852 signed_type = builtin_type_long;
853 }
854 else
855 {
856 high_bit = (((ULONGEST)1)
857 << (TARGET_LONG_LONG_BIT - 32 - 1)
858 << 16
859 << 16);
860 if (high_bit == 0)
861 /* A long long does not fit in a LONGEST. */
862 high_bit =
863 (ULONGEST)1 << (sizeof (LONGEST) * HOST_CHAR_BIT - 1);
864 unsigned_type = builtin_type_unsigned_long_long;
865 signed_type = builtin_type_long_long;
866 }
867
868 putithere->typed_val_int.val = n;
869
870 /* If the high bit of the worked out type is set then this number
871 has to be unsigned. */
872
873 if (unsigned_p || (n & high_bit))
874 {
875 putithere->typed_val_int.type = unsigned_type;
876 }
877 else
878 {
879 putithere->typed_val_int.type = signed_type;
880 }
881
882 return INT;
883 }
884
885 struct token
886 {
887 char *operator;
888 int token;
889 enum exp_opcode opcode;
890 };
891
892 static const struct token tokentab3[] =
893 {
894 {"shr", RSH, BINOP_END},
895 {"shl", LSH, BINOP_END},
896 {"and", ANDAND, BINOP_END},
897 {"div", DIV, BINOP_END},
898 {"not", NOT, BINOP_END},
899 {"mod", MOD, BINOP_END},
900 {"inc", INCREMENT, BINOP_END},
901 {"dec", DECREMENT, BINOP_END},
902 {"xor", XOR, BINOP_END}
903 };
904
905 static const struct token tokentab2[] =
906 {
907 {"or", OR, BINOP_END},
908 {"<>", NOTEQUAL, BINOP_END},
909 {"<=", LEQ, BINOP_END},
910 {">=", GEQ, BINOP_END},
911 {":=", ASSIGN, BINOP_END}
912 };
913
914 /* Allocate uppercased var */
915 /* make an uppercased copy of tokstart */
916 static char * uptok (tokstart, namelen)
917 char *tokstart;
918 int namelen;
919 {
920 int i;
921 char *uptokstart = (char *)malloc(namelen+1);
922 for (i = 0;i <= namelen;i++)
923 {
924 if ((tokstart[i]>='a' && tokstart[i]<='z'))
925 uptokstart[i] = tokstart[i]-('a'-'A');
926 else
927 uptokstart[i] = tokstart[i];
928 }
929 uptokstart[namelen]='\0';
930 return uptokstart;
931 }
932 /* Read one token, getting characters through lexptr. */
933
934
935 static int
936 yylex ()
937 {
938 int c;
939 int namelen;
940 unsigned int i;
941 char *tokstart;
942 char *uptokstart;
943 char *tokptr;
944 char *p;
945 int tempbufindex;
946 static char *tempbuf;
947 static int tempbufsize;
948
949 retry:
950
951 tokstart = lexptr;
952 /* See if it is a special token of length 3. */
953 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
954 if (STREQN (tokstart, tokentab3[i].operator, 3))
955 {
956 lexptr += 3;
957 yylval.opcode = tokentab3[i].opcode;
958 return tokentab3[i].token;
959 }
960
961 /* See if it is a special token of length 2. */
962 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
963 if (STREQN (tokstart, tokentab2[i].operator, 2))
964 {
965 lexptr += 2;
966 yylval.opcode = tokentab2[i].opcode;
967 return tokentab2[i].token;
968 }
969
970 switch (c = *tokstart)
971 {
972 case 0:
973 return 0;
974
975 case ' ':
976 case '\t':
977 case '\n':
978 lexptr++;
979 goto retry;
980
981 case '\'':
982 /* We either have a character constant ('0' or '\177' for example)
983 or we have a quoted symbol reference ('foo(int,int)' in object pascal
984 for example). */
985 lexptr++;
986 c = *lexptr++;
987 if (c == '\\')
988 c = parse_escape (&lexptr);
989 else if (c == '\'')
990 error ("Empty character constant.");
991
992 yylval.typed_val_int.val = c;
993 yylval.typed_val_int.type = builtin_type_char;
994
995 c = *lexptr++;
996 if (c != '\'')
997 {
998 namelen = skip_quoted (tokstart) - tokstart;
999 if (namelen > 2)
1000 {
1001 lexptr = tokstart + namelen;
1002 if (lexptr[-1] != '\'')
1003 error ("Unmatched single quote.");
1004 namelen -= 2;
1005 tokstart++;
1006 uptokstart = uptok(tokstart,namelen);
1007 goto tryname;
1008 }
1009 error ("Invalid character constant.");
1010 }
1011 return INT;
1012
1013 case '(':
1014 paren_depth++;
1015 lexptr++;
1016 return c;
1017
1018 case ')':
1019 if (paren_depth == 0)
1020 return 0;
1021 paren_depth--;
1022 lexptr++;
1023 return c;
1024
1025 case ',':
1026 if (comma_terminates && paren_depth == 0)
1027 return 0;
1028 lexptr++;
1029 return c;
1030
1031 case '.':
1032 /* Might be a floating point number. */
1033 if (lexptr[1] < '0' || lexptr[1] > '9')
1034 goto symbol; /* Nope, must be a symbol. */
1035 /* FALL THRU into number case. */
1036
1037 case '0':
1038 case '1':
1039 case '2':
1040 case '3':
1041 case '4':
1042 case '5':
1043 case '6':
1044 case '7':
1045 case '8':
1046 case '9':
1047 {
1048 /* It's a number. */
1049 int got_dot = 0, got_e = 0, toktype;
1050 register char *p = tokstart;
1051 int hex = input_radix > 10;
1052
1053 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1054 {
1055 p += 2;
1056 hex = 1;
1057 }
1058 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1059 {
1060 p += 2;
1061 hex = 0;
1062 }
1063
1064 for (;; ++p)
1065 {
1066 /* This test includes !hex because 'e' is a valid hex digit
1067 and thus does not indicate a floating point number when
1068 the radix is hex. */
1069 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1070 got_dot = got_e = 1;
1071 /* This test does not include !hex, because a '.' always indicates
1072 a decimal floating point number regardless of the radix. */
1073 else if (!got_dot && *p == '.')
1074 got_dot = 1;
1075 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1076 && (*p == '-' || *p == '+'))
1077 /* This is the sign of the exponent, not the end of the
1078 number. */
1079 continue;
1080 /* We will take any letters or digits. parse_number will
1081 complain if past the radix, or if L or U are not final. */
1082 else if ((*p < '0' || *p > '9')
1083 && ((*p < 'a' || *p > 'z')
1084 && (*p < 'A' || *p > 'Z')))
1085 break;
1086 }
1087 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1088 if (toktype == ERROR)
1089 {
1090 char *err_copy = (char *) alloca (p - tokstart + 1);
1091
1092 memcpy (err_copy, tokstart, p - tokstart);
1093 err_copy[p - tokstart] = 0;
1094 error ("Invalid number \"%s\".", err_copy);
1095 }
1096 lexptr = p;
1097 return toktype;
1098 }
1099
1100 case '+':
1101 case '-':
1102 case '*':
1103 case '/':
1104 case '|':
1105 case '&':
1106 case '^':
1107 case '~':
1108 case '!':
1109 case '@':
1110 case '<':
1111 case '>':
1112 case '[':
1113 case ']':
1114 case '?':
1115 case ':':
1116 case '=':
1117 case '{':
1118 case '}':
1119 symbol:
1120 lexptr++;
1121 return c;
1122
1123 case '"':
1124
1125 /* Build the gdb internal form of the input string in tempbuf,
1126 translating any standard C escape forms seen. Note that the
1127 buffer is null byte terminated *only* for the convenience of
1128 debugging gdb itself and printing the buffer contents when
1129 the buffer contains no embedded nulls. Gdb does not depend
1130 upon the buffer being null byte terminated, it uses the length
1131 string instead. This allows gdb to handle C strings (as well
1132 as strings in other languages) with embedded null bytes */
1133
1134 tokptr = ++tokstart;
1135 tempbufindex = 0;
1136
1137 do {
1138 /* Grow the static temp buffer if necessary, including allocating
1139 the first one on demand. */
1140 if (tempbufindex + 1 >= tempbufsize)
1141 {
1142 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1143 }
1144 switch (*tokptr)
1145 {
1146 case '\0':
1147 case '"':
1148 /* Do nothing, loop will terminate. */
1149 break;
1150 case '\\':
1151 tokptr++;
1152 c = parse_escape (&tokptr);
1153 if (c == -1)
1154 {
1155 continue;
1156 }
1157 tempbuf[tempbufindex++] = c;
1158 break;
1159 default:
1160 tempbuf[tempbufindex++] = *tokptr++;
1161 break;
1162 }
1163 } while ((*tokptr != '"') && (*tokptr != '\0'));
1164 if (*tokptr++ != '"')
1165 {
1166 error ("Unterminated string in expression.");
1167 }
1168 tempbuf[tempbufindex] = '\0'; /* See note above */
1169 yylval.sval.ptr = tempbuf;
1170 yylval.sval.length = tempbufindex;
1171 lexptr = tokptr;
1172 return (STRING);
1173 }
1174
1175 if (!(c == '_' || c == '$'
1176 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1177 /* We must have come across a bad character (e.g. ';'). */
1178 error ("Invalid character '%c' in expression.", c);
1179
1180 /* It's a name. See how long it is. */
1181 namelen = 0;
1182 for (c = tokstart[namelen];
1183 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1184 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1185 {
1186 /* Template parameter lists are part of the name.
1187 FIXME: This mishandles `print $a<4&&$a>3'. */
1188 if (c == '<')
1189 {
1190 int i = namelen;
1191 int nesting_level = 1;
1192 while (tokstart[++i])
1193 {
1194 if (tokstart[i] == '<')
1195 nesting_level++;
1196 else if (tokstart[i] == '>')
1197 {
1198 if (--nesting_level == 0)
1199 break;
1200 }
1201 }
1202 if (tokstart[i] == '>')
1203 namelen = i;
1204 else
1205 break;
1206 }
1207
1208 /* do NOT uppercase internals because of registers !!! */
1209 c = tokstart[++namelen];
1210 }
1211
1212 uptokstart = uptok(tokstart,namelen);
1213
1214 /* The token "if" terminates the expression and is NOT
1215 removed from the input stream. */
1216 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1217 {
1218 return 0;
1219 }
1220
1221 lexptr += namelen;
1222
1223 tryname:
1224
1225 /* Catch specific keywords. Should be done with a data structure. */
1226 switch (namelen)
1227 {
1228 case 6:
1229 if (STREQ (uptokstart, "OBJECT"))
1230 return CLASS;
1231 if (STREQ (uptokstart, "RECORD"))
1232 return STRUCT;
1233 if (STREQ (uptokstart, "SIZEOF"))
1234 return SIZEOF;
1235 break;
1236 case 5:
1237 if (STREQ (uptokstart, "CLASS"))
1238 return CLASS;
1239 if (STREQ (uptokstart, "FALSE"))
1240 {
1241 yylval.lval = 0;
1242 return FALSE;
1243 }
1244 break;
1245 case 4:
1246 if (STREQ (uptokstart, "TRUE"))
1247 {
1248 yylval.lval = 1;
1249 return TRUE;
1250 }
1251 if (STREQ (uptokstart, "SELF"))
1252 {
1253 /* here we search for 'this' like
1254 inserted in FPC stabs debug info */
1255 static const char this_name[] =
1256 { /* CPLUS_MARKER,*/ 't', 'h', 'i', 's', '\0' };
1257
1258 if (lookup_symbol (this_name, expression_context_block,
1259 VAR_NAMESPACE, (int *) NULL,
1260 (struct symtab **) NULL))
1261 return THIS;
1262 }
1263 break;
1264 default:
1265 break;
1266 }
1267
1268 yylval.sval.ptr = tokstart;
1269 yylval.sval.length = namelen;
1270
1271 if (*tokstart == '$')
1272 {
1273 /* $ is the normal prefix for pascal hexadecimal values
1274 but this conflicts with the GDB use for debugger variables
1275 so in expression to enter hexadecimal values
1276 we still need to use C syntax with 0xff */
1277 write_dollar_variable (yylval.sval);
1278 return VARIABLE;
1279 }
1280
1281 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1282 functions or symtabs. If this is not so, then ...
1283 Use token-type TYPENAME for symbols that happen to be defined
1284 currently as names of types; NAME for other symbols.
1285 The caller is not constrained to care about the distinction. */
1286 {
1287 char *tmp = copy_name (yylval.sval);
1288 struct symbol *sym;
1289 int is_a_field_of_this = 0;
1290 int hextype;
1291
1292 sym = lookup_symbol (tmp, expression_context_block,
1293 VAR_NAMESPACE,
1294 &is_a_field_of_this,
1295 (struct symtab **) NULL);
1296 /* second chance uppercased ! */
1297 if (!sym)
1298 {
1299 for (i = 0;i <= namelen;i++)
1300 {
1301 if ((tmp[i]>='a' && tmp[i]<='z'))
1302 tmp[i] -= ('a'-'A');
1303 /* I am not sure that copy_name gives excatly the same result ! */
1304 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1305 tokstart[i] -= ('a'-'A');
1306 }
1307 sym = lookup_symbol (tmp, expression_context_block,
1308 VAR_NAMESPACE,
1309 &is_a_field_of_this,
1310 (struct symtab **) NULL);
1311 }
1312 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1313 no psymtabs (coff, xcoff, or some future change to blow away the
1314 psymtabs once once symbols are read). */
1315 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1316 lookup_symtab (tmp))
1317 {
1318 yylval.ssym.sym = sym;
1319 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1320 return BLOCKNAME;
1321 }
1322 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1323 {
1324 #if 1
1325 /* Despite the following flaw, we need to keep this code enabled.
1326 Because we can get called from check_stub_method, if we don't
1327 handle nested types then it screws many operations in any
1328 program which uses nested types. */
1329 /* In "A::x", if x is a member function of A and there happens
1330 to be a type (nested or not, since the stabs don't make that
1331 distinction) named x, then this code incorrectly thinks we
1332 are dealing with nested types rather than a member function. */
1333
1334 char *p;
1335 char *namestart;
1336 struct symbol *best_sym;
1337
1338 /* Look ahead to detect nested types. This probably should be
1339 done in the grammar, but trying seemed to introduce a lot
1340 of shift/reduce and reduce/reduce conflicts. It's possible
1341 that it could be done, though. Or perhaps a non-grammar, but
1342 less ad hoc, approach would work well. */
1343
1344 /* Since we do not currently have any way of distinguishing
1345 a nested type from a non-nested one (the stabs don't tell
1346 us whether a type is nested), we just ignore the
1347 containing type. */
1348
1349 p = lexptr;
1350 best_sym = sym;
1351 while (1)
1352 {
1353 /* Skip whitespace. */
1354 while (*p == ' ' || *p == '\t' || *p == '\n')
1355 ++p;
1356 if (*p == ':' && p[1] == ':')
1357 {
1358 /* Skip the `::'. */
1359 p += 2;
1360 /* Skip whitespace. */
1361 while (*p == ' ' || *p == '\t' || *p == '\n')
1362 ++p;
1363 namestart = p;
1364 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1365 || (*p >= 'a' && *p <= 'z')
1366 || (*p >= 'A' && *p <= 'Z'))
1367 ++p;
1368 if (p != namestart)
1369 {
1370 struct symbol *cur_sym;
1371 /* As big as the whole rest of the expression, which is
1372 at least big enough. */
1373 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1374 char *tmp1;
1375
1376 tmp1 = ncopy;
1377 memcpy (tmp1, tmp, strlen (tmp));
1378 tmp1 += strlen (tmp);
1379 memcpy (tmp1, "::", 2);
1380 tmp1 += 2;
1381 memcpy (tmp1, namestart, p - namestart);
1382 tmp1[p - namestart] = '\0';
1383 cur_sym = lookup_symbol (ncopy, expression_context_block,
1384 VAR_NAMESPACE, (int *) NULL,
1385 (struct symtab **) NULL);
1386 if (cur_sym)
1387 {
1388 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1389 {
1390 best_sym = cur_sym;
1391 lexptr = p;
1392 }
1393 else
1394 break;
1395 }
1396 else
1397 break;
1398 }
1399 else
1400 break;
1401 }
1402 else
1403 break;
1404 }
1405
1406 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1407 #else /* not 0 */
1408 yylval.tsym.type = SYMBOL_TYPE (sym);
1409 #endif /* not 0 */
1410 return TYPENAME;
1411 }
1412 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1413 return TYPENAME;
1414
1415 /* Input names that aren't symbols but ARE valid hex numbers,
1416 when the input radix permits them, can be names or numbers
1417 depending on the parse. Note we support radixes > 16 here. */
1418 if (!sym &&
1419 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1420 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1421 {
1422 YYSTYPE newlval; /* Its value is ignored. */
1423 hextype = parse_number (tokstart, namelen, 0, &newlval);
1424 if (hextype == INT)
1425 {
1426 yylval.ssym.sym = sym;
1427 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1428 return NAME_OR_INT;
1429 }
1430 }
1431
1432 free(uptokstart);
1433 /* Any other kind of symbol */
1434 yylval.ssym.sym = sym;
1435 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1436 return NAME;
1437 }
1438 }
1439
1440 void
1441 yyerror (msg)
1442 char *msg;
1443 {
1444 error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);
1445 }
1446