1 /* Target-machine dependent code for Motorola 88000 series, for GDB.
2 Copyright (C) 1988, 1990, 1991 Free Software Foundation, Inc.
4 This file is part of GDB.
6 This program is free software; you can redistribute it and/or modify
7 it under the terms of the GNU General Public License as published by
8 the Free Software Foundation; either version 2 of the License, or
9 (at your option) any later version.
11 This program is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14 GNU General Public License for more details.
16 You should have received a copy of the GNU General Public License
17 along with this program; if not, write to the Free Software
18 Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
30 /* Size of an instruction */
31 #define BYTES_PER_88K_INSN 4
33 void frame_find_saved_regs ();
35 /* is this target an m88110? Otherwise assume m88100. This has
36 relevance for the ways in which we screw with instruction pointers. */
37 int target_is_m88110 = 0;
39 /* Given a GDB frame, determine the address of the calling function's frame.
40 This will be used to create a new GDB frame struct, and then
41 INIT_EXTRA_FRAME_INFO and INIT_FRAME_PC will be called for the new frame.
43 For us, the frame address is its stack pointer value, so we look up
44 the function prologue to determine the caller's sp value, and return it. */
47 frame_chain (thisframe)
51 frame_find_saved_regs (thisframe, (struct frame_saved_regs *) 0);
52 /* NOTE: this depends on frame_find_saved_regs returning the VALUE, not
53 the ADDRESS, of SP_REGNUM. It also depends on the cache of
54 frame_find_saved_regs results. */
55 if (thisframe->fsr->regs[SP_REGNUM])
56 return thisframe->fsr->regs[SP_REGNUM];
58 return thisframe->frame; /* Leaf fn -- next frame up has same SP. */
62 frameless_function_invocation (frame)
66 frame_find_saved_regs (frame, (struct frame_saved_regs *) 0);
67 /* NOTE: this depends on frame_find_saved_regs returning the VALUE, not
68 the ADDRESS, of SP_REGNUM. It also depends on the cache of
69 frame_find_saved_regs results. */
70 if (frame->fsr->regs[SP_REGNUM])
71 return 0; /* Frameful -- return addr saved somewhere */
73 return 1; /* Frameless -- no saved return address */
77 init_extra_frame_info (fromleaf, fi)
79 struct frame_info *fi;
81 fi->fsr = 0; /* Not yet allocated */
82 fi->args_pointer = 0; /* Unknown */
83 fi->locals_pointer = 0; /* Unknown */
86 /* Examine an m88k function prologue, recording the addresses at which
87 registers are saved explicitly by the prologue code, and returning
88 the address of the first instruction after the prologue (but not
89 after the instruction at address LIMIT, as explained below).
91 LIMIT places an upper bound on addresses of the instructions to be
92 examined. If the prologue code scan reaches LIMIT, the scan is
93 aborted and LIMIT is returned. This is used, when examining the
94 prologue for the current frame, to keep examine_prologue () from
95 claiming that a given register has been saved when in fact the
96 instruction that saves it has not yet been executed. LIMIT is used
97 at other times to stop the scan when we hit code after the true
98 function prologue (e.g. for the first source line) which might
99 otherwise be mistaken for function prologue.
101 The format of the function prologue matched by this routine is
102 derived from examination of the source to gcc 1.95, particularly
103 the routine output_prologue () in config/out-m88k.c.
105 subu r31,r31,n # stack pointer update
107 (st rn,r31,offset)? # save incoming regs
108 (st.d rn,r31,offset)?
110 (addu r30,r31,n)? # frame pointer update
112 (pic sequence)? # PIC code prologue
114 (or rn,rm,0)? # Move parameters to other regs
117 /* Macros for extracting fields from instructions. */
119 #define BITMASK(pos, width) (((0x1 << (width)) - 1) << (pos))
120 #define EXTRACT_FIELD(val, pos, width) ((val) >> (pos) & BITMASK (0, width))
122 /* Prologue code that handles position-independent-code setup. */
124 struct pic_prologue_code {
125 unsigned long insn, mask;
128 static struct pic_prologue_code pic_prologue_code [] = {
129 /* FIXME -- until this is translated to hex, we won't match it... */
131 /* or r10,r1,0 (if not saved) */
133 /* or.u r25,r0,const */
134 /*LabN: or r25,r25,const2 */
136 /* or r1,r10,0 (if not saved) */
139 /* Fetch the instruction at ADDR, returning 0 if ADDR is beyond LIM or
140 is not the address of a valid instruction, the address of the next
141 instruction beyond ADDR otherwise. *PWORD1 receives the first word
142 of the instruction. PWORD2 is ignored -- a remnant of the original
145 #define NEXT_PROLOGUE_INSN(addr, lim, pword1) \
146 (((addr) < (lim)) ? next_insn (addr, pword1) : 0)
148 /* Read the m88k instruction at 'memaddr' and return the address of
149 the next instruction after that, or 0 if 'memaddr' is not the
150 address of a valid instruction. The instruction
151 is stored at 'pword1'. */
154 next_insn (memaddr, pword1)
155 unsigned long *pword1;
158 *pword1 = read_memory_integer (memaddr, BYTES_PER_88K_INSN);
159 return memaddr + BYTES_PER_88K_INSN;
162 /* Read a register from frames called by us (or from the hardware regs). */
165 read_next_frame_reg(fi, regno)
169 for (; fi; fi = fi->next) {
170 if (regno == SP_REGNUM) return fi->frame;
171 else if (fi->fsr->regs[regno])
172 return read_memory_integer(fi->fsr->regs[regno], 4);
174 return read_register(regno);
177 /* Examine the prologue of a function. `ip' points to the first instruction.
178 `limit' is the limit of the prologue (e.g. the addr of the first
179 linenumber, or perhaps the program counter if we're stepping through).
180 `frame_sp' is the stack pointer value in use in this frame.
181 `fsr' is a pointer to a frame_saved_regs structure into which we put
182 info about the registers saved by this frame.
183 `fi' is a struct frame_info pointer; we fill in various fields in it
184 to reflect the offsets of the arg pointer and the locals pointer. */
187 examine_prologue (ip, limit, frame_sp, fsr, fi)
188 register CORE_ADDR ip;
189 register CORE_ADDR limit;
191 struct frame_saved_regs *fsr;
192 struct frame_info *fi;
194 register CORE_ADDR next_ip;
196 register struct pic_prologue_code *pcode;
199 char must_adjust[32]; /* If set, must adjust offsets in fsr */
200 int sp_offset = -1; /* -1 means not set (valid must be mult of 8) */
201 int fp_offset = -1; /* -1 means not set */
204 memset (must_adjust, '\0', sizeof (must_adjust));
205 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
207 /* Accept move of incoming registers to other registers, using
208 "or rd,rs,0" or "or.u rd,rs,0" or "or rd,r0,rs" or "or rd,rs,r0".
209 We don't have to worry about walking into the first lines of code,
210 since the first line number will stop us (assuming we have symbols).
211 What we have actually seen is "or r10,r0,r12". */
213 #define OR_MOVE_INSN 0x58000000 /* or/or.u with immed of 0 */
214 #define OR_MOVE_MASK 0xF800FFFF
215 #define OR_REG_MOVE1_INSN 0xF4005800 /* or rd,r0,rs */
216 #define OR_REG_MOVE1_MASK 0xFC1FFFE0
217 #define OR_REG_MOVE2_INSN 0xF4005800 /* or rd,rs,r0 */
218 #define OR_REG_MOVE2_MASK 0xFC00FFFF
220 ((insn & OR_MOVE_MASK) == OR_MOVE_INSN ||
221 (insn & OR_REG_MOVE1_MASK) == OR_REG_MOVE1_INSN ||
222 (insn & OR_REG_MOVE2_MASK) == OR_REG_MOVE2_INSN
226 /* We don't care what moves to where. The result of the moves
227 has already been reflected in what the compiler tells us is the
228 location of these parameters. */
230 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
233 /* Accept an optional "subu sp,sp,n" to set up the stack pointer. */
235 #define SUBU_SP_INSN 0x67ff0000
236 #define SUBU_SP_MASK 0xffff0007 /* Note offset must be mult. of 8 */
237 #define SUBU_OFFSET(x) ((unsigned)(x & 0xFFFF))
239 ((insn & SUBU_SP_MASK) == SUBU_SP_INSN)) /* subu r31, r31, N */
241 sp_offset = -SUBU_OFFSET (insn);
243 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
246 /* The function must start with a stack-pointer adjustment, or
247 we don't know WHAT'S going on... */
251 /* Accept zero or more instances of "st rx,sp,n" or "st.d rx,sp,n".
252 This may cause us to mistake the copying of a register
253 parameter to the frame for the saving of a callee-saved
254 register, but that can't be helped, since with the
255 "-fcall-saved" flag, any register can be made callee-saved.
256 This probably doesn't matter, since the ``saved'' caller's values of
257 non-callee-saved registers are not relevant anyway. */
259 #define STD_STACK_INSN 0x201f0000
260 #define STD_STACK_MASK 0xfc1f0000
261 #define ST_STACK_INSN 0x241f0000
262 #define ST_STACK_MASK 0xfc1f0000
263 #define ST_OFFSET(x) ((unsigned)((x) & 0xFFFF))
264 #define ST_SRC(x) EXTRACT_FIELD ((x), 21, 5)
268 if ((insn & ST_STACK_MASK) == ST_STACK_INSN)
270 else if ((insn & STD_STACK_MASK) == STD_STACK_INSN)
276 offset = ST_OFFSET (insn);
279 must_adjust[src] = 1;
280 fsr->regs[src++] = offset; /* Will be adjusted later */
284 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
287 /* Accept an optional "addu r30,r31,n" to set up the frame pointer. */
289 #define ADDU_FP_INSN 0x63df0000
290 #define ADDU_FP_MASK 0xffff0000
291 #define ADDU_OFFSET(x) ((unsigned)(x & 0xFFFF))
293 ((insn & ADDU_FP_MASK) == ADDU_FP_INSN)) /* addu r30, r31, N */
295 fp_offset = ADDU_OFFSET (insn);
297 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
300 /* Accept the PIC prologue code if present. */
302 pcode = pic_prologue_code;
303 size = sizeof (pic_prologue_code) / sizeof (*pic_prologue_code);
304 /* If return addr is saved, we don't use first or last insn of PICstuff. */
305 if (fsr->regs[SRP_REGNUM]) {
310 while (size-- && next_ip && (pcode->insn == (pcode->mask & insn)))
314 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
317 /* Accept moves of parameter registers to other registers, using
318 "or rd,rs,0" or "or.u rd,rs,0" or "or rd,r0,rs" or "or rd,rs,r0".
319 We don't have to worry about walking into the first lines of code,
320 since the first line number will stop us (assuming we have symbols).
321 What gcc actually seems to produce is "or rd,r0,rs". */
323 #define OR_MOVE_INSN 0x58000000 /* or/or.u with immed of 0 */
324 #define OR_MOVE_MASK 0xF800FFFF
325 #define OR_REG_MOVE1_INSN 0xF4005800 /* or rd,r0,rs */
326 #define OR_REG_MOVE1_MASK 0xFC1FFFE0
327 #define OR_REG_MOVE2_INSN 0xF4005800 /* or rd,rs,r0 */
328 #define OR_REG_MOVE2_MASK 0xFC00FFFF
330 ((insn & OR_MOVE_MASK) == OR_MOVE_INSN ||
331 (insn & OR_REG_MOVE1_MASK) == OR_REG_MOVE1_INSN ||
332 (insn & OR_REG_MOVE2_MASK) == OR_REG_MOVE2_INSN
336 /* We don't care what moves to where. The result of the moves
337 has already been reflected in what the compiler tells us is the
338 location of these parameters. */
340 next_ip = NEXT_PROLOGUE_INSN (ip, limit, &insn);
343 /* We're done with the prologue. If we don't care about the stack
344 frame itself, just return. (Note that fsr->regs has been trashed,
345 but the one caller who calls with fi==0 passes a dummy there.) */
353 sp_offset original (before any alloca calls) displacement of SP
356 fp_offset displacement from original SP to the FP for this frame
359 fsr->regs[0..31] displacement from original SP to the stack
360 location where reg[0..31] is stored.
362 must_adjust[0..31] set if corresponding offset was set.
364 If alloca has been called between the function prologue and the current
365 IP, then the current SP (frame_sp) will not be the original SP as set by
366 the function prologue. If the current SP is not the original SP, then the
367 compiler will have allocated an FP for this frame, fp_offset will be set,
368 and we can use it to calculate the original SP.
370 Then, we figure out where the arguments and locals are, and relocate the
371 offsets in fsr->regs to absolute addresses. */
373 if (fp_offset != -1) {
374 /* We have a frame pointer, so get it, and base our calc's on it. */
375 frame_fp = (CORE_ADDR) read_next_frame_reg (fi->next, ACTUAL_FP_REGNUM);
376 frame_sp = frame_fp - fp_offset;
378 /* We have no frame pointer, therefore frame_sp is still the same value
379 as set by prologue. But where is the frame itself? */
380 if (must_adjust[SRP_REGNUM]) {
381 /* Function header saved SRP (r1), the return address. Frame starts
382 4 bytes down from where it was saved. */
383 frame_fp = frame_sp + fsr->regs[SRP_REGNUM] - 4;
384 fi->locals_pointer = frame_fp;
386 /* Function header didn't save SRP (r1), so we are in a leaf fn or
387 are otherwise confused. */
392 /* The locals are relative to the FP (whether it exists as an allocated
393 register, or just as an assumed offset from the SP) */
394 fi->locals_pointer = frame_fp;
396 /* The arguments are just above the SP as it was before we adjusted it
398 fi->args_pointer = frame_sp - sp_offset;
400 /* Now that we know the SP value used by the prologue, we know where
401 it saved all the registers. */
402 for (src = 0; src < 32; src++)
403 if (must_adjust[src])
404 fsr->regs[src] += frame_sp;
406 /* The saved value of the SP is always known. */
408 if (fsr->regs[SP_REGNUM] != 0
409 && fsr->regs[SP_REGNUM] != frame_sp - sp_offset)
410 fprintf_unfiltered(gdb_stderr, "Bad saved SP value %x != %x, offset %x!\n",
411 fsr->regs[SP_REGNUM],
412 frame_sp - sp_offset, sp_offset);
414 fsr->regs[SP_REGNUM] = frame_sp - sp_offset;
419 /* Given an ip value corresponding to the start of a function,
420 return the ip of the first instruction after the function
427 struct frame_saved_regs saved_regs_dummy;
428 struct symtab_and_line sal;
431 sal = find_pc_line (ip, 0);
432 limit = (sal.end) ? sal.end : 0xffffffff;
434 return (examine_prologue (ip, limit, (FRAME_ADDR) 0, &saved_regs_dummy,
435 (struct frame_info *)0 ));
438 /* Put here the code to store, into a struct frame_saved_regs,
439 the addresses of the saved registers of frame described by FRAME_INFO.
440 This includes special registers such as pc and fp saved in special
441 ways in the stack frame. sp is even more special:
442 the address we return for it IS the sp for the next frame.
444 We cache the result of doing this in the frame_cache_obstack, since
445 it is fairly expensive. */
448 frame_find_saved_regs (fi, fsr)
449 struct frame_info *fi;
450 struct frame_saved_regs *fsr;
452 register struct frame_saved_regs *cache_fsr;
453 extern struct obstack frame_cache_obstack;
455 struct symtab_and_line sal;
460 cache_fsr = (struct frame_saved_regs *)
461 obstack_alloc (&frame_cache_obstack,
462 sizeof (struct frame_saved_regs));
463 memset (cache_fsr, '\0', sizeof (struct frame_saved_regs));
466 /* Find the start and end of the function prologue. If the PC
467 is in the function prologue, we only consider the part that
468 has executed already. */
470 ip = get_pc_function_start (fi->pc);
471 sal = find_pc_line (ip, 0);
472 limit = (sal.end && sal.end < fi->pc) ? sal.end: fi->pc;
474 /* This will fill in fields in *fi as well as in cache_fsr. */
475 #ifdef SIGTRAMP_FRAME_FIXUP
476 if (fi->signal_handler_caller)
477 SIGTRAMP_FRAME_FIXUP(fi->frame);
479 examine_prologue (ip, limit, fi->frame, cache_fsr, fi);
480 #ifdef SIGTRAMP_SP_FIXUP
481 if (fi->signal_handler_caller && fi->fsr->regs[SP_REGNUM])
482 SIGTRAMP_SP_FIXUP(fi->fsr->regs[SP_REGNUM]);
490 /* Return the address of the locals block for the frame
491 described by FI. Returns 0 if the address is unknown.
492 NOTE! Frame locals are referred to by negative offsets from the
493 argument pointer, so this is the same as frame_args_address(). */
496 frame_locals_address (fi)
497 struct frame_info *fi;
499 struct frame_saved_regs fsr;
501 if (fi->args_pointer) /* Cached value is likely there. */
502 return fi->args_pointer;
504 /* Nope, generate it. */
506 get_frame_saved_regs (fi, &fsr);
508 return fi->args_pointer;
511 /* Return the address of the argument block for the frame
512 described by FI. Returns 0 if the address is unknown. */
515 frame_args_address (fi)
516 struct frame_info *fi;
518 struct frame_saved_regs fsr;
520 if (fi->args_pointer) /* Cached value is likely there. */
521 return fi->args_pointer;
523 /* Nope, generate it. */
525 get_frame_saved_regs (fi, &fsr);
527 return fi->args_pointer;
530 /* Return the saved PC from this frame.
532 If the frame has a memory copy of SRP_REGNUM, use that. If not,
533 just use the register SRP_REGNUM itself. */
536 frame_saved_pc (frame)
539 return read_next_frame_reg(frame, SRP_REGNUM);
543 /* I believe this is all obsolete call dummy stuff. */
545 pushed_size (prev_words, v)
549 switch (TYPE_CODE (VALUE_TYPE (v)))
551 case TYPE_CODE_VOID: /* Void type (values zero length) */
553 return 0; /* That was easy! */
555 case TYPE_CODE_PTR: /* Pointer type */
556 case TYPE_CODE_ENUM: /* Enumeration type */
557 case TYPE_CODE_INT: /* Integer type */
558 case TYPE_CODE_REF: /* C++ Reference types */
559 case TYPE_CODE_ARRAY: /* Array type, lower & upper bounds */
563 case TYPE_CODE_FLT: /* Floating type */
565 if (TYPE_LENGTH (VALUE_TYPE (v)) == 4)
568 /* Assume that it must be a double. */
569 if (prev_words & 1) /* at an odd-word boundary */
570 return 3; /* round to 8-byte boundary */
574 case TYPE_CODE_STRUCT: /* C struct or Pascal record */
575 case TYPE_CODE_UNION: /* C union or Pascal variant part */
577 return (((TYPE_LENGTH (VALUE_TYPE (v)) + 3) / 4) * 4);
579 case TYPE_CODE_FUNC: /* Function type */
580 case TYPE_CODE_SET: /* Pascal sets */
581 case TYPE_CODE_RANGE: /* Range (integers within bounds) */
582 case TYPE_CODE_STRING: /* String type */
583 case TYPE_CODE_MEMBER: /* Member type */
584 case TYPE_CODE_METHOD: /* Method type */
585 /* Don't know how to pass these yet. */
587 case TYPE_CODE_UNDEF: /* Not used; catches errors */
594 store_parm_word (address, val)
598 write_memory (address, (char *)&val, 4);
602 store_parm (prev_words, left_parm_addr, v)
603 unsigned int prev_words;
604 CORE_ADDR left_parm_addr;
607 CORE_ADDR start = left_parm_addr + (prev_words * 4);
608 int *val_addr = (int *)VALUE_CONTENTS(v);
610 switch (TYPE_CODE (VALUE_TYPE (v)))
612 case TYPE_CODE_VOID: /* Void type (values zero length) */
616 case TYPE_CODE_PTR: /* Pointer type */
617 case TYPE_CODE_ENUM: /* Enumeration type */
618 case TYPE_CODE_INT: /* Integer type */
619 case TYPE_CODE_ARRAY: /* Array type, lower & upper bounds */
620 case TYPE_CODE_REF: /* C++ Reference types */
622 store_parm_word (start, *val_addr);
625 case TYPE_CODE_FLT: /* Floating type */
627 if (TYPE_LENGTH (VALUE_TYPE (v)) == 4)
629 store_parm_word (start, *val_addr);
634 store_parm_word (start + ((prev_words & 1) * 4), val_addr[0]);
635 store_parm_word (start + ((prev_words & 1) * 4) + 4, val_addr[1]);
636 return 2 + (prev_words & 1);
639 case TYPE_CODE_STRUCT: /* C struct or Pascal record */
640 case TYPE_CODE_UNION: /* C union or Pascal variant part */
643 unsigned int words = (((TYPE_LENGTH (VALUE_TYPE (v)) + 3) / 4) * 4);
646 for (word = 0; word < words; word++)
647 store_parm_word (start + (word * 4), val_addr[word]);
656 /* This routine sets up all of the parameter values needed to make a pseudo
657 call. The name "push_parameters" is a misnomer on some archs,
658 because (on the m88k) most parameters generally end up being passed in
659 registers rather than on the stack. In this routine however, we do
660 end up storing *all* parameter values onto the stack (even if we will
661 realize later that some of these stores were unnecessary). */
663 #define FIRST_PARM_REGNUM 2
666 push_parameters (return_type, struct_conv, nargs, args)
667 struct type *return_type;
673 unsigned int p_words = 0;
674 CORE_ADDR left_parm_addr;
676 /* Start out by creating a space for the return value (if need be). We
677 only need to do this if the return value is a struct or union. If we
678 do make a space for a struct or union return value, then we must also
679 arrange for the base address of that space to go into r12, which is the
680 standard place to pass the address of the return value area to the
681 callee. Note that only structs and unions are returned in this fashion.
682 Ints, enums, pointers, and floats are returned into r2. Doubles are
683 returned into the register pair {r2,r3}. Note also that the space
684 reserved for a struct or union return value only has to be word aligned
685 (not double-word) but it is double-word aligned here anyway (just in
686 case that becomes important someday). */
688 switch (TYPE_CODE (return_type))
690 case TYPE_CODE_STRUCT:
691 case TYPE_CODE_UNION:
693 int return_bytes = ((TYPE_LENGTH (return_type) + 7) / 8) * 8;
696 rv_addr = read_register (SP_REGNUM) - return_bytes;
698 write_register (SP_REGNUM, rv_addr); /* push space onto the stack */
699 write_register (SRA_REGNUM, rv_addr);/* set return value register */
705 /* Here we make a pre-pass on the whole parameter list to figure out exactly
706 how many words worth of stuff we are going to pass. */
708 for (p_words = 0, parm_num = 0; parm_num < nargs; parm_num++)
709 p_words += pushed_size (p_words, value_arg_coerce (args[parm_num]));
711 /* Now, check to see if we have to round up the number of parameter words
712 to get up to the next 8-bytes boundary. This may be necessary because
713 of the software convention to always keep the stack aligned on an 8-byte
717 p_words++; /* round to 8-byte boundary */
719 /* Now figure out the absolute address of the leftmost parameter, and update
720 the stack pointer to point at that address. */
722 left_parm_addr = read_register (SP_REGNUM) - (p_words * 4);
723 write_register (SP_REGNUM, left_parm_addr);
725 /* Now we can go through all of the parameters (in left-to-right order)
726 and write them to their parameter stack slots. Note that we are not
727 really "pushing" the parameter values. The stack space for these values
728 was already allocated above. Now we are just filling it up. */
730 for (p_words = 0, parm_num = 0; parm_num < nargs; parm_num++)
732 store_parm (p_words, left_parm_addr, value_arg_coerce (args[parm_num]));
734 /* Now that we are all done storing the parameter values into the stack, we
735 must go back and load up the parameter registers with the values from the
736 corresponding stack slots. Note that in the two cases of (a) gaps in the
737 parameter word sequence causes by (otherwise) misaligned doubles, and (b)
738 slots correcponding to structs or unions, the work we do here in loading
739 some parameter registers may be unnecessary, but who cares? */
741 for (p_words = 0; p_words < 8; p_words++)
743 write_register (FIRST_PARM_REGNUM + p_words,
744 read_memory_integer (left_parm_addr + (p_words * 4), 4));
749 collect_returned_value (rval, value_type, struct_return, nargs, args)
751 struct type *value_type;
756 char retbuf[REGISTER_BYTES];
758 memcpy (retbuf, registers, REGISTER_BYTES);
759 *rval = value_being_returned (value_type, retbuf, struct_return);
764 /*start of lines added by kev*/
766 #define DUMMY_FRAME_SIZE 192
769 write_word (sp, word)
771 unsigned LONGEST word;
773 register int len = REGISTER_SIZE;
774 char buffer[MAX_REGISTER_RAW_SIZE];
776 store_unsigned_integer (buffer, len, word);
777 write_memory (sp, buffer, len);
781 m88k_push_dummy_frame()
783 register CORE_ADDR sp = read_register (SP_REGNUM);
787 sp -= DUMMY_FRAME_SIZE; /* allocate a bunch of space */
789 for (rn = 0, offset = 0; rn <= SP_REGNUM; rn++, offset+=4)
790 write_word (sp+offset, read_register(rn));
792 write_word (sp+offset, read_register (SXIP_REGNUM));
795 write_word (sp+offset, read_register (SNIP_REGNUM));
798 write_word (sp+offset, read_register (SFIP_REGNUM));
801 write_word (sp+offset, read_register (PSR_REGNUM));
804 write_word (sp+offset, read_register (FPSR_REGNUM));
807 write_word (sp+offset, read_register (FPCR_REGNUM));
810 write_register (SP_REGNUM, sp);
811 write_register (ACTUAL_FP_REGNUM, sp);
817 register FRAME frame = get_current_frame ();
818 register CORE_ADDR fp;
820 struct frame_saved_regs fsr;
821 struct frame_info *fi;
823 fi = get_frame_info (frame);
825 get_frame_saved_regs (fi, &fsr);
827 if (PC_IN_CALL_DUMMY (read_pc(), read_register(SP_REGNUM), FRAME_FP(fi)))
829 /* FIXME: I think get_frame_saved_regs should be handling this so
830 that we can deal with the saved registers properly (e.g. frame
831 1 is a call dummy, the user types "frame 2" and then "print $ps"). */
832 register CORE_ADDR sp = read_register (ACTUAL_FP_REGNUM);
835 for (regnum = 0, offset = 0; regnum <= SP_REGNUM; regnum++, offset+=4)
836 (void) write_register (regnum, read_memory_integer (sp+offset, 4));
838 write_register (SXIP_REGNUM, read_memory_integer (sp+offset, 4));
841 write_register (SNIP_REGNUM, read_memory_integer (sp+offset, 4));
844 write_register (SFIP_REGNUM, read_memory_integer (sp+offset, 4));
847 write_register (PSR_REGNUM, read_memory_integer (sp+offset, 4));
850 write_register (FPSR_REGNUM, read_memory_integer (sp+offset, 4));
853 write_register (FPCR_REGNUM, read_memory_integer (sp+offset, 4));
859 for (regnum = FP_REGNUM ; regnum > 0 ; regnum--)
860 if (fsr.regs[regnum])
861 write_register (regnum,
862 read_memory_integer (fsr.regs[regnum], 4));
863 write_pc(frame_saved_pc(frame));
865 reinit_frame_cache ();