-/* Machine-dependent code which would otherwise be in inflow.c and core.c,
- for GDB, the GNU debugger.
- Copyright (C) 1986, 1987, 1989 Free Software Foundation, Inc.
- This code is for the sparc cpu.
+/* Target-dependent code for the SPARC for GDB, the GNU debugger.
+ Copyright 1986, 1987, 1989, 1991, 1992, 1993 Free Software Foundation, Inc.
This file is part of GDB.
-GDB is free software; you can redistribute it and/or modify
+This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 1, or (at your option)
-any later version.
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
-GDB is distributed in the hope that it will be useful,
+This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
-along with GDB; see the file COPYING. If not, write to
-the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. */
+along with this program; if not, write to the Free Software
+Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
-#include <stdio.h>
#include "defs.h"
-#include "param.h"
#include "frame.h"
#include "inferior.h"
#include "obstack.h"
-#include "signame.h"
#include "target.h"
#include "ieee-float.h"
-#include <sys/param.h>
-#include <sys/dir.h>
-#include <sys/user.h>
-#include <signal.h>
-#include <sys/ioctl.h>
-#include <fcntl.h>
+#include "symfile.h" /* for objfiles.h */
+#include "objfiles.h" /* for find_pc_section */
-#include <sys/ptrace.h>
-#include <machine/reg.h>
-
-#include <sys/file.h>
-#include <sys/stat.h>
-#include <sys/core.h>
+#ifdef USE_PROC_FS
+#include <sys/procfs.h>
+#endif
#include "gdbcore.h"
/* From infrun.c */
extern int stop_after_trap;
+/* We don't store all registers immediately when requested, since they
+ get sent over in large chunks anyway. Instead, we accumulate most
+ of the changes and send them over once. "deferred_stores" keeps
+ track of which sets of registers we have locally-changed copies of,
+ so we only need send the groups that have changed. */
+
+int deferred_stores = 0; /* Cumulates stores we want to do eventually. */
+
typedef enum
{
- Error, not_branch, bicc, bicca, ba, baa, ticc, ta,
+ Error, not_branch, bicc, bicca, ba, baa, ticc, ta
} branch_type;
/* Simulate single-step ptrace call for sun4. Code written by Gary
int one_stepped;
+/* single_step() is called just before we want to resume the inferior,
+ if we want to single-step it but there is no hardware or kernel single-step
+ support (as on all SPARCs). We find all the possible targets of the
+ coming instruction and breakpoint them.
+
+ single_step is also called just after the inferior stops. If we had
+ set up a simulated single-step, we undo our damage. */
+
void
-single_step (signal)
- int signal;
+single_step (ignore)
+ int ignore; /* pid, but we don't need it */
{
branch_type br, isannulled();
CORE_ADDR pc;
target_insert_breakpoint (target, break_mem[2]);
}
- /* Let it go */
- ptrace (7, inferior_pid, 1, signal);
+ /* We are ready to let it go */
one_stepped = 1;
return;
}
}
}
\f
-/*
- * Find the pc saved in frame FRAME.
- */
+#define FRAME_SAVED_L0 0 /* Byte offset from SP */
+#define FRAME_SAVED_I0 (8 * REGISTER_RAW_SIZE (0)) /* Byte offset from SP */
+
+CORE_ADDR
+sparc_frame_chain (thisframe)
+ FRAME thisframe;
+{
+ REGISTER_TYPE retval;
+ int err;
+ CORE_ADDR addr;
+
+ addr = thisframe->frame + FRAME_SAVED_I0 +
+ REGISTER_RAW_SIZE (FP_REGNUM) * (FP_REGNUM - I0_REGNUM);
+ err = target_read_memory (addr, (char *) &retval, sizeof (REGISTER_TYPE));
+ if (err)
+ return 0;
+ return extract_address (&retval, sizeof (retval));
+}
+
+CORE_ADDR
+sparc_extract_struct_value_address (regbuf)
+ char regbuf[REGISTER_BYTES];
+{
+ /* FIXME, handle byte swapping */
+ return read_memory_integer (((int *)(regbuf))[SP_REGNUM]+(16*4),
+ sizeof (CORE_ADDR));
+}
+
+/* Find the pc saved in frame FRAME. */
+
CORE_ADDR
frame_saved_pc (frame)
FRAME frame;
{
- CORE_ADDR prev_pc;
+ REGISTER_TYPE retval;
+ CORE_ADDR addr;
- /* If it's at the bottom, the return value's stored in i7/rp */
- if (get_current_frame () == frame)
- prev_pc = GET_RWINDOW_REG (read_register (SP_REGNUM), rw_in[7]);
- else
- /* Wouldn't this always work? This would allow this routine to
- be completely a macro. */
- prev_pc = GET_RWINDOW_REG (frame->bottom, rw_in[7]);
-
- return PC_ADJUST (prev_pc);
+ addr = (frame->bottom + FRAME_SAVED_I0 +
+ REGISTER_RAW_SIZE (I7_REGNUM) * (I7_REGNUM - I0_REGNUM));
+ read_memory (addr, (char *) &retval, sizeof (REGISTER_TYPE));
+ return PC_ADJUST (extract_address (&retval, sizeof (REGISTER_TYPE)));
}
/*
* difficulty.
*/
FRAME
-setup_arbitrary_frame (frame, stack)
- FRAME_ADDR frame, stack;
+setup_arbitrary_frame (argc, argv)
+ int argc;
+ FRAME_ADDR *argv;
{
- FRAME fid = create_new_frame (frame, 0);
+ FRAME fid;
+
+ if (argc != 2)
+ error ("Sparc frame specifications require two arguments: fp and sp");
+
+ fid = create_new_frame (argv[0], 0);
if (!fid)
fatal ("internal: create_new_frame returned invalid frame id");
- fid->bottom = stack;
-
+ fid->bottom = argv[1];
+ fid->pc = FRAME_SAVED_PC (fid);
return fid;
}
-
-/*
- * This routine appears to be passed a size by which to increase the
- * stack. It then executes a save instruction in the inferior to
- * increase the stack by this amount. Only the register window system
- * should be affected by this; the program counter & etc. will not be.
- *
- * This instructions used for this purpose are:
- *
- * sethi %hi(0x0),g1 *
- * add g1,0x1ee0,g1 *
- * save sp,g1,sp
- * sethi %hi(0x0),g1 *
- * add g1,0x1ee0,g1 *
- * t g0,0x1,o0
- * sethi %hi(0x0),g0 (nop)
- *
- * I presume that these set g1 to be the negative of the size, do a
- * save (putting the stack pointer at sp - size) and restore the
- * original contents of g1. A * indicates that the actual value of
- * the instruction is modified below.
- */
-static int save_insn_opcodes[] = {
- 0x03000000, 0x82007ee0, 0x9de38001, 0x03000000,
- 0x82007ee0, 0x91d02001, 0x01000000 };
-
-/* Neither do_save_insn or do_restore_insn save stack configuration
- (current_frame, etc),
- since the stack is in an indeterminate state through the call to
- each of them. That responsibility of the routine which calls them. */
-
-static void
-do_save_insn (size)
- int size;
-{
- int g1 = read_register (G1_REGNUM);
- CORE_ADDR sp = read_register (SP_REGNUM);
- CORE_ADDR pc = read_register (PC_REGNUM);
- CORE_ADDR npc = read_register (NPC_REGNUM);
- CORE_ADDR fake_pc = sp - sizeof (save_insn_opcodes);
- struct inferior_status inf_status;
-
- save_inferior_status (&inf_status, 0); /* Don't restore stack info */
- /*
- * See above.
- */
- save_insn_opcodes[0] = 0x03000000 | ((-size >> 10) & 0x3fffff);
- save_insn_opcodes[1] = 0x82006000 | (-size & 0x3ff);
- save_insn_opcodes[3] = 0x03000000 | ((g1 >> 10) & 0x3fffff);
- save_insn_opcodes[4] = 0x82006000 | (g1 & 0x3ff);
- write_memory (fake_pc, (char *)save_insn_opcodes, sizeof (save_insn_opcodes));
-
- clear_proceed_status ();
- stop_after_trap = 1;
- proceed (fake_pc, 0, 0);
-
- write_register (PC_REGNUM, pc);
- write_register (NPC_REGNUM, npc);
- restore_inferior_status (&inf_status);
-}
-
-/*
- * This routine takes a program counter value. It restores the
- * register window system to the frame above the current one.
- * THIS ROUTINE CLOBBERS PC AND NPC IN THE TARGET!
- */
-
-/* The following insns translate to:
-
- restore %g0,%g0,%g0
- t %g0,1
- sethi %hi(0),%g0 */
+/* Given a pc value, skip it forward past the function prologue by
+ disassembling instructions that appear to be a prologue.
-static int restore_insn_opcodes[] = { 0x81e80000, 0x91d02001, 0x01000000 };
+ If FRAMELESS_P is set, we are only testing to see if the function
+ is frameless. This allows a quicker answer.
-static void
-do_restore_insn ()
-{
- CORE_ADDR sp = read_register (SP_REGNUM);
- CORE_ADDR fake_pc = sp - sizeof (restore_insn_opcodes);
- struct inferior_status inf_status;
-
- save_inferior_status (&inf_status, 0); /* Don't restore stack info */
-
- write_memory (fake_pc, (char *)restore_insn_opcodes,
- sizeof (restore_insn_opcodes));
-
- clear_proceed_status ();
- stop_after_trap = 1;
- proceed (fake_pc, 0, 0);
-
- restore_inferior_status (&inf_status);
-}
-
-/* This routine should be more specific in it's actions; making sure
- that it uses the same register in the initial prologue section.
- Also, FIXME-SOON, it should recognize leaf functions as ones without
- a SAVE in the prologue, and pass that info back to the caller so the
- PC and arguments can be properly located. */
+ This routine should be more specific in its actions; making sure
+ that it uses the same register in the initial prologue section. */
CORE_ADDR
-skip_prologue (pc)
- CORE_ADDR pc;
+skip_prologue (start_pc, frameless_p)
+ CORE_ADDR start_pc;
+ int frameless_p;
{
union
{
int i;
} x;
int dest = -1;
+ CORE_ADDR pc = start_pc;
x.i = read_memory_integer (pc, 4);
/* Recognize an add immediate value to register to either %g1 or
the destination register recorded above. Actually, this might
- well recognize several different arithmetic operations. */
+ well recognize several different arithmetic operations.
+ It doesn't check that rs1 == rd because in theory "sub %g0, 5, %g1"
+ followed by "save %sp, %g1, %sp" is a valid prologue (Not that
+ I imagine any compiler really does that, however). */
if (x.add.op == 2 && x.add.i && (x.add.rd == 1 || x.add.rd == dest))
{
pc += 4;
if (x.add.op == 2 && (x.add.op3 ^ 32) == 28)
{
pc += 4;
+ if (frameless_p) /* If the save is all we care about, */
+ return pc; /* return before doing more work */
x.i = read_memory_integer (pc, 4);
}
+ else
+ {
+ /* Without a save instruction, it's not a prologue. */
+ return start_pc;
+ }
/* Now we need to recognize stores into the frame from the input
registers. This recognizes all non alternate stores of input
if (!fid)
fatal ("Bad frame info struct in FRAME_FIND_SAVED_REGS");
- bzero (saved_regs_addr, sizeof (*saved_regs_addr));
+ memset (saved_regs_addr, 0, sizeof (*saved_regs_addr));
/* Old test.
if (fi->pc >= frame - CALL_DUMMY_LENGTH - 0x140
/* Push an empty stack frame, and record in it the current PC, regs, etc.
- Note that the write's are of registers in the context of the newly
- pushed frame. Thus the the fp*'s, the g*'s, the i*'s, and
- the randoms, of the new frame, are being saved. The locals and outs
+ We save the non-windowed registers and the ins. The locals and outs
are new; they don't need to be saved. The i's and l's of
- the last frame were saved by the do_save_insn in the register
- file (now on the stack, since a context switch happended imm after).
+ the last frame were already saved on the stack
- The return pointer register %i7 does not have
- the pc saved into it (return from this frame will be accomplished
- by a POP_FRAME). In fact, we must leave it unclobbered, since we
- must preserve it in the calling routine except across call instructions. */
+ The return pointer register %i7 does not have the pc saved into it
+ (return from this frame will be accomplished by a POP_FRAME). In
+ fact, we must leave it unclobbered, since we must preserve it in
+ the calling routine except across call instructions. I'm not sure
+ the preceding sentence is true; isn't it based on confusing the %i7
+ saved in the dummy frame versus the one saved in the frame of the
+ calling routine? */
/* Definitely see tm-sparc.h for more doc of the frame format here. */
void
sparc_push_dummy_frame ()
{
- CORE_ADDR fp;
+ CORE_ADDR sp;
char register_temp[REGISTER_BYTES];
- do_save_insn (0x140); /* FIXME where does this value come from? */
- fp = read_register (FP_REGNUM);
+ sp = read_register (SP_REGNUM);
- read_register_bytes (REGISTER_BYTE (FP0_REGNUM), register_temp, 32 * 4);
- write_memory (fp - 0x80, register_temp, 32 * 4);
+ read_register_bytes (REGISTER_BYTE (FP0_REGNUM), register_temp,
+ REGISTER_RAW_SIZE (FP0_REGNUM) * 32);
+ write_memory (sp - 0x80, register_temp, REGISTER_RAW_SIZE (FP0_REGNUM) * 32);
- read_register_bytes (REGISTER_BYTE (G0_REGNUM), register_temp, 8 * 4);
- write_memory (fp - 0xa0, register_temp, 8 * 4);
+ read_register_bytes (REGISTER_BYTE (G0_REGNUM), register_temp,
+ REGISTER_RAW_SIZE (G0_REGNUM) * 8);
+ write_memory (sp - 0xa0, register_temp, REGISTER_RAW_SIZE (G0_REGNUM) * 8);
- read_register_bytes (REGISTER_BYTE (I0_REGNUM), register_temp, 8 * 4);
- write_memory (fp - 0xc0, register_temp, 8 * 4);
+ read_register_bytes (REGISTER_BYTE (O0_REGNUM), register_temp,
+ REGISTER_RAW_SIZE (O0_REGNUM) * 8);
+ write_memory (sp - 0xc0, register_temp, REGISTER_RAW_SIZE (O0_REGNUM) * 8);
/* Y, PS, WIM, TBR, PC, NPC, FPS, CPS regs */
- read_register_bytes (REGISTER_BYTE (Y_REGNUM), register_temp, 8 * 4);
- write_memory (fp - 0xe0, register_temp, 8 * 4);
+ read_register_bytes (REGISTER_BYTE (Y_REGNUM), register_temp,
+ REGISTER_RAW_SIZE (Y_REGNUM) * 8);
+ write_memory (sp - 0xe0, register_temp, REGISTER_RAW_SIZE (Y_REGNUM) * 8);
+
+ {
+ CORE_ADDR old_sp = sp;
+
+ /* Now move the stack pointer (equivalent to the add part of a save
+ instruction). */
+ sp -= 0x140;
+ write_register (SP_REGNUM, sp);
+
+ /* Now make sure that the frame pointer we save in the new frame points
+ to the old frame (equivalent to the register window shift part of
+ a save instruction). Need to do this after the write to the sp, or
+ else this might get written into the wrong set of saved ins&locals. */
+ write_register (FP_REGNUM, old_sp);
+ }
}
/* Discard from the stack the innermost frame, restoring all saved registers.
fi = get_frame_info (frame);
get_frame_saved_regs (fi, &fsr);
- do_restore_insn ();
if (fsr.regs[FP0_REGNUM])
{
read_memory (fsr.regs[FP0_REGNUM], raw_buffer, 32 * 4);
}
if (fsr.regs[I0_REGNUM])
{
+ CORE_ADDR sp;
+
+ char reg_temp[REGISTER_BYTES];
+
read_memory (fsr.regs[I0_REGNUM], raw_buffer, 8 * 4);
- write_register_bytes (REGISTER_BYTE (O0_REGNUM), raw_buffer, 8 * 4);
+
+ /* Get the ins and locals which we are about to restore. Just
+ moving the stack pointer is all that is really needed, except
+ store_inferior_registers is then going to write the ins and
+ locals from the registers array, so we need to muck with the
+ registers array. */
+ sp = fsr.regs[SP_REGNUM];
+ read_memory (sp, reg_temp, REGISTER_RAW_SIZE (L0_REGNUM) * 16);
+
+ /* Restore the out registers.
+ Among other things this writes the new stack pointer. */
+ write_register_bytes (REGISTER_BYTE (O0_REGNUM), raw_buffer,
+ REGISTER_RAW_SIZE (O0_REGNUM) * 8);
+
+ write_register_bytes (REGISTER_BYTE (L0_REGNUM), reg_temp,
+ REGISTER_RAW_SIZE (L0_REGNUM) * 16);
}
if (fsr.regs[PS_REGNUM])
write_register (PS_REGNUM, read_memory_integer (fsr.regs[PS_REGNUM], 4));
read_pc ()));
}
+/* On the Sun 4 under SunOS, the compile will leave a fake insn which
+ encodes the structure size being returned. If we detect such
+ a fake insn, step past it. */
+
+CORE_ADDR
+sparc_pc_adjust(pc)
+ CORE_ADDR pc;
+{
+ unsigned long insn;
+ char buf[4];
+ int err;
+
+ err = target_read_memory (pc + 8, buf, sizeof(long));
+ insn = extract_unsigned_integer (buf, 4);
+ if ((err == 0) && (insn & 0xfffffe00) == 0)
+ return pc+12;
+ else
+ return pc+8;
+}
+
+
/* Structure of SPARC extended floating point numbers.
This information is not currently used by GDB, since no current SPARC
implementations support extended float. */
-const struct ext_format ext_format_sparc[] = {
+const struct ext_format ext_format_sparc = {
/* tot sbyte smask expbyte manbyte */
- { 16, 0, 0x80, 0,1, 4,8 }, /* sparc */
+ 16, 0, 0x80, 0,1, 4,8, /* sparc */
};
+\f
+#ifdef USE_PROC_FS /* Target dependent support for /proc */
+
+/* The /proc interface divides the target machine's register set up into
+ two different sets, the general register set (gregset) and the floating
+ point register set (fpregset). For each set, there is an ioctl to get
+ the current register set and another ioctl to set the current values.
+
+ The actual structure passed through the ioctl interface is, of course,
+ naturally machine dependent, and is different for each set of registers.
+ For the sparc for example, the general register set is typically defined
+ by:
+
+ typedef int gregset_t[38];
+
+ #define R_G0 0
+ ...
+ #define R_TBR 37
+
+ and the floating point set by:
+
+ typedef struct prfpregset {
+ union {
+ u_long pr_regs[32];
+ double pr_dregs[16];
+ } pr_fr;
+ void * pr_filler;
+ u_long pr_fsr;
+ u_char pr_qcnt;
+ u_char pr_q_entrysize;
+ u_char pr_en;
+ u_long pr_q[64];
+ } prfpregset_t;
+
+ These routines provide the packing and unpacking of gregset_t and
+ fpregset_t formatted data.
+
+ */
+
+
+/* Given a pointer to a general register set in /proc format (gregset_t *),
+ unpack the register contents and supply them as gdb's idea of the current
+ register values. */
+
+void
+supply_gregset (gregsetp)
+prgregset_t *gregsetp;
+{
+ register int regi;
+ register prgreg_t *regp = (prgreg_t *) gregsetp;
+
+ /* GDB register numbers for Gn, On, Ln, In all match /proc reg numbers. */
+ for (regi = G0_REGNUM ; regi <= I7_REGNUM ; regi++)
+ {
+ supply_register (regi, (char *) (regp + regi));
+ }
+
+ /* These require a bit more care. */
+ supply_register (PS_REGNUM, (char *) (regp + R_PS));
+ supply_register (PC_REGNUM, (char *) (regp + R_PC));
+ supply_register (NPC_REGNUM,(char *) (regp + R_nPC));
+ supply_register (Y_REGNUM, (char *) (regp + R_Y));
+}
+
+void
+fill_gregset (gregsetp, regno)
+prgregset_t *gregsetp;
+int regno;
+{
+ int regi;
+ register prgreg_t *regp = (prgreg_t *) gregsetp;
+ extern char registers[];
+
+ for (regi = 0 ; regi <= R_I7 ; regi++)
+ {
+ if ((regno == -1) || (regno == regi))
+ {
+ *(regp + regi) = *(int *) ®isters[REGISTER_BYTE (regi)];
+ }
+ }
+ if ((regno == -1) || (regno == PS_REGNUM))
+ {
+ *(regp + R_PS) = *(int *) ®isters[REGISTER_BYTE (PS_REGNUM)];
+ }
+ if ((regno == -1) || (regno == PC_REGNUM))
+ {
+ *(regp + R_PC) = *(int *) ®isters[REGISTER_BYTE (PC_REGNUM)];
+ }
+ if ((regno == -1) || (regno == NPC_REGNUM))
+ {
+ *(regp + R_nPC) = *(int *) ®isters[REGISTER_BYTE (NPC_REGNUM)];
+ }
+ if ((regno == -1) || (regno == Y_REGNUM))
+ {
+ *(regp + R_Y) = *(int *) ®isters[REGISTER_BYTE (Y_REGNUM)];
+ }
+}
+
+#if defined (FP0_REGNUM)
+
+/* Given a pointer to a floating point register set in /proc format
+ (fpregset_t *), unpack the register contents and supply them as gdb's
+ idea of the current floating point register values. */
+
+void
+supply_fpregset (fpregsetp)
+prfpregset_t *fpregsetp;
+{
+ register int regi;
+ char *from;
+
+ for (regi = FP0_REGNUM ; regi < FP0_REGNUM+32 ; regi++)
+ {
+ from = (char *) &fpregsetp->pr_fr.pr_regs[regi-FP0_REGNUM];
+ supply_register (regi, from);
+ }
+ supply_register (FPS_REGNUM, (char *) &(fpregsetp->pr_fsr));
+}
+
+/* Given a pointer to a floating point register set in /proc format
+ (fpregset_t *), update the register specified by REGNO from gdb's idea
+ of the current floating point register set. If REGNO is -1, update
+ them all. */
+
+void
+fill_fpregset (fpregsetp, regno)
+prfpregset_t *fpregsetp;
+int regno;
+{
+ int regi;
+ char *to;
+ char *from;
+ extern char registers[];
+
+ for (regi = FP0_REGNUM ; regi < FP0_REGNUM+32 ; regi++)
+ {
+ if ((regno == -1) || (regno == regi))
+ {
+ from = (char *) ®isters[REGISTER_BYTE (regi)];
+ to = (char *) &fpregsetp->pr_fr.pr_regs[regi-FP0_REGNUM];
+ memcpy (to, from, REGISTER_RAW_SIZE (regi));
+ }
+ }
+ if ((regno == -1) || (regno == FPS_REGNUM))
+ {
+ fpregsetp->pr_fsr = *(int *) ®isters[REGISTER_BYTE (FPS_REGNUM)];
+ }
+}
+
+#endif /* defined (FP0_REGNUM) */
+
+#endif /* USE_PROC_FS */
+
+
+#ifdef GET_LONGJMP_TARGET
+
+/* Figure out where the longjmp will land. We expect that we have just entered
+ longjmp and haven't yet setup the stack frame, so the args are still in the
+ output regs. %o0 (O0_REGNUM) points at the jmp_buf structure from which we
+ extract the pc (JB_PC) that we will land at. The pc is copied into ADDR.
+ This routine returns true on success */
+
+int
+get_longjmp_target(pc)
+ CORE_ADDR *pc;
+{
+ CORE_ADDR jb_addr;
+#define LONGJMP_TARGET_SIZE 4
+ char buf[LONGJMP_TARGET_SIZE];
+
+ jb_addr = read_register(O0_REGNUM);
+
+ if (target_read_memory(jb_addr + JB_PC * JB_ELEMENT_SIZE, buf,
+ LONGJMP_TARGET_SIZE))
+ return 0;
+
+ *pc = extract_address (buf, LONGJMP_TARGET_SIZE);
+
+ return 1;
+}
+#endif /* GET_LONGJMP_TARGET */
+
+/* So far used only for sparc solaris. In sparc solaris, we recognize
+ a trampoline by it's section name. That is, if the pc is in a
+ section named ".plt" then we are in a trampline. */
+
+int
+in_solib_trampoline(pc, name)
+ CORE_ADDR pc;
+ char *name;
+{
+ struct obj_section *s;
+ int retval = 0;
+
+ s = find_pc_section(pc);
+
+ retval = (s != NULL
+ && s->sec_ptr->name != NULL
+ && STREQ (s->sec_ptr->name, ".plt"));
+ return(retval);
+}
+