mep-tdep.c revision 1.8
1/* Target-dependent code for the Toshiba MeP for GDB, the GNU debugger.
2
3   Copyright (C) 2001-2019 Free Software Foundation, Inc.
4
5   Contributed by Red Hat, Inc.
6
7   This file is part of GDB.
8
9   This program is free software; you can redistribute it and/or modify
10   it under the terms of the GNU General Public License as published by
11   the Free Software Foundation; either version 3 of the License, or
12   (at your option) any later version.
13
14   This program is distributed in the hope that it will be useful,
15   but WITHOUT ANY WARRANTY; without even the implied warranty of
16   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17   GNU General Public License for more details.
18
19   You should have received a copy of the GNU General Public License
20   along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
21
22#include "defs.h"
23#include "frame.h"
24#include "frame-unwind.h"
25#include "frame-base.h"
26#include "symtab.h"
27#include "gdbtypes.h"
28#include "gdbcmd.h"
29#include "gdbcore.h"
30#include "value.h"
31#include "inferior.h"
32#include "dis-asm.h"
33#include "symfile.h"
34#include "objfiles.h"
35#include "language.h"
36#include "arch-utils.h"
37#include "regcache.h"
38#include "remote.h"
39#include "sim-regno.h"
40#include "disasm.h"
41#include "trad-frame.h"
42#include "reggroups.h"
43#include "elf-bfd.h"
44#include "elf/mep.h"
45#include "prologue-value.h"
46#include "cgen/bitset.h"
47#include "infcall.h"
48
49/* Get the user's customized MeP coprocessor register names from
50   libopcodes.  */
51#include "../opcodes/mep-desc.h"
52#include "../opcodes/mep-opc.h"
53
54
55/* The gdbarch_tdep structure.  */
56
57/* A quick recap for GDB hackers not familiar with the whole Toshiba
58   Media Processor story:
59
60   The MeP media engine is a configureable processor: users can design
61   their own coprocessors, implement custom instructions, adjust cache
62   sizes, select optional standard facilities like add-and-saturate
63   instructions, and so on.  Then, they can build custom versions of
64   the GNU toolchain to support their customized chips.  The
65   MeP-Integrator program (see utils/mep) takes a GNU toolchain source
66   tree, and a config file pointing to various files provided by the
67   user describing their customizations, and edits the source tree to
68   produce a compiler that can generate their custom instructions, an
69   assembler that can assemble them and recognize their custom
70   register names, and so on.
71
72   Furthermore, the user can actually specify several of these custom
73   configurations, called 'me_modules', and get a toolchain which can
74   produce code for any of them, given a compiler/assembler switch;
75   you say something like 'gcc -mconfig=mm_max' to generate code for
76   the me_module named 'mm_max'.
77
78   GDB, in particular, needs to:
79
80   - use the coprocessor control register names provided by the user
81     in their hardware description, in expressions, 'info register'
82     output, and disassembly,
83
84   - know the number, names, and types of the coprocessor's
85     general-purpose registers, adjust the 'info all-registers' output
86     accordingly, and print error messages if the user refers to one
87     that doesn't exist
88
89   - allow access to the control bus space only when the configuration
90     actually has a control bus, and recognize which regions of the
91     control bus space are actually populated,
92
93   - disassemble using the user's provided mnemonics for their custom
94     instructions, and
95
96   - recognize whether the $hi and $lo registers are present, and
97     allow access to them only when they are actually there.
98
99   There are three sources of information about what sort of me_module
100   we're actually dealing with:
101
102   - A MeP executable file indicates which me_module it was compiled
103     for, and libopcodes has tables describing each module.  So, given
104     an executable file, we can find out about the processor it was
105     compiled for.
106
107   - There are SID command-line options to select a particular
108     me_module, overriding the one specified in the ELF file.  SID
109     provides GDB with a fake read-only register, 'module', which
110     indicates which me_module GDB is communicating with an instance
111     of.
112
113   - There are SID command-line options to enable or disable certain
114     optional processor features, overriding the defaults for the
115     selected me_module.  The MeP $OPT register indicates which
116     options are present on the current processor.  */
117
118
119struct gdbarch_tdep
120{
121  /* A CGEN cpu descriptor for this BFD architecture and machine.
122
123     Note: this is *not* customized for any particular me_module; the
124     MeP libopcodes machinery actually puts off module-specific
125     customization until the last minute.  So this contains
126     information about all supported me_modules.  */
127  CGEN_CPU_DESC cpu_desc;
128
129  /* The me_module index from the ELF file we used to select this
130     architecture, or CONFIG_NONE if there was none.
131
132     Note that we should prefer to use the me_module number available
133     via the 'module' register, whenever we're actually talking to a
134     real target.
135
136     In the absence of live information, we'd like to get the
137     me_module number from the ELF file.  But which ELF file: the
138     executable file, the core file, ... ?  The answer is, "the last
139     ELF file we used to set the current architecture".  Thus, we
140     create a separate instance of the gdbarch structure for each
141     me_module value mep_gdbarch_init sees, and store the me_module
142     value from the ELF file here.  */
143  CONFIG_ATTR me_module;
144};
145
146
147
148/* Getting me_module information from the CGEN tables.  */
149
150
151/* Find an entry in the DESC's hardware table whose name begins with
152   PREFIX, and whose ISA mask intersects COPRO_ISA_MASK, but does not
153   intersect with GENERIC_ISA_MASK.  If there is no matching entry,
154   return zero.  */
155static const CGEN_HW_ENTRY *
156find_hw_entry_by_prefix_and_isa (CGEN_CPU_DESC desc,
157                                 const char *prefix,
158                                 CGEN_BITSET *copro_isa_mask,
159                                 CGEN_BITSET *generic_isa_mask)
160{
161  int prefix_len = strlen (prefix);
162  int i;
163
164  for (i = 0; i < desc->hw_table.num_entries; i++)
165    {
166      const CGEN_HW_ENTRY *hw = desc->hw_table.entries[i];
167      if (strncmp (prefix, hw->name, prefix_len) == 0)
168        {
169          CGEN_BITSET *hw_isa_mask
170            = ((CGEN_BITSET *)
171               &CGEN_ATTR_CGEN_HW_ISA_VALUE (CGEN_HW_ATTRS (hw)));
172
173          if (cgen_bitset_intersect_p (hw_isa_mask, copro_isa_mask)
174              && ! cgen_bitset_intersect_p (hw_isa_mask, generic_isa_mask))
175            return hw;
176        }
177    }
178
179  return 0;
180}
181
182
183/* Find an entry in DESC's hardware table whose type is TYPE.  Return
184   zero if there is none.  */
185static const CGEN_HW_ENTRY *
186find_hw_entry_by_type (CGEN_CPU_DESC desc, CGEN_HW_TYPE type)
187{
188  int i;
189
190  for (i = 0; i < desc->hw_table.num_entries; i++)
191    {
192      const CGEN_HW_ENTRY *hw = desc->hw_table.entries[i];
193
194      if (hw->type == type)
195        return hw;
196    }
197
198  return 0;
199}
200
201
202/* Return the CGEN hardware table entry for the coprocessor register
203   set for ME_MODULE, whose name prefix is PREFIX.  If ME_MODULE has
204   no such register set, return zero.  If ME_MODULE is the generic
205   me_module CONFIG_NONE, return the table entry for the register set
206   whose hardware type is GENERIC_TYPE.  */
207static const CGEN_HW_ENTRY *
208me_module_register_set (CONFIG_ATTR me_module,
209                        const char *prefix,
210                        CGEN_HW_TYPE generic_type)
211{
212  /* This is kind of tricky, because the hardware table is constructed
213     in a way that isn't very helpful.  Perhaps we can fix that, but
214     here's how it works at the moment:
215
216     The configuration map, `mep_config_map', is indexed by me_module
217     number, and indicates which coprocessor and core ISAs that
218     me_module supports.  The 'core_isa' mask includes all the core
219     ISAs, and the 'cop_isa' mask includes all the coprocessor ISAs.
220     The entry for the generic me_module, CONFIG_NONE, has an empty
221     'cop_isa', and its 'core_isa' selects only the standard MeP
222     instruction set.
223
224     The CGEN CPU descriptor's hardware table, desc->hw_table, has
225     entries for all the register sets, for all me_modules.  Each
226     entry has a mask indicating which ISAs use that register set.
227     So, if an me_module supports some coprocessor ISA, we can find
228     applicable register sets by scanning the hardware table for
229     register sets whose masks include (at least some of) those ISAs.
230
231     Each hardware table entry also has a name, whose prefix says
232     whether it's a general-purpose ("h-cr") or control ("h-ccr")
233     coprocessor register set.  It might be nicer to have an attribute
234     indicating what sort of register set it was, that we could use
235     instead of pattern-matching on the name.
236
237     When there is no hardware table entry whose mask includes a
238     particular coprocessor ISA and whose name starts with a given
239     prefix, then that means that that coprocessor doesn't have any
240     registers of that type.  In such cases, this function must return
241     a null pointer.
242
243     Coprocessor register sets' masks may or may not include the core
244     ISA for the me_module they belong to.  Those generated by a2cgen
245     do, but the sample me_module included in the unconfigured tree,
246     'ccfx', does not.
247
248     There are generic coprocessor register sets, intended only for
249     use with the generic me_module.  Unfortunately, their masks
250     include *all* ISAs --- even those for coprocessors that don't
251     have such register sets.  This makes detecting the case where a
252     coprocessor lacks a particular register set more complicated.
253
254     So, here's the approach we take:
255
256     - For CONFIG_NONE, we return the generic coprocessor register set.
257
258     - For any other me_module, we search for a register set whose
259       mask contains any of the me_module's coprocessor ISAs,
260       specifically excluding the generic coprocessor register sets.  */
261
262  CGEN_CPU_DESC desc = gdbarch_tdep (target_gdbarch ())->cpu_desc;
263  const CGEN_HW_ENTRY *hw;
264
265  if (me_module == CONFIG_NONE)
266    hw = find_hw_entry_by_type (desc, generic_type);
267  else
268    {
269      CGEN_BITSET *cop = &mep_config_map[me_module].cop_isa;
270      CGEN_BITSET *core = &mep_config_map[me_module].core_isa;
271      CGEN_BITSET *generic = &mep_config_map[CONFIG_NONE].core_isa;
272      CGEN_BITSET *cop_and_core;
273
274      /* The coprocessor ISAs include the ISA for the specific core which
275	 has that coprocessor.  */
276      cop_and_core = cgen_bitset_copy (cop);
277      cgen_bitset_union (cop, core, cop_and_core);
278      hw = find_hw_entry_by_prefix_and_isa (desc, prefix, cop_and_core, generic);
279    }
280
281  return hw;
282}
283
284
285/* Given a hardware table entry HW representing a register set, return
286   a pointer to the keyword table with all the register names.  If HW
287   is NULL, return NULL, to propage the "no such register set" info
288   along.  */
289static CGEN_KEYWORD *
290register_set_keyword_table (const CGEN_HW_ENTRY *hw)
291{
292  if (! hw)
293    return NULL;
294
295  /* Check that HW is actually a keyword table.  */
296  gdb_assert (hw->asm_type == CGEN_ASM_KEYWORD);
297
298  /* The 'asm_data' field of a register set's hardware table entry
299     refers to a keyword table.  */
300  return (CGEN_KEYWORD *) hw->asm_data;
301}
302
303
304/* Given a keyword table KEYWORD and a register number REGNUM, return
305   the name of the register, or "" if KEYWORD contains no register
306   whose number is REGNUM.  */
307static const char *
308register_name_from_keyword (CGEN_KEYWORD *keyword_table, int regnum)
309{
310  const CGEN_KEYWORD_ENTRY *entry
311    = cgen_keyword_lookup_value (keyword_table, regnum);
312
313  if (entry)
314    {
315      char *name = entry->name;
316
317      /* The CGEN keyword entries for register names include the
318         leading $, which appears in MeP assembly as well as in GDB.
319         But we don't want to return that; GDB core code adds that
320         itself.  */
321      if (name[0] == '$')
322        name++;
323
324      return name;
325    }
326  else
327    return "";
328}
329
330
331/* Masks for option bits in the OPT special-purpose register.  */
332enum {
333  MEP_OPT_DIV = 1 << 25,        /* 32-bit divide instruction option */
334  MEP_OPT_MUL = 1 << 24,        /* 32-bit multiply instruction option */
335  MEP_OPT_BIT = 1 << 23,        /* bit manipulation instruction option */
336  MEP_OPT_SAT = 1 << 22,        /* saturation instruction option */
337  MEP_OPT_CLP = 1 << 21,        /* clip instruction option */
338  MEP_OPT_MIN = 1 << 20,        /* min/max instruction option */
339  MEP_OPT_AVE = 1 << 19,        /* average instruction option */
340  MEP_OPT_ABS = 1 << 18,        /* absolute difference instruction option */
341  MEP_OPT_LDZ = 1 << 16,        /* leading zero instruction option */
342  MEP_OPT_VL64 = 1 << 6,        /* 64-bit VLIW operation mode option */
343  MEP_OPT_VL32 = 1 << 5,        /* 32-bit VLIW operation mode option */
344  MEP_OPT_COP = 1 << 4,         /* coprocessor option */
345  MEP_OPT_DSP = 1 << 2,         /* DSP option */
346  MEP_OPT_UCI = 1 << 1,         /* UCI option */
347  MEP_OPT_DBG = 1 << 0,         /* DBG function option */
348};
349
350
351/* Given the option_mask value for a particular entry in
352   mep_config_map, produce the value the processor's OPT register
353   would use to represent the same set of options.  */
354static unsigned int
355opt_from_option_mask (unsigned int option_mask)
356{
357  /* A table mapping OPT register bits onto CGEN config map option
358     bits.  */
359  struct {
360    unsigned int opt_bit, option_mask_bit;
361  } bits[] = {
362    { MEP_OPT_DIV, 1 << CGEN_INSN_OPTIONAL_DIV_INSN },
363    { MEP_OPT_MUL, 1 << CGEN_INSN_OPTIONAL_MUL_INSN },
364    { MEP_OPT_DIV, 1 << CGEN_INSN_OPTIONAL_DIV_INSN },
365    { MEP_OPT_DBG, 1 << CGEN_INSN_OPTIONAL_DEBUG_INSN },
366    { MEP_OPT_LDZ, 1 << CGEN_INSN_OPTIONAL_LDZ_INSN },
367    { MEP_OPT_ABS, 1 << CGEN_INSN_OPTIONAL_ABS_INSN },
368    { MEP_OPT_AVE, 1 << CGEN_INSN_OPTIONAL_AVE_INSN },
369    { MEP_OPT_MIN, 1 << CGEN_INSN_OPTIONAL_MINMAX_INSN },
370    { MEP_OPT_CLP, 1 << CGEN_INSN_OPTIONAL_CLIP_INSN },
371    { MEP_OPT_SAT, 1 << CGEN_INSN_OPTIONAL_SAT_INSN },
372    { MEP_OPT_UCI, 1 << CGEN_INSN_OPTIONAL_UCI_INSN },
373    { MEP_OPT_DSP, 1 << CGEN_INSN_OPTIONAL_DSP_INSN },
374    { MEP_OPT_COP, 1 << CGEN_INSN_OPTIONAL_CP_INSN },
375  };
376
377  int i;
378  unsigned int opt = 0;
379
380  for (i = 0; i < (sizeof (bits) / sizeof (bits[0])); i++)
381    if (option_mask & bits[i].option_mask_bit)
382      opt |= bits[i].opt_bit;
383
384  return opt;
385}
386
387
388/* Return the value the $OPT register would use to represent the set
389   of options for ME_MODULE.  */
390static unsigned int
391me_module_opt (CONFIG_ATTR me_module)
392{
393  return opt_from_option_mask (mep_config_map[me_module].option_mask);
394}
395
396
397/* Return the width of ME_MODULE's coprocessor data bus, in bits.
398   This is either 32 or 64.  */
399static int
400me_module_cop_data_bus_width (CONFIG_ATTR me_module)
401{
402  if (mep_config_map[me_module].option_mask
403      & (1 << CGEN_INSN_OPTIONAL_CP64_INSN))
404    return 64;
405  else
406    return 32;
407}
408
409
410/* Return true if ME_MODULE is big-endian, false otherwise.  */
411static int
412me_module_big_endian (CONFIG_ATTR me_module)
413{
414  return mep_config_map[me_module].big_endian;
415}
416
417
418/* Return the name of ME_MODULE, or NULL if it has no name.  */
419static const char *
420me_module_name (CONFIG_ATTR me_module)
421{
422  /* The default me_module has "" as its name, but it's easier for our
423     callers to test for NULL.  */
424  if (! mep_config_map[me_module].name
425      || mep_config_map[me_module].name[0] == '\0')
426    return NULL;
427  else
428    return mep_config_map[me_module].name;
429}
430
431/* Register set.  */
432
433
434/* The MeP spec defines the following registers:
435   16 general purpose registers (r0-r15)
436   32 control/special registers (csr0-csr31)
437   32 coprocessor general-purpose registers (c0 -- c31)
438   64 coprocessor control registers (ccr0 -- ccr63)
439
440   For the raw registers, we assign numbers here explicitly, instead
441   of letting the enum assign them for us; the numbers are a matter of
442   external protocol, and shouldn't shift around as things are edited.
443
444   We access the control/special registers via pseudoregisters, to
445   enforce read-only portions that some registers have.
446
447   We access the coprocessor general purpose and control registers via
448   pseudoregisters, to make sure they appear in the proper order in
449   the 'info all-registers' command (which uses the register number
450   ordering), and also to allow them to be renamed and resized
451   depending on the me_module in use.
452
453   The MeP allows coprocessor general-purpose registers to be either
454   32 or 64 bits long, depending on the configuration.  Since we don't
455   want the format of the 'g' packet to vary from one core to another,
456   the raw coprocessor GPRs are always 64 bits.  GDB doesn't allow the
457   types of registers to change (see the implementation of
458   register_type), so we have four banks of pseudoregisters for the
459   coprocessor gprs --- 32-bit vs. 64-bit, and integer
460   vs. floating-point --- and we show or hide them depending on the
461   configuration.  */
462enum
463{
464  MEP_FIRST_RAW_REGNUM = 0,
465
466  MEP_FIRST_GPR_REGNUM = 0,
467  MEP_R0_REGNUM = 0,
468  MEP_R1_REGNUM = 1,
469  MEP_R2_REGNUM = 2,
470  MEP_R3_REGNUM = 3,
471  MEP_R4_REGNUM = 4,
472  MEP_R5_REGNUM = 5,
473  MEP_R6_REGNUM = 6,
474  MEP_R7_REGNUM = 7,
475  MEP_R8_REGNUM = 8,
476  MEP_R9_REGNUM = 9,
477  MEP_R10_REGNUM = 10,
478  MEP_R11_REGNUM = 11,
479  MEP_R12_REGNUM = 12,
480  MEP_FP_REGNUM = MEP_R8_REGNUM,
481  MEP_R13_REGNUM = 13,
482  MEP_TP_REGNUM = MEP_R13_REGNUM,	/* (r13) Tiny data pointer */
483  MEP_R14_REGNUM = 14,
484  MEP_GP_REGNUM = MEP_R14_REGNUM,	/* (r14) Global pointer */
485  MEP_R15_REGNUM = 15,
486  MEP_SP_REGNUM = MEP_R15_REGNUM,	/* (r15) Stack pointer */
487  MEP_LAST_GPR_REGNUM = MEP_R15_REGNUM,
488
489  /* The raw control registers.  These are the values as received via
490     the remote protocol, directly from the target; we only let user
491     code touch the via the pseudoregisters, which enforce read-only
492     bits.  */
493  MEP_FIRST_RAW_CSR_REGNUM = 16,
494  MEP_RAW_PC_REGNUM    = 16,    /* Program counter */
495  MEP_RAW_LP_REGNUM    = 17,    /* Link pointer */
496  MEP_RAW_SAR_REGNUM   = 18,    /* Raw shift amount */
497  MEP_RAW_CSR3_REGNUM  = 19,    /* csr3: reserved */
498  MEP_RAW_RPB_REGNUM   = 20,    /* Raw repeat begin address */
499  MEP_RAW_RPE_REGNUM   = 21,    /* Repeat end address */
500  MEP_RAW_RPC_REGNUM   = 22,    /* Repeat count */
501  MEP_RAW_HI_REGNUM    = 23, /* Upper 32 bits of result of 64 bit mult/div */
502  MEP_RAW_LO_REGNUM    = 24, /* Lower 32 bits of result of 64 bit mult/div */
503  MEP_RAW_CSR9_REGNUM  = 25,    /* csr3: reserved */
504  MEP_RAW_CSR10_REGNUM = 26,    /* csr3: reserved */
505  MEP_RAW_CSR11_REGNUM = 27,    /* csr3: reserved */
506  MEP_RAW_MB0_REGNUM   = 28,    /* Raw modulo begin address 0 */
507  MEP_RAW_ME0_REGNUM   = 29,    /* Raw modulo end address 0 */
508  MEP_RAW_MB1_REGNUM   = 30,    /* Raw modulo begin address 1 */
509  MEP_RAW_ME1_REGNUM   = 31,    /* Raw modulo end address 1 */
510  MEP_RAW_PSW_REGNUM   = 32,    /* Raw program status word */
511  MEP_RAW_ID_REGNUM    = 33,    /* Raw processor ID/revision */
512  MEP_RAW_TMP_REGNUM   = 34,    /* Temporary */
513  MEP_RAW_EPC_REGNUM   = 35,    /* Exception program counter */
514  MEP_RAW_EXC_REGNUM   = 36,    /* Raw exception cause */
515  MEP_RAW_CFG_REGNUM   = 37,    /* Raw processor configuration*/
516  MEP_RAW_CSR22_REGNUM = 38,    /* csr3: reserved */
517  MEP_RAW_NPC_REGNUM   = 39,    /* Nonmaskable interrupt PC */
518  MEP_RAW_DBG_REGNUM   = 40,    /* Raw debug */
519  MEP_RAW_DEPC_REGNUM  = 41,    /* Debug exception PC */
520  MEP_RAW_OPT_REGNUM   = 42,    /* Raw options */
521  MEP_RAW_RCFG_REGNUM  = 43,    /* Raw local ram config */
522  MEP_RAW_CCFG_REGNUM  = 44,    /* Raw cache config */
523  MEP_RAW_CSR29_REGNUM = 45,    /* csr3: reserved */
524  MEP_RAW_CSR30_REGNUM = 46,    /* csr3: reserved */
525  MEP_RAW_CSR31_REGNUM = 47,    /* csr3: reserved */
526  MEP_LAST_RAW_CSR_REGNUM = MEP_RAW_CSR31_REGNUM,
527
528  /* The raw coprocessor general-purpose registers.  These are all 64
529     bits wide.  */
530  MEP_FIRST_RAW_CR_REGNUM = 48,
531  MEP_LAST_RAW_CR_REGNUM = MEP_FIRST_RAW_CR_REGNUM + 31,
532
533  MEP_FIRST_RAW_CCR_REGNUM = 80,
534  MEP_LAST_RAW_CCR_REGNUM = MEP_FIRST_RAW_CCR_REGNUM + 63,
535
536  /* The module number register.  This is the index of the me_module
537     of which the current target is an instance.  (This is not a real
538     MeP-specified register; it's provided by SID.)  */
539  MEP_MODULE_REGNUM,
540
541  MEP_LAST_RAW_REGNUM = MEP_MODULE_REGNUM,
542
543  MEP_NUM_RAW_REGS = MEP_LAST_RAW_REGNUM + 1,
544
545  /* Pseudoregisters.  See mep_pseudo_register_read and
546     mep_pseudo_register_write.  */
547  MEP_FIRST_PSEUDO_REGNUM = MEP_NUM_RAW_REGS,
548
549  /* We have a pseudoregister for every control/special register, to
550     implement registers with read-only bits.  */
551  MEP_FIRST_CSR_REGNUM = MEP_FIRST_PSEUDO_REGNUM,
552  MEP_PC_REGNUM = MEP_FIRST_CSR_REGNUM, /* Program counter */
553  MEP_LP_REGNUM,                /* Link pointer */
554  MEP_SAR_REGNUM,               /* shift amount */
555  MEP_CSR3_REGNUM,              /* csr3: reserved */
556  MEP_RPB_REGNUM,               /* repeat begin address */
557  MEP_RPE_REGNUM,               /* Repeat end address */
558  MEP_RPC_REGNUM,               /* Repeat count */
559  MEP_HI_REGNUM,  /* Upper 32 bits of the result of 64 bit mult/div */
560  MEP_LO_REGNUM,  /* Lower 32 bits of the result of 64 bit mult/div */
561  MEP_CSR9_REGNUM,              /* csr3: reserved */
562  MEP_CSR10_REGNUM,             /* csr3: reserved */
563  MEP_CSR11_REGNUM,             /* csr3: reserved */
564  MEP_MB0_REGNUM,               /* modulo begin address 0 */
565  MEP_ME0_REGNUM,               /* modulo end address 0 */
566  MEP_MB1_REGNUM,               /* modulo begin address 1 */
567  MEP_ME1_REGNUM,               /* modulo end address 1 */
568  MEP_PSW_REGNUM,               /* program status word */
569  MEP_ID_REGNUM,                /* processor ID/revision */
570  MEP_TMP_REGNUM,               /* Temporary */
571  MEP_EPC_REGNUM,               /* Exception program counter */
572  MEP_EXC_REGNUM,               /* exception cause */
573  MEP_CFG_REGNUM,               /* processor configuration*/
574  MEP_CSR22_REGNUM,             /* csr3: reserved */
575  MEP_NPC_REGNUM,               /* Nonmaskable interrupt PC */
576  MEP_DBG_REGNUM,               /* debug */
577  MEP_DEPC_REGNUM,              /* Debug exception PC */
578  MEP_OPT_REGNUM,               /* options */
579  MEP_RCFG_REGNUM,              /* local ram config */
580  MEP_CCFG_REGNUM,              /* cache config */
581  MEP_CSR29_REGNUM,             /* csr3: reserved */
582  MEP_CSR30_REGNUM,             /* csr3: reserved */
583  MEP_CSR31_REGNUM,             /* csr3: reserved */
584  MEP_LAST_CSR_REGNUM = MEP_CSR31_REGNUM,
585
586  /* The 32-bit integer view of the coprocessor GPR's.  */
587  MEP_FIRST_CR32_REGNUM,
588  MEP_LAST_CR32_REGNUM = MEP_FIRST_CR32_REGNUM + 31,
589
590  /* The 32-bit floating-point view of the coprocessor GPR's.  */
591  MEP_FIRST_FP_CR32_REGNUM,
592  MEP_LAST_FP_CR32_REGNUM = MEP_FIRST_FP_CR32_REGNUM + 31,
593
594  /* The 64-bit integer view of the coprocessor GPR's.  */
595  MEP_FIRST_CR64_REGNUM,
596  MEP_LAST_CR64_REGNUM = MEP_FIRST_CR64_REGNUM + 31,
597
598  /* The 64-bit floating-point view of the coprocessor GPR's.  */
599  MEP_FIRST_FP_CR64_REGNUM,
600  MEP_LAST_FP_CR64_REGNUM = MEP_FIRST_FP_CR64_REGNUM + 31,
601
602  MEP_FIRST_CCR_REGNUM,
603  MEP_LAST_CCR_REGNUM = MEP_FIRST_CCR_REGNUM + 63,
604
605  MEP_LAST_PSEUDO_REGNUM = MEP_LAST_CCR_REGNUM,
606
607  MEP_NUM_PSEUDO_REGS = (MEP_LAST_PSEUDO_REGNUM - MEP_LAST_RAW_REGNUM),
608
609  MEP_NUM_REGS = MEP_NUM_RAW_REGS + MEP_NUM_PSEUDO_REGS
610};
611
612
613#define IN_SET(set, n) \
614  (MEP_FIRST_ ## set ## _REGNUM <= (n) && (n) <= MEP_LAST_ ## set ## _REGNUM)
615
616#define IS_GPR_REGNUM(n)     (IN_SET (GPR,     (n)))
617#define IS_RAW_CSR_REGNUM(n) (IN_SET (RAW_CSR, (n)))
618#define IS_RAW_CR_REGNUM(n)  (IN_SET (RAW_CR,  (n)))
619#define IS_RAW_CCR_REGNUM(n) (IN_SET (RAW_CCR, (n)))
620
621#define IS_CSR_REGNUM(n)     (IN_SET (CSR,     (n)))
622#define IS_CR32_REGNUM(n)    (IN_SET (CR32,    (n)))
623#define IS_FP_CR32_REGNUM(n) (IN_SET (FP_CR32, (n)))
624#define IS_CR64_REGNUM(n)    (IN_SET (CR64,    (n)))
625#define IS_FP_CR64_REGNUM(n) (IN_SET (FP_CR64, (n)))
626#define IS_CR_REGNUM(n)      (IS_CR32_REGNUM (n) || IS_FP_CR32_REGNUM (n) \
627                              || IS_CR64_REGNUM (n) || IS_FP_CR64_REGNUM (n))
628#define IS_CCR_REGNUM(n)     (IN_SET (CCR,     (n)))
629
630#define IS_RAW_REGNUM(n)     (IN_SET (RAW,     (n)))
631#define IS_PSEUDO_REGNUM(n)  (IN_SET (PSEUDO,  (n)))
632
633#define NUM_REGS_IN_SET(set) \
634  (MEP_LAST_ ## set ## _REGNUM - MEP_FIRST_ ## set ## _REGNUM + 1)
635
636#define MEP_GPR_SIZE (4)        /* Size of a MeP general-purpose register.  */
637#define MEP_PSW_SIZE (4)        /* Size of the PSW register.  */
638#define MEP_LP_SIZE (4)         /* Size of the LP register.  */
639
640
641/* Many of the control/special registers contain bits that cannot be
642   written to; some are entirely read-only.  So we present them all as
643   pseudoregisters.
644
645   The following table describes the special properties of each CSR.  */
646struct mep_csr_register
647{
648  /* The number of this CSR's raw register.  */
649  int raw;
650
651  /* The number of this CSR's pseudoregister.  */
652  int pseudo;
653
654  /* A mask of the bits that are writeable: if a bit is set here, then
655     it can be modified; if the bit is clear, then it cannot.  */
656  LONGEST writeable_bits;
657};
658
659
660/* mep_csr_registers[i] describes the i'th CSR.
661   We just list the register numbers here explicitly to help catch
662   typos.  */
663#define CSR(name) MEP_RAW_ ## name ## _REGNUM, MEP_ ## name ## _REGNUM
664struct mep_csr_register mep_csr_registers[] = {
665  { CSR(PC),    0xffffffff },   /* manual says r/o, but we can write it */
666  { CSR(LP),    0xffffffff },
667  { CSR(SAR),   0x0000003f },
668  { CSR(CSR3),  0xffffffff },
669  { CSR(RPB),   0xfffffffe },
670  { CSR(RPE),   0xffffffff },
671  { CSR(RPC),   0xffffffff },
672  { CSR(HI),    0xffffffff },
673  { CSR(LO),    0xffffffff },
674  { CSR(CSR9),  0xffffffff },
675  { CSR(CSR10), 0xffffffff },
676  { CSR(CSR11), 0xffffffff },
677  { CSR(MB0),   0x0000ffff },
678  { CSR(ME0),   0x0000ffff },
679  { CSR(MB1),   0x0000ffff },
680  { CSR(ME1),   0x0000ffff },
681  { CSR(PSW),   0x000003ff },
682  { CSR(ID),    0x00000000 },
683  { CSR(TMP),   0xffffffff },
684  { CSR(EPC),   0xffffffff },
685  { CSR(EXC),   0x000030f0 },
686  { CSR(CFG),   0x00c0001b },
687  { CSR(CSR22), 0xffffffff },
688  { CSR(NPC),   0xffffffff },
689  { CSR(DBG),   0x00000580 },
690  { CSR(DEPC),  0xffffffff },
691  { CSR(OPT),   0x00000000 },
692  { CSR(RCFG),  0x00000000 },
693  { CSR(CCFG),  0x00000000 },
694  { CSR(CSR29), 0xffffffff },
695  { CSR(CSR30), 0xffffffff },
696  { CSR(CSR31), 0xffffffff },
697};
698
699
700/* If R is the number of a raw register, then mep_raw_to_pseudo[R] is
701   the number of the corresponding pseudoregister.  Otherwise,
702   mep_raw_to_pseudo[R] == R.  */
703static int mep_raw_to_pseudo[MEP_NUM_REGS];
704
705/* If R is the number of a pseudoregister, then mep_pseudo_to_raw[R]
706   is the number of the underlying raw register.  Otherwise
707   mep_pseudo_to_raw[R] == R.  */
708static int mep_pseudo_to_raw[MEP_NUM_REGS];
709
710static void
711mep_init_pseudoregister_maps (void)
712{
713  int i;
714
715  /* Verify that mep_csr_registers covers all the CSRs, in order.  */
716  gdb_assert (ARRAY_SIZE (mep_csr_registers) == NUM_REGS_IN_SET (CSR));
717  gdb_assert (ARRAY_SIZE (mep_csr_registers) == NUM_REGS_IN_SET (RAW_CSR));
718
719  /* Verify that the raw and pseudo ranges have matching sizes.  */
720  gdb_assert (NUM_REGS_IN_SET (RAW_CSR) == NUM_REGS_IN_SET (CSR));
721  gdb_assert (NUM_REGS_IN_SET (RAW_CR)  == NUM_REGS_IN_SET (CR32));
722  gdb_assert (NUM_REGS_IN_SET (RAW_CR)  == NUM_REGS_IN_SET (CR64));
723  gdb_assert (NUM_REGS_IN_SET (RAW_CCR) == NUM_REGS_IN_SET (CCR));
724
725  for (i = 0; i < ARRAY_SIZE (mep_csr_registers); i++)
726    {
727      struct mep_csr_register *r = &mep_csr_registers[i];
728
729      gdb_assert (r->pseudo == MEP_FIRST_CSR_REGNUM + i);
730      gdb_assert (r->raw    == MEP_FIRST_RAW_CSR_REGNUM + i);
731    }
732
733  /* Set up the initial  raw<->pseudo mappings.  */
734  for (i = 0; i < MEP_NUM_REGS; i++)
735    {
736      mep_raw_to_pseudo[i] = i;
737      mep_pseudo_to_raw[i] = i;
738    }
739
740  /* Add the CSR raw<->pseudo mappings.  */
741  for (i = 0; i < ARRAY_SIZE (mep_csr_registers); i++)
742    {
743      struct mep_csr_register *r = &mep_csr_registers[i];
744
745      mep_raw_to_pseudo[r->raw] = r->pseudo;
746      mep_pseudo_to_raw[r->pseudo] = r->raw;
747    }
748
749  /* Add the CR raw<->pseudo mappings.  */
750  for (i = 0; i < NUM_REGS_IN_SET (RAW_CR); i++)
751    {
752      int raw = MEP_FIRST_RAW_CR_REGNUM + i;
753      int pseudo32 = MEP_FIRST_CR32_REGNUM + i;
754      int pseudofp32 = MEP_FIRST_FP_CR32_REGNUM + i;
755      int pseudo64 = MEP_FIRST_CR64_REGNUM + i;
756      int pseudofp64 = MEP_FIRST_FP_CR64_REGNUM + i;
757
758      /* Truly, the raw->pseudo mapping depends on the current module.
759         But we use the raw->pseudo mapping when we read the debugging
760         info; at that point, we don't know what module we'll actually
761         be running yet.  So, we always supply the 64-bit register
762         numbers; GDB knows how to pick a smaller value out of a
763         larger register properly.  */
764      mep_raw_to_pseudo[raw] = pseudo64;
765      mep_pseudo_to_raw[pseudo32] = raw;
766      mep_pseudo_to_raw[pseudofp32] = raw;
767      mep_pseudo_to_raw[pseudo64] = raw;
768      mep_pseudo_to_raw[pseudofp64] = raw;
769    }
770
771  /* Add the CCR raw<->pseudo mappings.  */
772  for (i = 0; i < NUM_REGS_IN_SET (CCR); i++)
773    {
774      int raw = MEP_FIRST_RAW_CCR_REGNUM + i;
775      int pseudo = MEP_FIRST_CCR_REGNUM + i;
776      mep_raw_to_pseudo[raw] = pseudo;
777      mep_pseudo_to_raw[pseudo] = raw;
778    }
779}
780
781
782static int
783mep_debug_reg_to_regnum (struct gdbarch *gdbarch, int debug_reg)
784{
785  /* The debug info uses the raw register numbers.  */
786  if (debug_reg >= 0 && debug_reg < ARRAY_SIZE (mep_raw_to_pseudo))
787    return mep_raw_to_pseudo[debug_reg];
788  return -1;
789}
790
791
792/* Return the size, in bits, of the coprocessor pseudoregister
793   numbered PSEUDO.  */
794static int
795mep_pseudo_cr_size (int pseudo)
796{
797  if (IS_CR32_REGNUM (pseudo)
798      || IS_FP_CR32_REGNUM (pseudo))
799    return 32;
800  else if (IS_CR64_REGNUM (pseudo)
801           || IS_FP_CR64_REGNUM (pseudo))
802    return 64;
803  else
804    gdb_assert_not_reached ("unexpected coprocessor pseudo register");
805}
806
807
808/* If the coprocessor pseudoregister numbered PSEUDO is a
809   floating-point register, return non-zero; if it is an integer
810   register, return zero.  */
811static int
812mep_pseudo_cr_is_float (int pseudo)
813{
814  return (IS_FP_CR32_REGNUM (pseudo)
815          || IS_FP_CR64_REGNUM (pseudo));
816}
817
818
819/* Given a coprocessor GPR pseudoregister number, return its index
820   within that register bank.  */
821static int
822mep_pseudo_cr_index (int pseudo)
823{
824  if (IS_CR32_REGNUM (pseudo))
825    return pseudo - MEP_FIRST_CR32_REGNUM;
826  else if (IS_FP_CR32_REGNUM (pseudo))
827      return pseudo - MEP_FIRST_FP_CR32_REGNUM;
828  else if (IS_CR64_REGNUM (pseudo))
829      return pseudo - MEP_FIRST_CR64_REGNUM;
830  else if (IS_FP_CR64_REGNUM (pseudo))
831      return pseudo - MEP_FIRST_FP_CR64_REGNUM;
832  else
833    gdb_assert_not_reached ("unexpected coprocessor pseudo register");
834}
835
836
837/* Return the me_module index describing the current target.
838
839   If the current target has registers (e.g., simulator, remote
840   target), then this uses the value of the 'module' register, raw
841   register MEP_MODULE_REGNUM.  Otherwise, this retrieves the value
842   from the ELF header's e_flags field of the current executable
843   file.  */
844static CONFIG_ATTR
845current_me_module (void)
846{
847  if (target_has_registers)
848    {
849      ULONGEST regval;
850      regcache_cooked_read_unsigned (get_current_regcache (),
851				     MEP_MODULE_REGNUM, &regval);
852      return (CONFIG_ATTR) regval;
853    }
854  else
855    return gdbarch_tdep (target_gdbarch ())->me_module;
856}
857
858
859/* Return the set of options for the current target, in the form that
860   the OPT register would use.
861
862   If the current target has registers (e.g., simulator, remote
863   target), then this is the actual value of the OPT register.  If the
864   current target does not have registers (e.g., an executable file),
865   then use the 'module_opt' field we computed when we build the
866   gdbarch object for this module.  */
867static unsigned int
868current_options (void)
869{
870  if (target_has_registers)
871    {
872      ULONGEST regval;
873      regcache_cooked_read_unsigned (get_current_regcache (),
874				     MEP_OPT_REGNUM, &regval);
875      return regval;
876    }
877  else
878    return me_module_opt (current_me_module ());
879}
880
881
882/* Return the width of the current me_module's coprocessor data bus,
883   in bits.  This is either 32 or 64.  */
884static int
885current_cop_data_bus_width (void)
886{
887  return me_module_cop_data_bus_width (current_me_module ());
888}
889
890
891/* Return the keyword table of coprocessor general-purpose register
892   names appropriate for the me_module we're dealing with.  */
893static CGEN_KEYWORD *
894current_cr_names (void)
895{
896  const CGEN_HW_ENTRY *hw
897    = me_module_register_set (current_me_module (), "h-cr-", HW_H_CR);
898
899  return register_set_keyword_table (hw);
900}
901
902
903/* Return non-zero if the coprocessor general-purpose registers are
904   floating-point values, zero otherwise.  */
905static int
906current_cr_is_float (void)
907{
908  const CGEN_HW_ENTRY *hw
909    = me_module_register_set (current_me_module (), "h-cr-", HW_H_CR);
910
911  return CGEN_ATTR_CGEN_HW_IS_FLOAT_VALUE (CGEN_HW_ATTRS (hw));
912}
913
914
915/* Return the keyword table of coprocessor control register names
916   appropriate for the me_module we're dealing with.  */
917static CGEN_KEYWORD *
918current_ccr_names (void)
919{
920  const CGEN_HW_ENTRY *hw
921    = me_module_register_set (current_me_module (), "h-ccr-", HW_H_CCR);
922
923  return register_set_keyword_table (hw);
924}
925
926
927static const char *
928mep_register_name (struct gdbarch *gdbarch, int regnr)
929{
930  /* General-purpose registers.  */
931  static const char *gpr_names[] = {
932    "r0",   "r1",   "r2",   "r3",   /* 0 */
933    "r4",   "r5",   "r6",   "r7",   /* 4 */
934    "fp",   "r9",   "r10",  "r11",  /* 8 */
935    "r12",  "tp",   "gp",   "sp"    /* 12 */
936  };
937
938  /* Special-purpose registers.  */
939  static const char *csr_names[] = {
940    "pc",   "lp",   "sar",  "",     /* 0  csr3: reserved */
941    "rpb",  "rpe",  "rpc",  "hi",   /* 4 */
942    "lo",   "",     "",     "",     /* 8  csr9-csr11: reserved */
943    "mb0",  "me0",  "mb1",  "me1",  /* 12 */
944
945    "psw",  "id",   "tmp",  "epc",  /* 16 */
946    "exc",  "cfg",  "",     "npc",  /* 20  csr22: reserved */
947    "dbg",  "depc", "opt",  "rcfg", /* 24 */
948    "ccfg", "",     "",     ""      /* 28  csr29-csr31: reserved */
949  };
950
951  if (IS_GPR_REGNUM (regnr))
952    return gpr_names[regnr - MEP_R0_REGNUM];
953  else if (IS_CSR_REGNUM (regnr))
954    {
955      /* The 'hi' and 'lo' registers are only present on processors
956         that have the 'MUL' or 'DIV' instructions enabled.  */
957      if ((regnr == MEP_HI_REGNUM || regnr == MEP_LO_REGNUM)
958          && (! (current_options () & (MEP_OPT_MUL | MEP_OPT_DIV))))
959        return "";
960
961      return csr_names[regnr - MEP_FIRST_CSR_REGNUM];
962    }
963  else if (IS_CR_REGNUM (regnr))
964    {
965      CGEN_KEYWORD *names;
966      int cr_size;
967      int cr_is_float;
968
969      /* Does this module have a coprocessor at all?  */
970      if (! (current_options () & MEP_OPT_COP))
971        return "";
972
973      names = current_cr_names ();
974      if (! names)
975        /* This module's coprocessor has no general-purpose registers.  */
976        return "";
977
978      cr_size = current_cop_data_bus_width ();
979      if (cr_size != mep_pseudo_cr_size (regnr))
980        /* This module's coprocessor's GPR's are of a different size.  */
981        return "";
982
983      cr_is_float = current_cr_is_float ();
984      /* The extra ! operators ensure we get boolean equality, not
985         numeric equality.  */
986      if (! cr_is_float != ! mep_pseudo_cr_is_float (regnr))
987        /* This module's coprocessor's GPR's are of a different type.  */
988        return "";
989
990      return register_name_from_keyword (names, mep_pseudo_cr_index (regnr));
991    }
992  else if (IS_CCR_REGNUM (regnr))
993    {
994      /* Does this module have a coprocessor at all?  */
995      if (! (current_options () & MEP_OPT_COP))
996        return "";
997
998      {
999        CGEN_KEYWORD *names = current_ccr_names ();
1000
1001        if (! names)
1002          /* This me_module's coprocessor has no control registers.  */
1003          return "";
1004
1005        return register_name_from_keyword (names, regnr-MEP_FIRST_CCR_REGNUM);
1006      }
1007    }
1008
1009  /* It might be nice to give the 'module' register a name, but that
1010     would affect the output of 'info all-registers', which would
1011     disturb the test suites.  So we leave it invisible.  */
1012  else
1013    return NULL;
1014}
1015
1016
1017/* Custom register groups for the MeP.  */
1018static struct reggroup *mep_csr_reggroup; /* control/special */
1019static struct reggroup *mep_cr_reggroup;  /* coprocessor general-purpose */
1020static struct reggroup *mep_ccr_reggroup; /* coprocessor control */
1021
1022
1023static int
1024mep_register_reggroup_p (struct gdbarch *gdbarch, int regnum,
1025                         struct reggroup *group)
1026{
1027  /* Filter reserved or unused register numbers.  */
1028  {
1029    const char *name = mep_register_name (gdbarch, regnum);
1030
1031    if (! name || name[0] == '\0')
1032      return 0;
1033  }
1034
1035  /* We could separate the GPRs and the CSRs.  Toshiba has approved of
1036     the existing behavior, so we'd want to run that by them.  */
1037  if (group == general_reggroup)
1038    return (IS_GPR_REGNUM (regnum)
1039            || IS_CSR_REGNUM (regnum));
1040
1041  /* Everything is in the 'all' reggroup, except for the raw CSR's.  */
1042  else if (group == all_reggroup)
1043    return (IS_GPR_REGNUM (regnum)
1044            || IS_CSR_REGNUM (regnum)
1045            || IS_CR_REGNUM (regnum)
1046            || IS_CCR_REGNUM (regnum));
1047
1048  /* All registers should be saved and restored, except for the raw
1049     CSR's.
1050
1051     This is probably right if the coprocessor is something like a
1052     floating-point unit, but would be wrong if the coprocessor is
1053     something that does I/O, where register accesses actually cause
1054     externally-visible actions.  But I get the impression that the
1055     coprocessor isn't supposed to do things like that --- you'd use a
1056     hardware engine, perhaps.  */
1057  else if (group == save_reggroup || group == restore_reggroup)
1058    return (IS_GPR_REGNUM (regnum)
1059            || IS_CSR_REGNUM (regnum)
1060            || IS_CR_REGNUM (regnum)
1061            || IS_CCR_REGNUM (regnum));
1062
1063  else if (group == mep_csr_reggroup)
1064    return IS_CSR_REGNUM (regnum);
1065  else if (group == mep_cr_reggroup)
1066    return IS_CR_REGNUM (regnum);
1067  else if (group == mep_ccr_reggroup)
1068    return IS_CCR_REGNUM (regnum);
1069  else
1070    return 0;
1071}
1072
1073
1074static struct type *
1075mep_register_type (struct gdbarch *gdbarch, int reg_nr)
1076{
1077  /* Coprocessor general-purpose registers may be either 32 or 64 bits
1078     long.  So for them, the raw registers are always 64 bits long (to
1079     keep the 'g' packet format fixed), and the pseudoregisters vary
1080     in length.  */
1081  if (IS_RAW_CR_REGNUM (reg_nr))
1082    return builtin_type (gdbarch)->builtin_uint64;
1083
1084  /* Since GDB doesn't allow registers to change type, we have two
1085     banks of pseudoregisters for the coprocessor general-purpose
1086     registers: one that gives a 32-bit view, and one that gives a
1087     64-bit view.  We hide or show one or the other depending on the
1088     current module.  */
1089  if (IS_CR_REGNUM (reg_nr))
1090    {
1091      int size = mep_pseudo_cr_size (reg_nr);
1092      if (size == 32)
1093        {
1094          if (mep_pseudo_cr_is_float (reg_nr))
1095            return builtin_type (gdbarch)->builtin_float;
1096          else
1097            return builtin_type (gdbarch)->builtin_uint32;
1098        }
1099      else if (size == 64)
1100        {
1101          if (mep_pseudo_cr_is_float (reg_nr))
1102            return builtin_type (gdbarch)->builtin_double;
1103          else
1104            return builtin_type (gdbarch)->builtin_uint64;
1105        }
1106      else
1107        gdb_assert_not_reached ("unexpected cr size");
1108    }
1109
1110  /* All other registers are 32 bits long.  */
1111  else
1112    return builtin_type (gdbarch)->builtin_uint32;
1113}
1114
1115static enum register_status
1116mep_pseudo_cr32_read (struct gdbarch *gdbarch,
1117		      readable_regcache *regcache,
1118                      int cookednum,
1119                      gdb_byte *buf)
1120{
1121  enum register_status status;
1122  enum bfd_endian byte_order = gdbarch_byte_order (gdbarch);
1123  /* Read the raw register into a 64-bit buffer, and then return the
1124     appropriate end of that buffer.  */
1125  int rawnum = mep_pseudo_to_raw[cookednum];
1126  gdb_byte buf64[8];
1127
1128  gdb_assert (TYPE_LENGTH (register_type (gdbarch, rawnum)) == sizeof (buf64));
1129  gdb_assert (TYPE_LENGTH (register_type (gdbarch, cookednum)) == 4);
1130  status = regcache->raw_read (rawnum, buf64);
1131  if (status == REG_VALID)
1132    {
1133      /* Slow, but legible.  */
1134      store_unsigned_integer (buf, 4, byte_order,
1135			      extract_unsigned_integer (buf64, 8, byte_order));
1136    }
1137  return status;
1138}
1139
1140
1141static enum register_status
1142mep_pseudo_cr64_read (struct gdbarch *gdbarch,
1143                      readable_regcache *regcache,
1144                      int cookednum,
1145                      gdb_byte *buf)
1146{
1147  return regcache->raw_read (mep_pseudo_to_raw[cookednum], buf);
1148}
1149
1150
1151static enum register_status
1152mep_pseudo_register_read (struct gdbarch *gdbarch,
1153			  readable_regcache *regcache,
1154                          int cookednum,
1155                          gdb_byte *buf)
1156{
1157  if (IS_CSR_REGNUM (cookednum)
1158      || IS_CCR_REGNUM (cookednum))
1159    return regcache->raw_read (mep_pseudo_to_raw[cookednum], buf);
1160  else if (IS_CR32_REGNUM (cookednum)
1161           || IS_FP_CR32_REGNUM (cookednum))
1162    return mep_pseudo_cr32_read (gdbarch, regcache, cookednum, buf);
1163  else if (IS_CR64_REGNUM (cookednum)
1164           || IS_FP_CR64_REGNUM (cookednum))
1165    return mep_pseudo_cr64_read (gdbarch, regcache, cookednum, buf);
1166  else
1167    gdb_assert_not_reached ("unexpected pseudo register");
1168}
1169
1170
1171static void
1172mep_pseudo_csr_write (struct gdbarch *gdbarch,
1173                      struct regcache *regcache,
1174                      int cookednum,
1175                      const gdb_byte *buf)
1176{
1177  enum bfd_endian byte_order = gdbarch_byte_order (gdbarch);
1178  int size = register_size (gdbarch, cookednum);
1179  struct mep_csr_register *r
1180    = &mep_csr_registers[cookednum - MEP_FIRST_CSR_REGNUM];
1181
1182  if (r->writeable_bits == 0)
1183    /* A completely read-only register; avoid the read-modify-
1184       write cycle, and juts ignore the entire write.  */
1185    ;
1186  else
1187    {
1188      /* A partially writeable register; do a read-modify-write cycle.  */
1189      ULONGEST old_bits;
1190      ULONGEST new_bits;
1191      ULONGEST mixed_bits;
1192
1193      regcache_raw_read_unsigned (regcache, r->raw, &old_bits);
1194      new_bits = extract_unsigned_integer (buf, size, byte_order);
1195      mixed_bits = ((r->writeable_bits & new_bits)
1196                    | (~r->writeable_bits & old_bits));
1197      regcache_raw_write_unsigned (regcache, r->raw, mixed_bits);
1198    }
1199}
1200
1201
1202static void
1203mep_pseudo_cr32_write (struct gdbarch *gdbarch,
1204                       struct regcache *regcache,
1205                       int cookednum,
1206                       const gdb_byte *buf)
1207{
1208  enum bfd_endian byte_order = gdbarch_byte_order (gdbarch);
1209  /* Expand the 32-bit value into a 64-bit value, and write that to
1210     the pseudoregister.  */
1211  int rawnum = mep_pseudo_to_raw[cookednum];
1212  gdb_byte buf64[8];
1213
1214  gdb_assert (TYPE_LENGTH (register_type (gdbarch, rawnum)) == sizeof (buf64));
1215  gdb_assert (TYPE_LENGTH (register_type (gdbarch, cookednum)) == 4);
1216  /* Slow, but legible.  */
1217  store_unsigned_integer (buf64, 8, byte_order,
1218			  extract_unsigned_integer (buf, 4, byte_order));
1219  regcache->raw_write (rawnum, buf64);
1220}
1221
1222
1223static void
1224mep_pseudo_cr64_write (struct gdbarch *gdbarch,
1225                     struct regcache *regcache,
1226                     int cookednum,
1227                     const gdb_byte *buf)
1228{
1229  regcache->raw_write (mep_pseudo_to_raw[cookednum], buf);
1230}
1231
1232
1233static void
1234mep_pseudo_register_write (struct gdbarch *gdbarch,
1235                           struct regcache *regcache,
1236                           int cookednum,
1237                           const gdb_byte *buf)
1238{
1239  if (IS_CSR_REGNUM (cookednum))
1240    mep_pseudo_csr_write (gdbarch, regcache, cookednum, buf);
1241  else if (IS_CR32_REGNUM (cookednum)
1242           || IS_FP_CR32_REGNUM (cookednum))
1243    mep_pseudo_cr32_write (gdbarch, regcache, cookednum, buf);
1244  else if (IS_CR64_REGNUM (cookednum)
1245           || IS_FP_CR64_REGNUM (cookednum))
1246    mep_pseudo_cr64_write (gdbarch, regcache, cookednum, buf);
1247  else if (IS_CCR_REGNUM (cookednum))
1248    regcache->raw_write (mep_pseudo_to_raw[cookednum], buf);
1249  else
1250    gdb_assert_not_reached ("unexpected pseudo register");
1251}
1252
1253
1254
1255/* Disassembly.  */
1256
1257static int
1258mep_gdb_print_insn (bfd_vma pc, disassemble_info * info)
1259{
1260  struct obj_section * s = find_pc_section (pc);
1261
1262  info->arch = bfd_arch_mep;
1263  if (s)
1264    {
1265      /* The libopcodes disassembly code uses the section to find the
1266         BFD, the BFD to find the ELF header, the ELF header to find
1267         the me_module index, and the me_module index to select the
1268         right instructions to print.  */
1269      info->section = s->the_bfd_section;
1270    }
1271
1272  return print_insn_mep (pc, info);
1273}
1274
1275
1276/* Prologue analysis.  */
1277
1278
1279/* The MeP has two classes of instructions: "core" instructions, which
1280   are pretty normal RISC chip stuff, and "coprocessor" instructions,
1281   which are mostly concerned with moving data in and out of
1282   coprocessor registers, and branching on coprocessor condition
1283   codes.  There's space in the instruction set for custom coprocessor
1284   instructions, too.
1285
1286   Instructions can be 16 or 32 bits long; the top two bits of the
1287   first byte indicate the length.  The coprocessor instructions are
1288   mixed in with the core instructions, and there's no easy way to
1289   distinguish them; you have to completely decode them to tell one
1290   from the other.
1291
1292   The MeP also supports a "VLIW" operation mode, where instructions
1293   always occur in fixed-width bundles.  The bundles are either 32
1294   bits or 64 bits long, depending on a fixed configuration flag.  You
1295   decode the first part of the bundle as normal; if it's a core
1296   instruction, and there's any space left in the bundle, the
1297   remainder of the bundle is a coprocessor instruction, which will
1298   execute in parallel with the core instruction.  If the first part
1299   of the bundle is a coprocessor instruction, it occupies the entire
1300   bundle.
1301
1302   So, here are all the cases:
1303
1304   - 32-bit VLIW mode:
1305     Every bundle is four bytes long, and naturally aligned, and can hold
1306     one or two instructions:
1307     - 16-bit core instruction; 16-bit coprocessor instruction
1308       These execute in parallel.
1309     - 32-bit core instruction
1310     - 32-bit coprocessor instruction
1311
1312   - 64-bit VLIW mode:
1313     Every bundle is eight bytes long, and naturally aligned, and can hold
1314     one or two instructions:
1315     - 16-bit core instruction; 48-bit (!) coprocessor instruction
1316       These execute in parallel.
1317     - 32-bit core instruction; 32-bit coprocessor instruction
1318       These execute in parallel.
1319     - 64-bit coprocessor instruction
1320
1321   Now, the MeP manual doesn't define any 48- or 64-bit coprocessor
1322   instruction, so I don't really know what's up there; perhaps these
1323   are always the user-defined coprocessor instructions.  */
1324
1325
1326/* Return non-zero if PC is in a VLIW code section, zero
1327   otherwise.  */
1328static int
1329mep_pc_in_vliw_section (CORE_ADDR pc)
1330{
1331  struct obj_section *s = find_pc_section (pc);
1332  if (s)
1333    return (s->the_bfd_section->flags & SEC_MEP_VLIW);
1334  return 0;
1335}
1336
1337
1338/* Set *INSN to the next core instruction at PC, and return the
1339   address of the next instruction.
1340
1341   The MeP instruction encoding is endian-dependent.  16- and 32-bit
1342   instructions are encoded as one or two two-byte parts, and each
1343   part is byte-swapped independently.  Thus:
1344
1345      void
1346      foo (void)
1347      {
1348        asm ("movu $1, 0x123456");
1349        asm ("sb $1,0x5678($2)");
1350        asm ("clip $1, 19");
1351      }
1352
1353   compiles to this big-endian code:
1354
1355       0:	d1 56 12 34 	movu $1,0x123456
1356       4:	c1 28 56 78 	sb $1,22136($2)
1357       8:	f1 01 10 98 	clip $1,0x13
1358       c:	70 02       	ret
1359
1360   and this little-endian code:
1361
1362       0:	56 d1 34 12 	movu $1,0x123456
1363       4:	28 c1 78 56 	sb $1,22136($2)
1364       8:	01 f1 98 10 	clip $1,0x13
1365       c:	02 70       	ret
1366
1367   Instructions are returned in *INSN in an endian-independent form: a
1368   given instruction always appears in *INSN the same way, regardless
1369   of whether the instruction stream is big-endian or little-endian.
1370
1371   *INSN's most significant 16 bits are the first (i.e., at lower
1372   addresses) 16 bit part of the instruction.  Its least significant
1373   16 bits are the second (i.e., higher-addressed) 16 bit part of the
1374   instruction, or zero for a 16-bit instruction.  Both 16-bit parts
1375   are fetched using the current endianness.
1376
1377   So, the *INSN values for the instruction sequence above would be
1378   the following, in either endianness:
1379
1380       0xd1561234       movu $1,0x123456
1381       0xc1285678 	sb $1,22136($2)
1382       0xf1011098 	clip $1,0x13
1383       0x70020000      	ret
1384
1385   (In a sense, it would be more natural to return 16-bit instructions
1386   in the least significant 16 bits of *INSN, but that would be
1387   ambiguous.  In order to tell whether you're looking at a 16- or a
1388   32-bit instruction, you have to consult the major opcode field ---
1389   the most significant four bits of the instruction's first 16-bit
1390   part.  But if we put 16-bit instructions at the least significant
1391   end of *INSN, then you don't know where to find the major opcode
1392   field until you know if it's a 16- or a 32-bit instruction ---
1393   which is where we started.)
1394
1395   If PC points to a core / coprocessor bundle in a VLIW section, set
1396   *INSN to the core instruction, and return the address of the next
1397   bundle.  This has the effect of skipping the bundled coprocessor
1398   instruction.  That's okay, since coprocessor instructions aren't
1399   significant to prologue analysis --- for the time being,
1400   anyway.  */
1401
1402static CORE_ADDR
1403mep_get_insn (struct gdbarch *gdbarch, CORE_ADDR pc, unsigned long *insn)
1404{
1405  enum bfd_endian byte_order = gdbarch_byte_order (gdbarch);
1406  int pc_in_vliw_section;
1407  int vliw_mode;
1408  int insn_len;
1409  gdb_byte buf[2];
1410
1411  *insn = 0;
1412
1413  /* Are we in a VLIW section?  */
1414  pc_in_vliw_section = mep_pc_in_vliw_section (pc);
1415  if (pc_in_vliw_section)
1416    {
1417      /* Yes, find out which bundle size.  */
1418      vliw_mode = current_options () & (MEP_OPT_VL32 | MEP_OPT_VL64);
1419
1420      /* If PC is in a VLIW section, but the current core doesn't say
1421         that it supports either VLIW mode, then we don't have enough
1422         information to parse the instruction stream it contains.
1423         Since the "undifferentiated" standard core doesn't have
1424         either VLIW mode bit set, this could happen.
1425
1426         But it shouldn't be an error to (say) set a breakpoint in a
1427         VLIW section, if you know you'll never reach it.  (Perhaps
1428         you have a script that sets a bunch of standard breakpoints.)
1429
1430         So we'll just return zero here, and hope for the best.  */
1431      if (! (vliw_mode & (MEP_OPT_VL32 | MEP_OPT_VL64)))
1432        return 0;
1433
1434      /* If both VL32 and VL64 are set, that's bogus, too.  */
1435      if (vliw_mode == (MEP_OPT_VL32 | MEP_OPT_VL64))
1436        return 0;
1437    }
1438  else
1439    vliw_mode = 0;
1440
1441  read_memory (pc, buf, sizeof (buf));
1442  *insn = extract_unsigned_integer (buf, 2, byte_order) << 16;
1443
1444  /* The major opcode --- the top four bits of the first 16-bit
1445     part --- indicates whether this instruction is 16 or 32 bits
1446     long.  All 32-bit instructions have a major opcode whose top
1447     two bits are 11; all the rest are 16-bit instructions.  */
1448  if ((*insn & 0xc0000000) == 0xc0000000)
1449    {
1450      /* Fetch the second 16-bit part of the instruction.  */
1451      read_memory (pc + 2, buf, sizeof (buf));
1452      *insn = *insn | extract_unsigned_integer (buf, 2, byte_order);
1453    }
1454
1455  /* If we're in VLIW code, then the VLIW width determines the address
1456     of the next instruction.  */
1457  if (vliw_mode)
1458    {
1459      /* In 32-bit VLIW code, all bundles are 32 bits long.  We ignore the
1460         coprocessor half of a core / copro bundle.  */
1461      if (vliw_mode == MEP_OPT_VL32)
1462        insn_len = 4;
1463
1464      /* In 64-bit VLIW code, all bundles are 64 bits long.  We ignore the
1465         coprocessor half of a core / copro bundle.  */
1466      else if (vliw_mode == MEP_OPT_VL64)
1467        insn_len = 8;
1468
1469      /* We'd better be in either core, 32-bit VLIW, or 64-bit VLIW mode.  */
1470      else
1471        gdb_assert_not_reached ("unexpected vliw mode");
1472    }
1473
1474  /* Otherwise, the top two bits of the major opcode are (again) what
1475     we need to check.  */
1476  else if ((*insn & 0xc0000000) == 0xc0000000)
1477    insn_len = 4;
1478  else
1479    insn_len = 2;
1480
1481  return pc + insn_len;
1482}
1483
1484
1485/* Sign-extend the LEN-bit value N.  */
1486#define SEXT(n, len) ((((int) (n)) ^ (1 << ((len) - 1))) - (1 << ((len) - 1)))
1487
1488/* Return the LEN-bit field at POS from I.  */
1489#define FIELD(i, pos, len) (((i) >> (pos)) & ((1 << (len)) - 1))
1490
1491/* Like FIELD, but sign-extend the field's value.  */
1492#define SFIELD(i, pos, len) (SEXT (FIELD ((i), (pos), (len)), (len)))
1493
1494
1495/* Macros for decoding instructions.
1496
1497   Remember that 16-bit instructions are placed in bits 16..31 of i,
1498   not at the least significant end; this means that the major opcode
1499   field is always in the same place, regardless of the width of the
1500   instruction.  As a reminder of this, we show the lower 16 bits of a
1501   16-bit instruction as xxxx_xxxx_xxxx_xxxx.  */
1502
1503/* SB Rn,(Rm)		      0000_nnnn_mmmm_1000 */
1504/* SH Rn,(Rm)		      0000_nnnn_mmmm_1001 */
1505/* SW Rn,(Rm)		      0000_nnnn_mmmm_1010 */
1506
1507/* SW Rn,disp16(Rm)	      1100_nnnn_mmmm_1010 dddd_dddd_dddd_dddd */
1508#define IS_SW(i)	      (((i) & 0xf00f0000) == 0xc00a0000)
1509/* SB Rn,disp16(Rm)	      1100_nnnn_mmmm_1000 dddd_dddd_dddd_dddd */
1510#define IS_SB(i)	      (((i) & 0xf00f0000) == 0xc0080000)
1511/* SH Rn,disp16(Rm)	      1100_nnnn_mmmm_1001 dddd_dddd_dddd_dddd */
1512#define IS_SH(i)	      (((i) & 0xf00f0000) == 0xc0090000)
1513#define SWBH_32_BASE(i)       (FIELD (i, 20, 4))
1514#define SWBH_32_SOURCE(i)     (FIELD (i, 24, 4))
1515#define SWBH_32_OFFSET(i)     (SFIELD (i, 0, 16))
1516
1517/* SW Rn,disp7.align4(SP)     0100_nnnn_0ddd_dd10 xxxx_xxxx_xxxx_xxxx */
1518#define IS_SW_IMMD(i)	      (((i) & 0xf0830000) == 0x40020000)
1519#define SW_IMMD_SOURCE(i)     (FIELD (i, 24, 4))
1520#define SW_IMMD_OFFSET(i)     (FIELD (i, 18, 5) << 2)
1521
1522/* SW Rn,(Rm)                 0000_nnnn_mmmm_1010 xxxx_xxxx_xxxx_xxxx */
1523#define IS_SW_REG(i)	      (((i) & 0xf00f0000) == 0x000a0000)
1524#define SW_REG_SOURCE(i)      (FIELD (i, 24, 4))
1525#define SW_REG_BASE(i)        (FIELD (i, 20, 4))
1526
1527/* ADD3 Rl,Rn,Rm              1001_nnnn_mmmm_llll xxxx_xxxx_xxxx_xxxx */
1528#define IS_ADD3_16_REG(i)     (((i) & 0xf0000000) == 0x90000000)
1529#define ADD3_16_REG_SRC1(i)   (FIELD (i, 20, 4))               /* n */
1530#define ADD3_16_REG_SRC2(i)   (FIELD (i, 24, 4))               /* m */
1531
1532/* ADD3 Rn,Rm,imm16           1100_nnnn_mmmm_0000 iiii_iiii_iiii_iiii */
1533#define IS_ADD3_32(i)	      (((i) & 0xf00f0000) == 0xc0000000)
1534#define ADD3_32_TARGET(i)     (FIELD (i, 24, 4))
1535#define ADD3_32_SOURCE(i)     (FIELD (i, 20, 4))
1536#define ADD3_32_OFFSET(i)     (SFIELD (i, 0, 16))
1537
1538/* ADD3 Rn,SP,imm7.align4     0100_nnnn_0iii_ii00 xxxx_xxxx_xxxx_xxxx */
1539#define IS_ADD3_16(i)  	      (((i) & 0xf0830000) == 0x40000000)
1540#define ADD3_16_TARGET(i)     (FIELD (i, 24, 4))
1541#define ADD3_16_OFFSET(i)     (FIELD (i, 18, 5) << 2)
1542
1543/* ADD Rn,imm6		      0110_nnnn_iiii_ii00 xxxx_xxxx_xxxx_xxxx */
1544#define IS_ADD(i) 	      (((i) & 0xf0030000) == 0x60000000)
1545#define ADD_TARGET(i)	      (FIELD (i, 24, 4))
1546#define ADD_OFFSET(i)         (SFIELD (i, 18, 6))
1547
1548/* LDC Rn,imm5		      0111_nnnn_iiii_101I xxxx_xxxx_xxxx_xxxx
1549                              imm5 = I||i[7:4] */
1550#define IS_LDC(i)	      (((i) & 0xf00e0000) == 0x700a0000)
1551#define LDC_IMM(i)            ((FIELD (i, 16, 1) << 4) | FIELD (i, 20, 4))
1552#define LDC_TARGET(i)         (FIELD (i, 24, 4))
1553
1554/* LW Rn,disp16(Rm)           1100_nnnn_mmmm_1110 dddd_dddd_dddd_dddd  */
1555#define IS_LW(i)              (((i) & 0xf00f0000) == 0xc00e0000)
1556#define LW_TARGET(i)          (FIELD (i, 24, 4))
1557#define LW_BASE(i)            (FIELD (i, 20, 4))
1558#define LW_OFFSET(i)          (SFIELD (i, 0, 16))
1559
1560/* MOV Rn,Rm		      0000_nnnn_mmmm_0000 xxxx_xxxx_xxxx_xxxx */
1561#define IS_MOV(i)	      (((i) & 0xf00f0000) == 0x00000000)
1562#define MOV_TARGET(i)	      (FIELD (i, 24, 4))
1563#define MOV_SOURCE(i)	      (FIELD (i, 20, 4))
1564
1565/* BRA disp12.align2	      1011_dddd_dddd_ddd0 xxxx_xxxx_xxxx_xxxx */
1566#define IS_BRA(i)	      (((i) & 0xf0010000) == 0xb0000000)
1567#define BRA_DISP(i)           (SFIELD (i, 17, 11) << 1)
1568
1569
1570/* This structure holds the results of a prologue analysis.  */
1571struct mep_prologue
1572{
1573  /* The architecture for which we generated this prologue info.  */
1574  struct gdbarch *gdbarch;
1575
1576  /* The offset from the frame base to the stack pointer --- always
1577     zero or negative.
1578
1579     Calling this a "size" is a bit misleading, but given that the
1580     stack grows downwards, using offsets for everything keeps one
1581     from going completely sign-crazy: you never change anything's
1582     sign for an ADD instruction; always change the second operand's
1583     sign for a SUB instruction; and everything takes care of
1584     itself.  */
1585  int frame_size;
1586
1587  /* Non-zero if this function has initialized the frame pointer from
1588     the stack pointer, zero otherwise.  */
1589  int has_frame_ptr;
1590
1591  /* If has_frame_ptr is non-zero, this is the offset from the frame
1592     base to where the frame pointer points.  This is always zero or
1593     negative.  */
1594  int frame_ptr_offset;
1595
1596  /* The address of the first instruction at which the frame has been
1597     set up and the arguments are where the debug info says they are
1598     --- as best as we can tell.  */
1599  CORE_ADDR prologue_end;
1600
1601  /* reg_offset[R] is the offset from the CFA at which register R is
1602     saved, or 1 if register R has not been saved.  (Real values are
1603     always zero or negative.)  */
1604  int reg_offset[MEP_NUM_REGS];
1605};
1606
1607/* Return non-zero if VALUE is an incoming argument register.  */
1608
1609static int
1610is_arg_reg (pv_t value)
1611{
1612  return (value.kind == pvk_register
1613          && MEP_R1_REGNUM <= value.reg && value.reg <= MEP_R4_REGNUM
1614          && value.k == 0);
1615}
1616
1617/* Return non-zero if a store of REG's current value VALUE to ADDR is
1618   probably spilling an argument register to its stack slot in STACK.
1619   Such instructions should be included in the prologue, if possible.
1620
1621   The store is a spill if:
1622   - the value being stored is REG's original value;
1623   - the value has not already been stored somewhere in STACK; and
1624   - ADDR is a stack slot's address (e.g., relative to the original
1625     value of the SP).  */
1626static int
1627is_arg_spill (struct gdbarch *gdbarch, pv_t value, pv_t addr,
1628	      struct pv_area *stack)
1629{
1630  return (is_arg_reg (value)
1631          && pv_is_register (addr, MEP_SP_REGNUM)
1632          && ! stack->find_reg (gdbarch, value.reg, 0));
1633}
1634
1635
1636/* Function for finding saved registers in a 'struct pv_area'; we pass
1637   this to pv_area::scan.
1638
1639   If VALUE is a saved register, ADDR says it was saved at a constant
1640   offset from the frame base, and SIZE indicates that the whole
1641   register was saved, record its offset in RESULT_UNTYPED.  */
1642static void
1643check_for_saved (void *result_untyped, pv_t addr, CORE_ADDR size, pv_t value)
1644{
1645  struct mep_prologue *result = (struct mep_prologue *) result_untyped;
1646
1647  if (value.kind == pvk_register
1648      && value.k == 0
1649      && pv_is_register (addr, MEP_SP_REGNUM)
1650      && size == register_size (result->gdbarch, value.reg))
1651    result->reg_offset[value.reg] = addr.k;
1652}
1653
1654
1655/* Analyze a prologue starting at START_PC, going no further than
1656   LIMIT_PC.  Fill in RESULT as appropriate.  */
1657static void
1658mep_analyze_prologue (struct gdbarch *gdbarch,
1659		      CORE_ADDR start_pc, CORE_ADDR limit_pc,
1660                      struct mep_prologue *result)
1661{
1662  CORE_ADDR pc;
1663  unsigned long insn;
1664  pv_t reg[MEP_NUM_REGS];
1665  CORE_ADDR after_last_frame_setup_insn = start_pc;
1666
1667  memset (result, 0, sizeof (*result));
1668  result->gdbarch = gdbarch;
1669
1670  for (int rn = 0; rn < MEP_NUM_REGS; rn++)
1671    {
1672      reg[rn] = pv_register (rn, 0);
1673      result->reg_offset[rn] = 1;
1674    }
1675
1676  pv_area stack (MEP_SP_REGNUM, gdbarch_addr_bit (gdbarch));
1677
1678  pc = start_pc;
1679  while (pc < limit_pc)
1680    {
1681      CORE_ADDR next_pc;
1682      pv_t pre_insn_fp, pre_insn_sp;
1683
1684      next_pc = mep_get_insn (gdbarch, pc, &insn);
1685
1686      /* A zero return from mep_get_insn means that either we weren't
1687         able to read the instruction from memory, or that we don't
1688         have enough information to be able to reliably decode it.  So
1689         we'll store here and hope for the best.  */
1690      if (! next_pc)
1691        break;
1692
1693      /* Note the current values of the SP and FP, so we can tell if
1694         this instruction changed them, below.  */
1695      pre_insn_fp = reg[MEP_FP_REGNUM];
1696      pre_insn_sp = reg[MEP_SP_REGNUM];
1697
1698      if (IS_ADD (insn))
1699        {
1700          int rn = ADD_TARGET (insn);
1701          CORE_ADDR imm6 = ADD_OFFSET (insn);
1702
1703          reg[rn] = pv_add_constant (reg[rn], imm6);
1704        }
1705      else if (IS_ADD3_16 (insn))
1706	{
1707          int rn = ADD3_16_TARGET (insn);
1708          int imm7 = ADD3_16_OFFSET (insn);
1709
1710          reg[rn] = pv_add_constant (reg[MEP_SP_REGNUM], imm7);
1711        }
1712      else if (IS_ADD3_32 (insn))
1713	{
1714          int rn = ADD3_32_TARGET (insn);
1715          int rm = ADD3_32_SOURCE (insn);
1716          int imm16 = ADD3_32_OFFSET (insn);
1717
1718          reg[rn] = pv_add_constant (reg[rm], imm16);
1719	}
1720      else if (IS_SW_REG (insn))
1721        {
1722          int rn = SW_REG_SOURCE (insn);
1723          int rm = SW_REG_BASE (insn);
1724
1725          /* If simulating this store would require us to forget
1726             everything we know about the stack frame in the name of
1727             accuracy, it would be better to just quit now.  */
1728          if (stack.store_would_trash (reg[rm]))
1729            break;
1730
1731          if (is_arg_spill (gdbarch, reg[rn], reg[rm], &stack))
1732            after_last_frame_setup_insn = next_pc;
1733
1734          stack.store (reg[rm], 4, reg[rn]);
1735        }
1736      else if (IS_SW_IMMD (insn))
1737        {
1738          int rn = SW_IMMD_SOURCE (insn);
1739          int offset = SW_IMMD_OFFSET (insn);
1740          pv_t addr = pv_add_constant (reg[MEP_SP_REGNUM], offset);
1741
1742          /* If simulating this store would require us to forget
1743             everything we know about the stack frame in the name of
1744             accuracy, it would be better to just quit now.  */
1745          if (stack.store_would_trash (addr))
1746            break;
1747
1748          if (is_arg_spill (gdbarch, reg[rn], addr, &stack))
1749            after_last_frame_setup_insn = next_pc;
1750
1751          stack.store (addr, 4, reg[rn]);
1752        }
1753      else if (IS_MOV (insn))
1754	{
1755          int rn = MOV_TARGET (insn);
1756          int rm = MOV_SOURCE (insn);
1757
1758          reg[rn] = reg[rm];
1759
1760	  if (pv_is_register (reg[rm], rm) && is_arg_reg (reg[rm]))
1761	    after_last_frame_setup_insn = next_pc;
1762	}
1763      else if (IS_SB (insn) || IS_SH (insn) || IS_SW (insn))
1764	{
1765          int rn = SWBH_32_SOURCE (insn);
1766          int rm = SWBH_32_BASE (insn);
1767          int disp = SWBH_32_OFFSET (insn);
1768          int size = (IS_SB (insn) ? 1
1769                      : IS_SH (insn) ? 2
1770                      : (gdb_assert (IS_SW (insn)), 4));
1771          pv_t addr = pv_add_constant (reg[rm], disp);
1772
1773          if (stack.store_would_trash (addr))
1774            break;
1775
1776          if (is_arg_spill (gdbarch, reg[rn], addr, &stack))
1777            after_last_frame_setup_insn = next_pc;
1778
1779          stack.store (addr, size, reg[rn]);
1780	}
1781      else if (IS_LDC (insn))
1782	{
1783          int rn = LDC_TARGET (insn);
1784          int cr = LDC_IMM (insn) + MEP_FIRST_CSR_REGNUM;
1785
1786          reg[rn] = reg[cr];
1787	}
1788      else if (IS_LW (insn))
1789        {
1790          int rn = LW_TARGET (insn);
1791          int rm = LW_BASE (insn);
1792          int offset = LW_OFFSET (insn);
1793          pv_t addr = pv_add_constant (reg[rm], offset);
1794
1795          reg[rn] = stack.fetch (addr, 4);
1796        }
1797      else if (IS_BRA (insn) && BRA_DISP (insn) > 0)
1798	{
1799	  /* When a loop appears as the first statement of a function
1800	     body, gcc 4.x will use a BRA instruction to branch to the
1801	     loop condition checking code.  This BRA instruction is
1802	     marked as part of the prologue.  We therefore set next_pc
1803	     to this branch target and also stop the prologue scan.
1804	     The instructions at and beyond the branch target should
1805	     no longer be associated with the prologue.
1806
1807	     Note that we only consider forward branches here.  We
1808	     presume that a forward branch is being used to skip over
1809	     a loop body.
1810
1811	     A backwards branch is covered by the default case below.
1812	     If we were to encounter a backwards branch, that would
1813	     most likely mean that we've scanned through a loop body.
1814	     We definitely want to stop the prologue scan when this
1815	     happens and that is precisely what is done by the default
1816	     case below.  */
1817	  next_pc = pc + BRA_DISP (insn);
1818	  after_last_frame_setup_insn = next_pc;
1819	  break;
1820	}
1821      else
1822        /* We've hit some instruction we don't know how to simulate.
1823           Strictly speaking, we should set every value we're
1824           tracking to "unknown".  But we'll be optimistic, assume
1825           that we have enough information already, and stop
1826           analysis here.  */
1827        break;
1828
1829      /* If this instruction changed the FP or decreased the SP (i.e.,
1830         allocated more stack space), then this may be a good place to
1831         declare the prologue finished.  However, there are some
1832         exceptions:
1833
1834         - If the instruction just changed the FP back to its original
1835           value, then that's probably a restore instruction.  The
1836           prologue should definitely end before that.
1837
1838         - If the instruction increased the value of the SP (that is,
1839           shrunk the frame), then it's probably part of a frame
1840           teardown sequence, and the prologue should end before that.  */
1841
1842      if (! pv_is_identical (reg[MEP_FP_REGNUM], pre_insn_fp))
1843        {
1844          if (! pv_is_register_k (reg[MEP_FP_REGNUM], MEP_FP_REGNUM, 0))
1845            after_last_frame_setup_insn = next_pc;
1846        }
1847      else if (! pv_is_identical (reg[MEP_SP_REGNUM], pre_insn_sp))
1848        {
1849          /* The comparison of constants looks odd, there, because .k
1850             is unsigned.  All it really means is that the new value
1851             is lower than it was before the instruction.  */
1852          if (pv_is_register (pre_insn_sp, MEP_SP_REGNUM)
1853              && pv_is_register (reg[MEP_SP_REGNUM], MEP_SP_REGNUM)
1854              && ((pre_insn_sp.k - reg[MEP_SP_REGNUM].k)
1855                  < (reg[MEP_SP_REGNUM].k - pre_insn_sp.k)))
1856            after_last_frame_setup_insn = next_pc;
1857        }
1858
1859      pc = next_pc;
1860    }
1861
1862  /* Is the frame size (offset, really) a known constant?  */
1863  if (pv_is_register (reg[MEP_SP_REGNUM], MEP_SP_REGNUM))
1864    result->frame_size = reg[MEP_SP_REGNUM].k;
1865
1866  /* Was the frame pointer initialized?  */
1867  if (pv_is_register (reg[MEP_FP_REGNUM], MEP_SP_REGNUM))
1868    {
1869      result->has_frame_ptr = 1;
1870      result->frame_ptr_offset = reg[MEP_FP_REGNUM].k;
1871    }
1872
1873  /* Record where all the registers were saved.  */
1874  stack.scan (check_for_saved, (void *) result);
1875
1876  result->prologue_end = after_last_frame_setup_insn;
1877}
1878
1879
1880static CORE_ADDR
1881mep_skip_prologue (struct gdbarch *gdbarch, CORE_ADDR pc)
1882{
1883  const char *name;
1884  CORE_ADDR func_addr, func_end;
1885  struct mep_prologue p;
1886
1887  /* Try to find the extent of the function that contains PC.  */
1888  if (! find_pc_partial_function (pc, &name, &func_addr, &func_end))
1889    return pc;
1890
1891  mep_analyze_prologue (gdbarch, pc, func_end, &p);
1892  return p.prologue_end;
1893}
1894
1895
1896
1897/* Breakpoints.  */
1898constexpr gdb_byte mep_break_insn[] = { 0x70, 0x32 };
1899
1900typedef BP_MANIPULATION (mep_break_insn) mep_breakpoint;
1901
1902
1903/* Frames and frame unwinding.  */
1904
1905
1906static struct mep_prologue *
1907mep_analyze_frame_prologue (struct frame_info *this_frame,
1908                            void **this_prologue_cache)
1909{
1910  if (! *this_prologue_cache)
1911    {
1912      CORE_ADDR func_start, stop_addr;
1913
1914      *this_prologue_cache
1915        = FRAME_OBSTACK_ZALLOC (struct mep_prologue);
1916
1917      func_start = get_frame_func (this_frame);
1918      stop_addr = get_frame_pc (this_frame);
1919
1920      /* If we couldn't find any function containing the PC, then
1921         just initialize the prologue cache, but don't do anything.  */
1922      if (! func_start)
1923        stop_addr = func_start;
1924
1925      mep_analyze_prologue (get_frame_arch (this_frame),
1926			    func_start, stop_addr,
1927			    (struct mep_prologue *) *this_prologue_cache);
1928    }
1929
1930  return (struct mep_prologue *) *this_prologue_cache;
1931}
1932
1933
1934/* Given the next frame and a prologue cache, return this frame's
1935   base.  */
1936static CORE_ADDR
1937mep_frame_base (struct frame_info *this_frame,
1938                void **this_prologue_cache)
1939{
1940  struct mep_prologue *p
1941    = mep_analyze_frame_prologue (this_frame, this_prologue_cache);
1942
1943  /* In functions that use alloca, the distance between the stack
1944     pointer and the frame base varies dynamically, so we can't use
1945     the SP plus static information like prologue analysis to find the
1946     frame base.  However, such functions must have a frame pointer,
1947     to be able to restore the SP on exit.  So whenever we do have a
1948     frame pointer, use that to find the base.  */
1949  if (p->has_frame_ptr)
1950    {
1951      CORE_ADDR fp
1952        = get_frame_register_unsigned (this_frame, MEP_FP_REGNUM);
1953      return fp - p->frame_ptr_offset;
1954    }
1955  else
1956    {
1957      CORE_ADDR sp
1958        = get_frame_register_unsigned (this_frame, MEP_SP_REGNUM);
1959      return sp - p->frame_size;
1960    }
1961}
1962
1963
1964static void
1965mep_frame_this_id (struct frame_info *this_frame,
1966                   void **this_prologue_cache,
1967                   struct frame_id *this_id)
1968{
1969  *this_id = frame_id_build (mep_frame_base (this_frame, this_prologue_cache),
1970                             get_frame_func (this_frame));
1971}
1972
1973
1974static struct value *
1975mep_frame_prev_register (struct frame_info *this_frame,
1976                         void **this_prologue_cache, int regnum)
1977{
1978  struct mep_prologue *p
1979    = mep_analyze_frame_prologue (this_frame, this_prologue_cache);
1980
1981  /* There are a number of complications in unwinding registers on the
1982     MeP, having to do with core functions calling VLIW functions and
1983     vice versa.
1984
1985     The least significant bit of the link register, LP.LTOM, is the
1986     VLIW mode toggle bit: it's set if a core function called a VLIW
1987     function, or vice versa, and clear when the caller and callee
1988     were both in the same mode.
1989
1990     So, if we're asked to unwind the PC, then we really want to
1991     unwind the LP and clear the least significant bit.  (Real return
1992     addresses are always even.)  And if we want to unwind the program
1993     status word (PSW), we need to toggle PSW.OM if LP.LTOM is set.
1994
1995     Tweaking the register values we return in this way means that the
1996     bits in BUFFERP[] are not the same as the bits you'd find at
1997     ADDRP in the inferior, so we make sure lvalp is not_lval when we
1998     do this.  */
1999  if (regnum == MEP_PC_REGNUM)
2000    {
2001      struct value *value;
2002      CORE_ADDR lp;
2003      value = mep_frame_prev_register (this_frame, this_prologue_cache,
2004				       MEP_LP_REGNUM);
2005      lp = value_as_long (value);
2006      release_value (value);
2007
2008      return frame_unwind_got_constant (this_frame, regnum, lp & ~1);
2009    }
2010  else
2011    {
2012      CORE_ADDR frame_base = mep_frame_base (this_frame, this_prologue_cache);
2013      struct value *value;
2014
2015      /* Our caller's SP is our frame base.  */
2016      if (regnum == MEP_SP_REGNUM)
2017	return frame_unwind_got_constant (this_frame, regnum, frame_base);
2018
2019      /* If prologue analysis says we saved this register somewhere,
2020         return a description of the stack slot holding it.  */
2021      if (p->reg_offset[regnum] != 1)
2022	value = frame_unwind_got_memory (this_frame, regnum,
2023					 frame_base + p->reg_offset[regnum]);
2024
2025      /* Otherwise, presume we haven't changed the value of this
2026         register, and get it from the next frame.  */
2027      else
2028	value = frame_unwind_got_register (this_frame, regnum, regnum);
2029
2030      /* If we need to toggle the operating mode, do so.  */
2031      if (regnum == MEP_PSW_REGNUM)
2032        {
2033	  CORE_ADDR psw, lp;
2034
2035	  psw = value_as_long (value);
2036	  release_value (value);
2037
2038          /* Get the LP's value, too.  */
2039	  value = get_frame_register_value (this_frame, MEP_LP_REGNUM);
2040	  lp = value_as_long (value);
2041	  release_value (value);
2042
2043          /* If LP.LTOM is set, then toggle PSW.OM.  */
2044	  if (lp & 0x1)
2045	    psw ^= 0x1000;
2046
2047	  return frame_unwind_got_constant (this_frame, regnum, psw);
2048        }
2049
2050      return value;
2051    }
2052}
2053
2054
2055static const struct frame_unwind mep_frame_unwind = {
2056  NORMAL_FRAME,
2057  default_frame_unwind_stop_reason,
2058  mep_frame_this_id,
2059  mep_frame_prev_register,
2060  NULL,
2061  default_frame_sniffer
2062};
2063
2064
2065/* Our general unwinding function can handle unwinding the PC.  */
2066static CORE_ADDR
2067mep_unwind_pc (struct gdbarch *gdbarch, struct frame_info *next_frame)
2068{
2069  return frame_unwind_register_unsigned (next_frame, MEP_PC_REGNUM);
2070}
2071
2072
2073/* Our general unwinding function can handle unwinding the SP.  */
2074static CORE_ADDR
2075mep_unwind_sp (struct gdbarch *gdbarch, struct frame_info *next_frame)
2076{
2077  return frame_unwind_register_unsigned (next_frame, MEP_SP_REGNUM);
2078}
2079
2080
2081
2082/* Return values.  */
2083
2084
2085static int
2086mep_use_struct_convention (struct type *type)
2087{
2088  return (TYPE_LENGTH (type) > MEP_GPR_SIZE);
2089}
2090
2091
2092static void
2093mep_extract_return_value (struct gdbarch *arch,
2094                          struct type *type,
2095                          struct regcache *regcache,
2096                          gdb_byte *valbuf)
2097{
2098  int byte_order = gdbarch_byte_order (arch);
2099
2100  /* Values that don't occupy a full register appear at the less
2101     significant end of the value.  This is the offset to where the
2102     value starts.  */
2103  int offset;
2104
2105  /* Return values > MEP_GPR_SIZE bytes are returned in memory,
2106     pointed to by R0.  */
2107  gdb_assert (TYPE_LENGTH (type) <= MEP_GPR_SIZE);
2108
2109  if (byte_order == BFD_ENDIAN_BIG)
2110    offset = MEP_GPR_SIZE - TYPE_LENGTH (type);
2111  else
2112    offset = 0;
2113
2114  /* Return values that do fit in a single register are returned in R0.  */
2115  regcache->cooked_read_part (MEP_R0_REGNUM, offset, TYPE_LENGTH (type),
2116			      valbuf);
2117}
2118
2119
2120static void
2121mep_store_return_value (struct gdbarch *arch,
2122                        struct type *type,
2123                        struct regcache *regcache,
2124                        const gdb_byte *valbuf)
2125{
2126  int byte_order = gdbarch_byte_order (arch);
2127
2128  /* Values that fit in a single register go in R0.  */
2129  if (TYPE_LENGTH (type) <= MEP_GPR_SIZE)
2130    {
2131      /* Values that don't occupy a full register appear at the least
2132         significant end of the value.  This is the offset to where the
2133         value starts.  */
2134      int offset;
2135
2136      if (byte_order == BFD_ENDIAN_BIG)
2137        offset = MEP_GPR_SIZE - TYPE_LENGTH (type);
2138      else
2139        offset = 0;
2140
2141      regcache->cooked_write_part (MEP_R0_REGNUM, offset, TYPE_LENGTH (type),
2142				   valbuf);
2143    }
2144
2145  /* Return values larger than a single register are returned in
2146     memory, pointed to by R0.  Unfortunately, we can't count on R0
2147     pointing to the return buffer, so we raise an error here.  */
2148  else
2149    error (_("\
2150GDB cannot set return values larger than four bytes; the Media Processor's\n\
2151calling conventions do not provide enough information to do this.\n\
2152Try using the 'return' command with no argument."));
2153}
2154
2155static enum return_value_convention
2156mep_return_value (struct gdbarch *gdbarch, struct value *function,
2157		  struct type *type, struct regcache *regcache,
2158		  gdb_byte *readbuf, const gdb_byte *writebuf)
2159{
2160  if (mep_use_struct_convention (type))
2161    {
2162      if (readbuf)
2163	{
2164	  ULONGEST addr;
2165	  /* Although the address of the struct buffer gets passed in R1, it's
2166	     returned in R0.  Fetch R0's value and then read the memory
2167	     at that address.  */
2168	  regcache_raw_read_unsigned (regcache, MEP_R0_REGNUM, &addr);
2169	  read_memory (addr, readbuf, TYPE_LENGTH (type));
2170	}
2171      if (writebuf)
2172	{
2173	  /* Return values larger than a single register are returned in
2174	     memory, pointed to by R0.  Unfortunately, we can't count on R0
2175	     pointing to the return buffer, so we raise an error here.  */
2176	  error (_("\
2177GDB cannot set return values larger than four bytes; the Media Processor's\n\
2178calling conventions do not provide enough information to do this.\n\
2179Try using the 'return' command with no argument."));
2180	}
2181      return RETURN_VALUE_ABI_RETURNS_ADDRESS;
2182    }
2183
2184  if (readbuf)
2185    mep_extract_return_value (gdbarch, type, regcache, readbuf);
2186  if (writebuf)
2187    mep_store_return_value (gdbarch, type, regcache, writebuf);
2188
2189  return RETURN_VALUE_REGISTER_CONVENTION;
2190}
2191
2192
2193/* Inferior calls.  */
2194
2195
2196static CORE_ADDR
2197mep_frame_align (struct gdbarch *gdbarch, CORE_ADDR sp)
2198{
2199  /* Require word alignment.  */
2200  return sp & -4;
2201}
2202
2203
2204/* From "lang_spec2.txt":
2205
2206   4.2 Calling conventions
2207
2208   4.2.1 Core register conventions
2209
2210   - Parameters should be evaluated from left to right, and they
2211     should be held in $1,$2,$3,$4 in order.  The fifth parameter or
2212     after should be held in the stack.  If the size is larger than 4
2213     bytes in the first four parameters, the pointer should be held in
2214     the registers instead.  If the size is larger than 4 bytes in the
2215     fifth parameter or after, the pointer should be held in the stack.
2216
2217   - Return value of a function should be held in register $0.  If the
2218     size of return value is larger than 4 bytes, $1 should hold the
2219     pointer pointing memory that would hold the return value.  In this
2220     case, the first parameter should be held in $2, the second one in
2221     $3, and the third one in $4, and the forth parameter or after
2222     should be held in the stack.
2223
2224   [This doesn't say so, but arguments shorter than four bytes are
2225   passed in the least significant end of a four-byte word when
2226   they're passed on the stack.]  */
2227
2228
2229/* Traverse the list of ARGC arguments ARGV; for every ARGV[i] too
2230   large to fit in a register, save it on the stack, and place its
2231   address in COPY[i].  SP is the initial stack pointer; return the
2232   new stack pointer.  */
2233static CORE_ADDR
2234push_large_arguments (CORE_ADDR sp, int argc, struct value **argv,
2235                      CORE_ADDR copy[])
2236{
2237  int i;
2238
2239  for (i = 0; i < argc; i++)
2240    {
2241      unsigned arg_len = TYPE_LENGTH (value_type (argv[i]));
2242
2243      if (arg_len > MEP_GPR_SIZE)
2244        {
2245          /* Reserve space for the copy, and then round the SP down, to
2246             make sure it's all aligned properly.  */
2247          sp = (sp - arg_len) & -4;
2248          write_memory (sp, value_contents (argv[i]), arg_len);
2249          copy[i] = sp;
2250        }
2251    }
2252
2253  return sp;
2254}
2255
2256
2257static CORE_ADDR
2258mep_push_dummy_call (struct gdbarch *gdbarch, struct value *function,
2259                     struct regcache *regcache, CORE_ADDR bp_addr,
2260                     int argc, struct value **argv, CORE_ADDR sp,
2261		     function_call_return_method return_method,
2262                     CORE_ADDR struct_addr)
2263{
2264  enum bfd_endian byte_order = gdbarch_byte_order (gdbarch);
2265  CORE_ADDR *copy = (CORE_ADDR *) alloca (argc * sizeof (copy[0]));
2266  int i;
2267
2268  /* The number of the next register available to hold an argument.  */
2269  int arg_reg;
2270
2271  /* The address of the next stack slot available to hold an argument.  */
2272  CORE_ADDR arg_stack;
2273
2274  /* The address of the end of the stack area for arguments.  This is
2275     just for error checking.  */
2276  CORE_ADDR arg_stack_end;
2277
2278  sp = push_large_arguments (sp, argc, argv, copy);
2279
2280  /* Reserve space for the stack arguments, if any.  */
2281  arg_stack_end = sp;
2282  if (argc + (struct_addr ? 1 : 0) > 4)
2283    sp -= ((argc + (struct_addr ? 1 : 0)) - 4) * MEP_GPR_SIZE;
2284
2285  arg_reg = MEP_R1_REGNUM;
2286  arg_stack = sp;
2287
2288  /* If we're returning a structure by value, push the pointer to the
2289     buffer as the first argument.  */
2290  if (return_method == return_method_struct)
2291    {
2292      regcache_cooked_write_unsigned (regcache, arg_reg, struct_addr);
2293      arg_reg++;
2294    }
2295
2296  for (i = 0; i < argc; i++)
2297    {
2298      ULONGEST value;
2299
2300      /* Arguments that fit in a GPR get expanded to fill the GPR.  */
2301      if (TYPE_LENGTH (value_type (argv[i])) <= MEP_GPR_SIZE)
2302        value = extract_unsigned_integer (value_contents (argv[i]),
2303                                          TYPE_LENGTH (value_type (argv[i])),
2304					  byte_order);
2305
2306      /* Arguments too large to fit in a GPR get copied to the stack,
2307         and we pass a pointer to the copy.  */
2308      else
2309        value = copy[i];
2310
2311      /* We use $1 -- $4 for passing arguments, then use the stack.  */
2312      if (arg_reg <= MEP_R4_REGNUM)
2313        {
2314          regcache_cooked_write_unsigned (regcache, arg_reg, value);
2315          arg_reg++;
2316        }
2317      else
2318        {
2319          gdb_byte buf[MEP_GPR_SIZE];
2320          store_unsigned_integer (buf, MEP_GPR_SIZE, byte_order, value);
2321          write_memory (arg_stack, buf, MEP_GPR_SIZE);
2322          arg_stack += MEP_GPR_SIZE;
2323        }
2324    }
2325
2326  gdb_assert (arg_stack <= arg_stack_end);
2327
2328  /* Set the return address.  */
2329  regcache_cooked_write_unsigned (regcache, MEP_LP_REGNUM, bp_addr);
2330
2331  /* Update the stack pointer.  */
2332  regcache_cooked_write_unsigned (regcache, MEP_SP_REGNUM, sp);
2333
2334  return sp;
2335}
2336
2337
2338static struct frame_id
2339mep_dummy_id (struct gdbarch *gdbarch, struct frame_info *this_frame)
2340{
2341  CORE_ADDR sp = get_frame_register_unsigned (this_frame, MEP_SP_REGNUM);
2342  return frame_id_build (sp, get_frame_pc (this_frame));
2343}
2344
2345
2346
2347/* Initialization.  */
2348
2349
2350static struct gdbarch *
2351mep_gdbarch_init (struct gdbarch_info info, struct gdbarch_list *arches)
2352{
2353  struct gdbarch *gdbarch;
2354  struct gdbarch_tdep *tdep;
2355
2356  /* Which me_module are we building a gdbarch object for?  */
2357  CONFIG_ATTR me_module;
2358
2359  /* If we have a BFD in hand, figure out which me_module it was built
2360     for.  Otherwise, use the no-particular-me_module code.  */
2361  if (info.abfd)
2362    {
2363      /* The way to get the me_module code depends on the object file
2364         format.  At the moment, we only know how to handle ELF.  */
2365      if (bfd_get_flavour (info.abfd) == bfd_target_elf_flavour)
2366	{
2367	  int flag = elf_elfheader (info.abfd)->e_flags & EF_MEP_INDEX_MASK;
2368	  me_module = (CONFIG_ATTR) flag;
2369	}
2370      else
2371        me_module = CONFIG_NONE;
2372    }
2373  else
2374    me_module = CONFIG_NONE;
2375
2376  /* If we're setting the architecture from a file, check the
2377     endianness of the file against that of the me_module.  */
2378  if (info.abfd)
2379    {
2380      /* The negations on either side make the comparison treat all
2381         non-zero (true) values as equal.  */
2382      if (! bfd_big_endian (info.abfd) != ! me_module_big_endian (me_module))
2383        {
2384          const char *module_name = me_module_name (me_module);
2385          const char *module_endianness
2386            = me_module_big_endian (me_module) ? "big" : "little";
2387          const char *file_name = bfd_get_filename (info.abfd);
2388          const char *file_endianness
2389            = bfd_big_endian (info.abfd) ? "big" : "little";
2390
2391          fputc_unfiltered ('\n', gdb_stderr);
2392          if (module_name)
2393            warning (_("the MeP module '%s' is %s-endian, but the executable\n"
2394		       "%s is %s-endian."),
2395                     module_name, module_endianness,
2396                     file_name, file_endianness);
2397          else
2398            warning (_("the selected MeP module is %s-endian, but the "
2399		       "executable\n"
2400		       "%s is %s-endian."),
2401                     module_endianness, file_name, file_endianness);
2402        }
2403    }
2404
2405  /* Find a candidate among the list of architectures we've created
2406     already.  info->bfd_arch_info needs to match, but we also want
2407     the right me_module: the ELF header's e_flags field needs to
2408     match as well.  */
2409  for (arches = gdbarch_list_lookup_by_info (arches, &info);
2410       arches != NULL;
2411       arches = gdbarch_list_lookup_by_info (arches->next, &info))
2412    if (gdbarch_tdep (arches->gdbarch)->me_module == me_module)
2413      return arches->gdbarch;
2414
2415  tdep = XCNEW (struct gdbarch_tdep);
2416  gdbarch = gdbarch_alloc (&info, tdep);
2417
2418  /* Get a CGEN CPU descriptor for this architecture.  */
2419  {
2420    const char *mach_name = info.bfd_arch_info->printable_name;
2421    enum cgen_endian endian = (info.byte_order == BFD_ENDIAN_BIG
2422                               ? CGEN_ENDIAN_BIG
2423                               : CGEN_ENDIAN_LITTLE);
2424
2425    tdep->cpu_desc = mep_cgen_cpu_open (CGEN_CPU_OPEN_BFDMACH, mach_name,
2426                                        CGEN_CPU_OPEN_ENDIAN, endian,
2427                                        CGEN_CPU_OPEN_END);
2428  }
2429
2430  tdep->me_module = me_module;
2431
2432  /* Register set.  */
2433  set_gdbarch_num_regs (gdbarch, MEP_NUM_RAW_REGS);
2434  set_gdbarch_pc_regnum (gdbarch, MEP_PC_REGNUM);
2435  set_gdbarch_sp_regnum (gdbarch, MEP_SP_REGNUM);
2436  set_gdbarch_register_name (gdbarch, mep_register_name);
2437  set_gdbarch_register_type (gdbarch, mep_register_type);
2438  set_gdbarch_num_pseudo_regs (gdbarch, MEP_NUM_PSEUDO_REGS);
2439  set_gdbarch_pseudo_register_read (gdbarch, mep_pseudo_register_read);
2440  set_gdbarch_pseudo_register_write (gdbarch, mep_pseudo_register_write);
2441  set_gdbarch_dwarf2_reg_to_regnum (gdbarch, mep_debug_reg_to_regnum);
2442  set_gdbarch_stab_reg_to_regnum (gdbarch, mep_debug_reg_to_regnum);
2443
2444  set_gdbarch_register_reggroup_p (gdbarch, mep_register_reggroup_p);
2445  reggroup_add (gdbarch, all_reggroup);
2446  reggroup_add (gdbarch, general_reggroup);
2447  reggroup_add (gdbarch, save_reggroup);
2448  reggroup_add (gdbarch, restore_reggroup);
2449  reggroup_add (gdbarch, mep_csr_reggroup);
2450  reggroup_add (gdbarch, mep_cr_reggroup);
2451  reggroup_add (gdbarch, mep_ccr_reggroup);
2452
2453  /* Disassembly.  */
2454  set_gdbarch_print_insn (gdbarch, mep_gdb_print_insn);
2455
2456  /* Breakpoints.  */
2457  set_gdbarch_breakpoint_kind_from_pc (gdbarch, mep_breakpoint::kind_from_pc);
2458  set_gdbarch_sw_breakpoint_from_kind (gdbarch, mep_breakpoint::bp_from_kind);
2459  set_gdbarch_decr_pc_after_break (gdbarch, 0);
2460  set_gdbarch_skip_prologue (gdbarch, mep_skip_prologue);
2461
2462  /* Frames and frame unwinding.  */
2463  frame_unwind_append_unwinder (gdbarch, &mep_frame_unwind);
2464  set_gdbarch_unwind_pc (gdbarch, mep_unwind_pc);
2465  set_gdbarch_unwind_sp (gdbarch, mep_unwind_sp);
2466  set_gdbarch_inner_than (gdbarch, core_addr_lessthan);
2467  set_gdbarch_frame_args_skip (gdbarch, 0);
2468
2469  /* Return values.  */
2470  set_gdbarch_return_value (gdbarch, mep_return_value);
2471
2472  /* Inferior function calls.  */
2473  set_gdbarch_frame_align (gdbarch, mep_frame_align);
2474  set_gdbarch_push_dummy_call (gdbarch, mep_push_dummy_call);
2475  set_gdbarch_dummy_id (gdbarch, mep_dummy_id);
2476
2477  return gdbarch;
2478}
2479
2480void
2481_initialize_mep_tdep (void)
2482{
2483  mep_csr_reggroup = reggroup_new ("csr", USER_REGGROUP);
2484  mep_cr_reggroup  = reggroup_new ("cr", USER_REGGROUP);
2485  mep_ccr_reggroup = reggroup_new ("ccr", USER_REGGROUP);
2486
2487  register_gdbarch_init (bfd_arch_mep, mep_gdbarch_init);
2488
2489  mep_init_pseudoregister_maps ();
2490}
2491