xref: /dflybsd-src/contrib/gdb-7/gdb/m2-lang.c (revision 5796c8dc12c637f18a1740c26afd8d40ffa9b719)
1*5796c8dcSSimon Schubert /* Modula 2 language support routines for GDB, the GNU debugger.
2*5796c8dcSSimon Schubert 
3*5796c8dcSSimon Schubert    Copyright (C) 1992, 1993, 1994, 1995, 1996, 1998, 2000, 2002, 2003, 2004,
4*5796c8dcSSimon Schubert    2005, 2007, 2008, 2009 Free Software Foundation, Inc.
5*5796c8dcSSimon Schubert 
6*5796c8dcSSimon Schubert    This file is part of GDB.
7*5796c8dcSSimon Schubert 
8*5796c8dcSSimon Schubert    This program is free software; you can redistribute it and/or modify
9*5796c8dcSSimon Schubert    it under the terms of the GNU General Public License as published by
10*5796c8dcSSimon Schubert    the Free Software Foundation; either version 3 of the License, or
11*5796c8dcSSimon Schubert    (at your option) any later version.
12*5796c8dcSSimon Schubert 
13*5796c8dcSSimon Schubert    This program is distributed in the hope that it will be useful,
14*5796c8dcSSimon Schubert    but WITHOUT ANY WARRANTY; without even the implied warranty of
15*5796c8dcSSimon Schubert    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16*5796c8dcSSimon Schubert    GNU General Public License for more details.
17*5796c8dcSSimon Schubert 
18*5796c8dcSSimon Schubert    You should have received a copy of the GNU General Public License
19*5796c8dcSSimon Schubert    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
20*5796c8dcSSimon Schubert 
21*5796c8dcSSimon Schubert #include "defs.h"
22*5796c8dcSSimon Schubert #include "symtab.h"
23*5796c8dcSSimon Schubert #include "gdbtypes.h"
24*5796c8dcSSimon Schubert #include "expression.h"
25*5796c8dcSSimon Schubert #include "parser-defs.h"
26*5796c8dcSSimon Schubert #include "language.h"
27*5796c8dcSSimon Schubert #include "m2-lang.h"
28*5796c8dcSSimon Schubert #include "c-lang.h"
29*5796c8dcSSimon Schubert #include "valprint.h"
30*5796c8dcSSimon Schubert 
31*5796c8dcSSimon Schubert extern void _initialize_m2_language (void);
32*5796c8dcSSimon Schubert static void m2_printchar (int, struct type *, struct ui_file *);
33*5796c8dcSSimon Schubert static void m2_emit_char (int, struct type *, struct ui_file *, int);
34*5796c8dcSSimon Schubert 
35*5796c8dcSSimon Schubert /* Print the character C on STREAM as part of the contents of a literal
36*5796c8dcSSimon Schubert    string whose delimiter is QUOTER.  Note that that format for printing
37*5796c8dcSSimon Schubert    characters and strings is language specific.
38*5796c8dcSSimon Schubert    FIXME:  This is a copy of the same function from c-exp.y.  It should
39*5796c8dcSSimon Schubert    be replaced with a true Modula version.  */
40*5796c8dcSSimon Schubert 
41*5796c8dcSSimon Schubert static void
42*5796c8dcSSimon Schubert m2_emit_char (int c, struct type *type, struct ui_file *stream, int quoter)
43*5796c8dcSSimon Schubert {
44*5796c8dcSSimon Schubert 
45*5796c8dcSSimon Schubert   c &= 0xFF;			/* Avoid sign bit follies */
46*5796c8dcSSimon Schubert 
47*5796c8dcSSimon Schubert   if (PRINT_LITERAL_FORM (c))
48*5796c8dcSSimon Schubert     {
49*5796c8dcSSimon Schubert       if (c == '\\' || c == quoter)
50*5796c8dcSSimon Schubert 	{
51*5796c8dcSSimon Schubert 	  fputs_filtered ("\\", stream);
52*5796c8dcSSimon Schubert 	}
53*5796c8dcSSimon Schubert       fprintf_filtered (stream, "%c", c);
54*5796c8dcSSimon Schubert     }
55*5796c8dcSSimon Schubert   else
56*5796c8dcSSimon Schubert     {
57*5796c8dcSSimon Schubert       switch (c)
58*5796c8dcSSimon Schubert 	{
59*5796c8dcSSimon Schubert 	case '\n':
60*5796c8dcSSimon Schubert 	  fputs_filtered ("\\n", stream);
61*5796c8dcSSimon Schubert 	  break;
62*5796c8dcSSimon Schubert 	case '\b':
63*5796c8dcSSimon Schubert 	  fputs_filtered ("\\b", stream);
64*5796c8dcSSimon Schubert 	  break;
65*5796c8dcSSimon Schubert 	case '\t':
66*5796c8dcSSimon Schubert 	  fputs_filtered ("\\t", stream);
67*5796c8dcSSimon Schubert 	  break;
68*5796c8dcSSimon Schubert 	case '\f':
69*5796c8dcSSimon Schubert 	  fputs_filtered ("\\f", stream);
70*5796c8dcSSimon Schubert 	  break;
71*5796c8dcSSimon Schubert 	case '\r':
72*5796c8dcSSimon Schubert 	  fputs_filtered ("\\r", stream);
73*5796c8dcSSimon Schubert 	  break;
74*5796c8dcSSimon Schubert 	case '\033':
75*5796c8dcSSimon Schubert 	  fputs_filtered ("\\e", stream);
76*5796c8dcSSimon Schubert 	  break;
77*5796c8dcSSimon Schubert 	case '\007':
78*5796c8dcSSimon Schubert 	  fputs_filtered ("\\a", stream);
79*5796c8dcSSimon Schubert 	  break;
80*5796c8dcSSimon Schubert 	default:
81*5796c8dcSSimon Schubert 	  fprintf_filtered (stream, "\\%.3o", (unsigned int) c);
82*5796c8dcSSimon Schubert 	  break;
83*5796c8dcSSimon Schubert 	}
84*5796c8dcSSimon Schubert     }
85*5796c8dcSSimon Schubert }
86*5796c8dcSSimon Schubert 
87*5796c8dcSSimon Schubert /* FIXME:  This is a copy of the same function from c-exp.y.  It should
88*5796c8dcSSimon Schubert    be replaced with a true Modula version.  */
89*5796c8dcSSimon Schubert 
90*5796c8dcSSimon Schubert static void
91*5796c8dcSSimon Schubert m2_printchar (int c, struct type *type, struct ui_file *stream)
92*5796c8dcSSimon Schubert {
93*5796c8dcSSimon Schubert   fputs_filtered ("'", stream);
94*5796c8dcSSimon Schubert   LA_EMIT_CHAR (c, type, stream, '\'');
95*5796c8dcSSimon Schubert   fputs_filtered ("'", stream);
96*5796c8dcSSimon Schubert }
97*5796c8dcSSimon Schubert 
98*5796c8dcSSimon Schubert /* Print the character string STRING, printing at most LENGTH characters.
99*5796c8dcSSimon Schubert    Printing stops early if the number hits print_max; repeat counts
100*5796c8dcSSimon Schubert    are printed as appropriate.  Print ellipses at the end if we
101*5796c8dcSSimon Schubert    had to stop before printing LENGTH characters, or if FORCE_ELLIPSES.
102*5796c8dcSSimon Schubert    FIXME:  This is a copy of the same function from c-exp.y.  It should
103*5796c8dcSSimon Schubert    be replaced with a true Modula version.  */
104*5796c8dcSSimon Schubert 
105*5796c8dcSSimon Schubert static void
106*5796c8dcSSimon Schubert m2_printstr (struct ui_file *stream, struct type *type, const gdb_byte *string,
107*5796c8dcSSimon Schubert 	     unsigned int length, int force_ellipses,
108*5796c8dcSSimon Schubert 	     const struct value_print_options *options)
109*5796c8dcSSimon Schubert {
110*5796c8dcSSimon Schubert   unsigned int i;
111*5796c8dcSSimon Schubert   unsigned int things_printed = 0;
112*5796c8dcSSimon Schubert   int in_quotes = 0;
113*5796c8dcSSimon Schubert   int need_comma = 0;
114*5796c8dcSSimon Schubert   int width = TYPE_LENGTH (type);
115*5796c8dcSSimon Schubert 
116*5796c8dcSSimon Schubert   if (length == 0)
117*5796c8dcSSimon Schubert     {
118*5796c8dcSSimon Schubert       fputs_filtered ("\"\"", gdb_stdout);
119*5796c8dcSSimon Schubert       return;
120*5796c8dcSSimon Schubert     }
121*5796c8dcSSimon Schubert 
122*5796c8dcSSimon Schubert   for (i = 0; i < length && things_printed < options->print_max; ++i)
123*5796c8dcSSimon Schubert     {
124*5796c8dcSSimon Schubert       /* Position of the character we are examining
125*5796c8dcSSimon Schubert          to see whether it is repeated.  */
126*5796c8dcSSimon Schubert       unsigned int rep1;
127*5796c8dcSSimon Schubert       /* Number of repetitions we have detected so far.  */
128*5796c8dcSSimon Schubert       unsigned int reps;
129*5796c8dcSSimon Schubert 
130*5796c8dcSSimon Schubert       QUIT;
131*5796c8dcSSimon Schubert 
132*5796c8dcSSimon Schubert       if (need_comma)
133*5796c8dcSSimon Schubert 	{
134*5796c8dcSSimon Schubert 	  fputs_filtered (", ", stream);
135*5796c8dcSSimon Schubert 	  need_comma = 0;
136*5796c8dcSSimon Schubert 	}
137*5796c8dcSSimon Schubert 
138*5796c8dcSSimon Schubert       rep1 = i + 1;
139*5796c8dcSSimon Schubert       reps = 1;
140*5796c8dcSSimon Schubert       while (rep1 < length && string[rep1] == string[i])
141*5796c8dcSSimon Schubert 	{
142*5796c8dcSSimon Schubert 	  ++rep1;
143*5796c8dcSSimon Schubert 	  ++reps;
144*5796c8dcSSimon Schubert 	}
145*5796c8dcSSimon Schubert 
146*5796c8dcSSimon Schubert       if (reps > options->repeat_count_threshold)
147*5796c8dcSSimon Schubert 	{
148*5796c8dcSSimon Schubert 	  if (in_quotes)
149*5796c8dcSSimon Schubert 	    {
150*5796c8dcSSimon Schubert 	      if (options->inspect_it)
151*5796c8dcSSimon Schubert 		fputs_filtered ("\\\", ", stream);
152*5796c8dcSSimon Schubert 	      else
153*5796c8dcSSimon Schubert 		fputs_filtered ("\", ", stream);
154*5796c8dcSSimon Schubert 	      in_quotes = 0;
155*5796c8dcSSimon Schubert 	    }
156*5796c8dcSSimon Schubert 	  m2_printchar (string[i], type, stream);
157*5796c8dcSSimon Schubert 	  fprintf_filtered (stream, " <repeats %u times>", reps);
158*5796c8dcSSimon Schubert 	  i = rep1 - 1;
159*5796c8dcSSimon Schubert 	  things_printed += options->repeat_count_threshold;
160*5796c8dcSSimon Schubert 	  need_comma = 1;
161*5796c8dcSSimon Schubert 	}
162*5796c8dcSSimon Schubert       else
163*5796c8dcSSimon Schubert 	{
164*5796c8dcSSimon Schubert 	  if (!in_quotes)
165*5796c8dcSSimon Schubert 	    {
166*5796c8dcSSimon Schubert 	      if (options->inspect_it)
167*5796c8dcSSimon Schubert 		fputs_filtered ("\\\"", stream);
168*5796c8dcSSimon Schubert 	      else
169*5796c8dcSSimon Schubert 		fputs_filtered ("\"", stream);
170*5796c8dcSSimon Schubert 	      in_quotes = 1;
171*5796c8dcSSimon Schubert 	    }
172*5796c8dcSSimon Schubert 	  LA_EMIT_CHAR (string[i], type, stream, '"');
173*5796c8dcSSimon Schubert 	  ++things_printed;
174*5796c8dcSSimon Schubert 	}
175*5796c8dcSSimon Schubert     }
176*5796c8dcSSimon Schubert 
177*5796c8dcSSimon Schubert   /* Terminate the quotes if necessary.  */
178*5796c8dcSSimon Schubert   if (in_quotes)
179*5796c8dcSSimon Schubert     {
180*5796c8dcSSimon Schubert       if (options->inspect_it)
181*5796c8dcSSimon Schubert 	fputs_filtered ("\\\"", stream);
182*5796c8dcSSimon Schubert       else
183*5796c8dcSSimon Schubert 	fputs_filtered ("\"", stream);
184*5796c8dcSSimon Schubert     }
185*5796c8dcSSimon Schubert 
186*5796c8dcSSimon Schubert   if (force_ellipses || i < length)
187*5796c8dcSSimon Schubert     fputs_filtered ("...", stream);
188*5796c8dcSSimon Schubert }
189*5796c8dcSSimon Schubert 
190*5796c8dcSSimon Schubert static struct value *
191*5796c8dcSSimon Schubert evaluate_subexp_modula2 (struct type *expect_type, struct expression *exp,
192*5796c8dcSSimon Schubert 			 int *pos, enum noside noside)
193*5796c8dcSSimon Schubert {
194*5796c8dcSSimon Schubert   enum exp_opcode op = exp->elts[*pos].opcode;
195*5796c8dcSSimon Schubert   struct value *arg1;
196*5796c8dcSSimon Schubert   struct value *arg2;
197*5796c8dcSSimon Schubert   struct type *type;
198*5796c8dcSSimon Schubert   switch (op)
199*5796c8dcSSimon Schubert     {
200*5796c8dcSSimon Schubert     case UNOP_HIGH:
201*5796c8dcSSimon Schubert       (*pos)++;
202*5796c8dcSSimon Schubert       arg1 = evaluate_subexp_with_coercion (exp, pos, noside);
203*5796c8dcSSimon Schubert 
204*5796c8dcSSimon Schubert       if (noside == EVAL_SKIP || noside == EVAL_AVOID_SIDE_EFFECTS)
205*5796c8dcSSimon Schubert 	return arg1;
206*5796c8dcSSimon Schubert       else
207*5796c8dcSSimon Schubert 	{
208*5796c8dcSSimon Schubert 	  arg1 = coerce_ref (arg1);
209*5796c8dcSSimon Schubert 	  type = check_typedef (value_type (arg1));
210*5796c8dcSSimon Schubert 
211*5796c8dcSSimon Schubert 	  if (m2_is_unbounded_array (type))
212*5796c8dcSSimon Schubert 	    {
213*5796c8dcSSimon Schubert 	      struct value *temp = arg1;
214*5796c8dcSSimon Schubert 	      type = TYPE_FIELD_TYPE (type, 1);
215*5796c8dcSSimon Schubert 	      /* i18n: Do not translate the "_m2_high" part!  */
216*5796c8dcSSimon Schubert 	      arg1 = value_struct_elt (&temp, NULL, "_m2_high", NULL,
217*5796c8dcSSimon Schubert 				       _("unbounded structure "
218*5796c8dcSSimon Schubert 					 "missing _m2_high field"));
219*5796c8dcSSimon Schubert 
220*5796c8dcSSimon Schubert 	      if (value_type (arg1) != type)
221*5796c8dcSSimon Schubert 		arg1 = value_cast (type, arg1);
222*5796c8dcSSimon Schubert 	    }
223*5796c8dcSSimon Schubert 	}
224*5796c8dcSSimon Schubert       return arg1;
225*5796c8dcSSimon Schubert 
226*5796c8dcSSimon Schubert     case BINOP_SUBSCRIPT:
227*5796c8dcSSimon Schubert       (*pos)++;
228*5796c8dcSSimon Schubert       arg1 = evaluate_subexp_with_coercion (exp, pos, noside);
229*5796c8dcSSimon Schubert       arg2 = evaluate_subexp_with_coercion (exp, pos, noside);
230*5796c8dcSSimon Schubert       if (noside == EVAL_SKIP)
231*5796c8dcSSimon Schubert 	goto nosideret;
232*5796c8dcSSimon Schubert       /* If the user attempts to subscript something that is not an
233*5796c8dcSSimon Schubert          array or pointer type (like a plain int variable for example),
234*5796c8dcSSimon Schubert          then report this as an error.  */
235*5796c8dcSSimon Schubert 
236*5796c8dcSSimon Schubert       arg1 = coerce_ref (arg1);
237*5796c8dcSSimon Schubert       type = check_typedef (value_type (arg1));
238*5796c8dcSSimon Schubert 
239*5796c8dcSSimon Schubert       if (m2_is_unbounded_array (type))
240*5796c8dcSSimon Schubert 	{
241*5796c8dcSSimon Schubert 	  struct value *temp = arg1;
242*5796c8dcSSimon Schubert 	  type = TYPE_FIELD_TYPE (type, 0);
243*5796c8dcSSimon Schubert 	  if (type == NULL || (TYPE_CODE (type) != TYPE_CODE_PTR)) {
244*5796c8dcSSimon Schubert 	    warning (_("internal error: unbounded array structure is unknown"));
245*5796c8dcSSimon Schubert 	    return evaluate_subexp_standard (expect_type, exp, pos, noside);
246*5796c8dcSSimon Schubert 	  }
247*5796c8dcSSimon Schubert 	  /* i18n: Do not translate the "_m2_contents" part!  */
248*5796c8dcSSimon Schubert 	  arg1 = value_struct_elt (&temp, NULL, "_m2_contents", NULL,
249*5796c8dcSSimon Schubert 				   _("unbounded structure "
250*5796c8dcSSimon Schubert 				     "missing _m2_contents field"));
251*5796c8dcSSimon Schubert 
252*5796c8dcSSimon Schubert 	  if (value_type (arg1) != type)
253*5796c8dcSSimon Schubert 	    arg1 = value_cast (type, arg1);
254*5796c8dcSSimon Schubert 
255*5796c8dcSSimon Schubert 	  type = check_typedef (value_type (arg1));
256*5796c8dcSSimon Schubert 	  return value_ind (value_ptradd (arg1, value_as_long (arg2)));
257*5796c8dcSSimon Schubert 	}
258*5796c8dcSSimon Schubert       else
259*5796c8dcSSimon Schubert 	if (TYPE_CODE (type) != TYPE_CODE_ARRAY)
260*5796c8dcSSimon Schubert 	  {
261*5796c8dcSSimon Schubert 	    if (TYPE_NAME (type))
262*5796c8dcSSimon Schubert 	      error (_("cannot subscript something of type `%s'"),
263*5796c8dcSSimon Schubert 		     TYPE_NAME (type));
264*5796c8dcSSimon Schubert 	    else
265*5796c8dcSSimon Schubert 	      error (_("cannot subscript requested type"));
266*5796c8dcSSimon Schubert 	  }
267*5796c8dcSSimon Schubert 
268*5796c8dcSSimon Schubert       if (noside == EVAL_AVOID_SIDE_EFFECTS)
269*5796c8dcSSimon Schubert 	return value_zero (TYPE_TARGET_TYPE (type), VALUE_LVAL (arg1));
270*5796c8dcSSimon Schubert       else
271*5796c8dcSSimon Schubert 	return value_subscript (arg1, value_as_long (arg2));
272*5796c8dcSSimon Schubert 
273*5796c8dcSSimon Schubert     default:
274*5796c8dcSSimon Schubert       return evaluate_subexp_standard (expect_type, exp, pos, noside);
275*5796c8dcSSimon Schubert     }
276*5796c8dcSSimon Schubert 
277*5796c8dcSSimon Schubert  nosideret:
278*5796c8dcSSimon Schubert   return value_from_longest (builtin_type (exp->gdbarch)->builtin_int, 1);
279*5796c8dcSSimon Schubert }
280*5796c8dcSSimon Schubert 
281*5796c8dcSSimon Schubert 
282*5796c8dcSSimon Schubert /* Table of operators and their precedences for printing expressions.  */
283*5796c8dcSSimon Schubert 
284*5796c8dcSSimon Schubert static const struct op_print m2_op_print_tab[] =
285*5796c8dcSSimon Schubert {
286*5796c8dcSSimon Schubert   {"+", BINOP_ADD, PREC_ADD, 0},
287*5796c8dcSSimon Schubert   {"+", UNOP_PLUS, PREC_PREFIX, 0},
288*5796c8dcSSimon Schubert   {"-", BINOP_SUB, PREC_ADD, 0},
289*5796c8dcSSimon Schubert   {"-", UNOP_NEG, PREC_PREFIX, 0},
290*5796c8dcSSimon Schubert   {"*", BINOP_MUL, PREC_MUL, 0},
291*5796c8dcSSimon Schubert   {"/", BINOP_DIV, PREC_MUL, 0},
292*5796c8dcSSimon Schubert   {"DIV", BINOP_INTDIV, PREC_MUL, 0},
293*5796c8dcSSimon Schubert   {"MOD", BINOP_REM, PREC_MUL, 0},
294*5796c8dcSSimon Schubert   {":=", BINOP_ASSIGN, PREC_ASSIGN, 1},
295*5796c8dcSSimon Schubert   {"OR", BINOP_LOGICAL_OR, PREC_LOGICAL_OR, 0},
296*5796c8dcSSimon Schubert   {"AND", BINOP_LOGICAL_AND, PREC_LOGICAL_AND, 0},
297*5796c8dcSSimon Schubert   {"NOT", UNOP_LOGICAL_NOT, PREC_PREFIX, 0},
298*5796c8dcSSimon Schubert   {"=", BINOP_EQUAL, PREC_EQUAL, 0},
299*5796c8dcSSimon Schubert   {"<>", BINOP_NOTEQUAL, PREC_EQUAL, 0},
300*5796c8dcSSimon Schubert   {"<=", BINOP_LEQ, PREC_ORDER, 0},
301*5796c8dcSSimon Schubert   {">=", BINOP_GEQ, PREC_ORDER, 0},
302*5796c8dcSSimon Schubert   {">", BINOP_GTR, PREC_ORDER, 0},
303*5796c8dcSSimon Schubert   {"<", BINOP_LESS, PREC_ORDER, 0},
304*5796c8dcSSimon Schubert   {"^", UNOP_IND, PREC_PREFIX, 0},
305*5796c8dcSSimon Schubert   {"@", BINOP_REPEAT, PREC_REPEAT, 0},
306*5796c8dcSSimon Schubert   {"CAP", UNOP_CAP, PREC_BUILTIN_FUNCTION, 0},
307*5796c8dcSSimon Schubert   {"CHR", UNOP_CHR, PREC_BUILTIN_FUNCTION, 0},
308*5796c8dcSSimon Schubert   {"ORD", UNOP_ORD, PREC_BUILTIN_FUNCTION, 0},
309*5796c8dcSSimon Schubert   {"FLOAT", UNOP_FLOAT, PREC_BUILTIN_FUNCTION, 0},
310*5796c8dcSSimon Schubert   {"HIGH", UNOP_HIGH, PREC_BUILTIN_FUNCTION, 0},
311*5796c8dcSSimon Schubert   {"MAX", UNOP_MAX, PREC_BUILTIN_FUNCTION, 0},
312*5796c8dcSSimon Schubert   {"MIN", UNOP_MIN, PREC_BUILTIN_FUNCTION, 0},
313*5796c8dcSSimon Schubert   {"ODD", UNOP_ODD, PREC_BUILTIN_FUNCTION, 0},
314*5796c8dcSSimon Schubert   {"TRUNC", UNOP_TRUNC, PREC_BUILTIN_FUNCTION, 0},
315*5796c8dcSSimon Schubert   {NULL, 0, 0, 0}
316*5796c8dcSSimon Schubert };
317*5796c8dcSSimon Schubert 
318*5796c8dcSSimon Schubert /* The built-in types of Modula-2.  */
319*5796c8dcSSimon Schubert 
320*5796c8dcSSimon Schubert enum m2_primitive_types {
321*5796c8dcSSimon Schubert   m2_primitive_type_char,
322*5796c8dcSSimon Schubert   m2_primitive_type_int,
323*5796c8dcSSimon Schubert   m2_primitive_type_card,
324*5796c8dcSSimon Schubert   m2_primitive_type_real,
325*5796c8dcSSimon Schubert   m2_primitive_type_bool,
326*5796c8dcSSimon Schubert   nr_m2_primitive_types
327*5796c8dcSSimon Schubert };
328*5796c8dcSSimon Schubert 
329*5796c8dcSSimon Schubert static void
330*5796c8dcSSimon Schubert m2_language_arch_info (struct gdbarch *gdbarch,
331*5796c8dcSSimon Schubert 		       struct language_arch_info *lai)
332*5796c8dcSSimon Schubert {
333*5796c8dcSSimon Schubert   const struct builtin_m2_type *builtin = builtin_m2_type (gdbarch);
334*5796c8dcSSimon Schubert 
335*5796c8dcSSimon Schubert   lai->string_char_type = builtin->builtin_char;
336*5796c8dcSSimon Schubert   lai->primitive_type_vector
337*5796c8dcSSimon Schubert     = GDBARCH_OBSTACK_CALLOC (gdbarch, nr_m2_primitive_types + 1,
338*5796c8dcSSimon Schubert                               struct type *);
339*5796c8dcSSimon Schubert 
340*5796c8dcSSimon Schubert   lai->primitive_type_vector [m2_primitive_type_char]
341*5796c8dcSSimon Schubert     = builtin->builtin_char;
342*5796c8dcSSimon Schubert   lai->primitive_type_vector [m2_primitive_type_int]
343*5796c8dcSSimon Schubert     = builtin->builtin_int;
344*5796c8dcSSimon Schubert   lai->primitive_type_vector [m2_primitive_type_card]
345*5796c8dcSSimon Schubert     = builtin->builtin_card;
346*5796c8dcSSimon Schubert   lai->primitive_type_vector [m2_primitive_type_real]
347*5796c8dcSSimon Schubert     = builtin->builtin_real;
348*5796c8dcSSimon Schubert   lai->primitive_type_vector [m2_primitive_type_bool]
349*5796c8dcSSimon Schubert     = builtin->builtin_bool;
350*5796c8dcSSimon Schubert 
351*5796c8dcSSimon Schubert   lai->bool_type_symbol = "BOOLEAN";
352*5796c8dcSSimon Schubert   lai->bool_type_default = builtin->builtin_bool;
353*5796c8dcSSimon Schubert }
354*5796c8dcSSimon Schubert 
355*5796c8dcSSimon Schubert const struct exp_descriptor exp_descriptor_modula2 =
356*5796c8dcSSimon Schubert {
357*5796c8dcSSimon Schubert   print_subexp_standard,
358*5796c8dcSSimon Schubert   operator_length_standard,
359*5796c8dcSSimon Schubert   op_name_standard,
360*5796c8dcSSimon Schubert   dump_subexp_body_standard,
361*5796c8dcSSimon Schubert   evaluate_subexp_modula2
362*5796c8dcSSimon Schubert };
363*5796c8dcSSimon Schubert 
364*5796c8dcSSimon Schubert const struct language_defn m2_language_defn =
365*5796c8dcSSimon Schubert {
366*5796c8dcSSimon Schubert   "modula-2",
367*5796c8dcSSimon Schubert   language_m2,
368*5796c8dcSSimon Schubert   range_check_on,
369*5796c8dcSSimon Schubert   type_check_on,
370*5796c8dcSSimon Schubert   case_sensitive_on,
371*5796c8dcSSimon Schubert   array_row_major,
372*5796c8dcSSimon Schubert   macro_expansion_no,
373*5796c8dcSSimon Schubert   &exp_descriptor_modula2,
374*5796c8dcSSimon Schubert   m2_parse,			/* parser */
375*5796c8dcSSimon Schubert   m2_error,			/* parser error function */
376*5796c8dcSSimon Schubert   null_post_parser,
377*5796c8dcSSimon Schubert   m2_printchar,			/* Print character constant */
378*5796c8dcSSimon Schubert   m2_printstr,			/* function to print string constant */
379*5796c8dcSSimon Schubert   m2_emit_char,			/* Function to print a single character */
380*5796c8dcSSimon Schubert   m2_print_type,		/* Print a type using appropriate syntax */
381*5796c8dcSSimon Schubert   m2_print_typedef,		/* Print a typedef using appropriate syntax */
382*5796c8dcSSimon Schubert   m2_val_print,			/* Print a value using appropriate syntax */
383*5796c8dcSSimon Schubert   c_value_print,		/* Print a top-level value */
384*5796c8dcSSimon Schubert   NULL,				/* Language specific skip_trampoline */
385*5796c8dcSSimon Schubert   NULL,		                /* name_of_this */
386*5796c8dcSSimon Schubert   basic_lookup_symbol_nonlocal,	/* lookup_symbol_nonlocal */
387*5796c8dcSSimon Schubert   basic_lookup_transparent_type,/* lookup_transparent_type */
388*5796c8dcSSimon Schubert   NULL,				/* Language specific symbol demangler */
389*5796c8dcSSimon Schubert   NULL,				/* Language specific class_name_from_physname */
390*5796c8dcSSimon Schubert   m2_op_print_tab,		/* expression operators for printing */
391*5796c8dcSSimon Schubert   0,				/* arrays are first-class (not c-style) */
392*5796c8dcSSimon Schubert   0,				/* String lower bound */
393*5796c8dcSSimon Schubert   default_word_break_characters,
394*5796c8dcSSimon Schubert   default_make_symbol_completion_list,
395*5796c8dcSSimon Schubert   m2_language_arch_info,
396*5796c8dcSSimon Schubert   default_print_array_index,
397*5796c8dcSSimon Schubert   default_pass_by_reference,
398*5796c8dcSSimon Schubert   default_get_string,
399*5796c8dcSSimon Schubert   LANG_MAGIC
400*5796c8dcSSimon Schubert };
401*5796c8dcSSimon Schubert 
402*5796c8dcSSimon Schubert static void *
403*5796c8dcSSimon Schubert build_m2_types (struct gdbarch *gdbarch)
404*5796c8dcSSimon Schubert {
405*5796c8dcSSimon Schubert   struct builtin_m2_type *builtin_m2_type
406*5796c8dcSSimon Schubert     = GDBARCH_OBSTACK_ZALLOC (gdbarch, struct builtin_m2_type);
407*5796c8dcSSimon Schubert 
408*5796c8dcSSimon Schubert   /* Modula-2 "pervasive" types.  NOTE:  these can be redefined!!! */
409*5796c8dcSSimon Schubert   builtin_m2_type->builtin_int
410*5796c8dcSSimon Schubert     = arch_integer_type (gdbarch, gdbarch_int_bit (gdbarch), 0, "INTEGER");
411*5796c8dcSSimon Schubert   builtin_m2_type->builtin_card
412*5796c8dcSSimon Schubert     = arch_integer_type (gdbarch, gdbarch_int_bit (gdbarch), 1, "CARDINAL");
413*5796c8dcSSimon Schubert   builtin_m2_type->builtin_real
414*5796c8dcSSimon Schubert     = arch_float_type (gdbarch, gdbarch_float_bit (gdbarch), "REAL", NULL);
415*5796c8dcSSimon Schubert   builtin_m2_type->builtin_char
416*5796c8dcSSimon Schubert     = arch_character_type (gdbarch, TARGET_CHAR_BIT, 1, "CHAR");
417*5796c8dcSSimon Schubert   builtin_m2_type->builtin_bool
418*5796c8dcSSimon Schubert     = arch_boolean_type (gdbarch, gdbarch_int_bit (gdbarch), 1, "BOOLEAN");
419*5796c8dcSSimon Schubert 
420*5796c8dcSSimon Schubert   return builtin_m2_type;
421*5796c8dcSSimon Schubert }
422*5796c8dcSSimon Schubert 
423*5796c8dcSSimon Schubert static struct gdbarch_data *m2_type_data;
424*5796c8dcSSimon Schubert 
425*5796c8dcSSimon Schubert const struct builtin_m2_type *
426*5796c8dcSSimon Schubert builtin_m2_type (struct gdbarch *gdbarch)
427*5796c8dcSSimon Schubert {
428*5796c8dcSSimon Schubert   return gdbarch_data (gdbarch, m2_type_data);
429*5796c8dcSSimon Schubert }
430*5796c8dcSSimon Schubert 
431*5796c8dcSSimon Schubert 
432*5796c8dcSSimon Schubert /* Initialization for Modula-2 */
433*5796c8dcSSimon Schubert 
434*5796c8dcSSimon Schubert void
435*5796c8dcSSimon Schubert _initialize_m2_language (void)
436*5796c8dcSSimon Schubert {
437*5796c8dcSSimon Schubert   m2_type_data = gdbarch_data_register_post_init (build_m2_types);
438*5796c8dcSSimon Schubert 
439*5796c8dcSSimon Schubert   add_language (&m2_language_defn);
440*5796c8dcSSimon Schubert }
441