From 6c633d454a09f6fd5f85f54d46f57a733967c667 Mon Sep 17 00:00:00 2001 From: Bob Wilson <bob.wilson@acm.org> Date: Fri, 18 Jan 2008 01:37:53 +0000 Subject: [PATCH] unwind-dw2-xtensa.h (_Unwind_FrameState): Remove pc field and add signal_ra. * config/xtensa/unwind-dw2-xtensa.h (_Unwind_FrameState): Remove pc field and add signal_ra. * config/xtensa/unwind-dw2-xtensa.c (uw_frame_state_for): Remove assignments to frame state pc. Move end of stack check after MD_FALLBACK_FRAME_STATE_FOR. (uw_update_context_1): Use frame state signal_regs if set, instead of checking signal_frame flag. (uw_update_context): Use frame state signal_ra if set. * config/xtensa/linux.h (MD_UNWIND_SUPPORT): Define. * config/xtensa/linux-unwind.h: New file. From-SVN: r131622 --- gcc/ChangeLog | 13 ++++ gcc/config/xtensa/linux-unwind.h | 101 ++++++++++++++++++++++++++ gcc/config/xtensa/linux.h | 6 +- gcc/config/xtensa/unwind-dw2-xtensa.c | 29 +++++--- gcc/config/xtensa/unwind-dw2-xtensa.h | 6 +- 5 files changed, 138 insertions(+), 17 deletions(-) create mode 100644 gcc/config/xtensa/linux-unwind.h diff --git a/gcc/ChangeLog b/gcc/ChangeLog index 2b1662a25967..987a47bf6b8c 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,3 +1,16 @@ +2007-01-17 Bob Wilson <bob.wilson@acm.org> + + * config/xtensa/unwind-dw2-xtensa.h (_Unwind_FrameState): Remove pc + field and add signal_ra. + * config/xtensa/unwind-dw2-xtensa.c (uw_frame_state_for): Remove + assignments to frame state pc. Move end of stack check after + MD_FALLBACK_FRAME_STATE_FOR. + (uw_update_context_1): Use frame state signal_regs if set, instead + of checking signal_frame flag. + (uw_update_context): Use frame state signal_ra if set. + * config/xtensa/linux.h (MD_UNWIND_SUPPORT): Define. + * config/xtensa/linux-unwind.h: New file. + 2007-01-18 Bernhard Fischer <aldot@gcc.gnu.org> * modulo-sched.c (get_sched_window): Fix comment typo. diff --git a/gcc/config/xtensa/linux-unwind.h b/gcc/config/xtensa/linux-unwind.h new file mode 100644 index 000000000000..18daff2d133c --- /dev/null +++ b/gcc/config/xtensa/linux-unwind.h @@ -0,0 +1,101 @@ +/* DWARF2 EH unwinding support for Xtensa. + Copyright (C) 2008 Free Software Foundation, Inc. + +This file is part of GCC. + +GCC 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 2, or (at your option) +any later version. + +In addition to the permissions in the GNU General Public License, the +Free Software Foundation gives you unlimited permission to link the +compiled version of this file with other programs, and to distribute +those programs without any restriction coming from the use of this +file. (The General Public License restrictions do apply in other +respects; for example, they cover modification of the file, and +distribution when not linked into another program.) + +GCC 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 GCC; see the file COPYING. If not, write to +the Free Software Foundation, 51 Franklin Street, Fifth Floor, +Boston, MA 02110-1301, USA. */ + +/* Do code reading to identify a signal frame, and set the frame + state data appropriately. See unwind-dw2-xtensa.c for the structs. + Don't use this at all if inhibit_libc is used. */ + +#ifndef inhibit_libc + +#include <signal.h> +#include <sys/ucontext.h> + +/* Encoded bytes for Xtensa instructions: + movi a2, __NR_rt_sigreturn + syscall + entry (first byte only) + Some of the bytes are endian-dependent. */ + +#define MOVI_BYTE0 0x22 +#define MOVI_BYTE2 225 /* __NR_rt_sigreturn */ +#define SYSC_BYTE0 0 +#define SYSC_BYTE2 0 + +#ifdef __XTENSA_EB__ +#define MOVI_BYTE1 0x0a +#define SYSC_BYTE1 0x05 +#define ENTRY_BYTE 0x6c +#else +#define MOVI_BYTE1 0xa0 +#define SYSC_BYTE1 0x50 +#define ENTRY_BYTE 0x36 +#endif + +#define MD_FALLBACK_FRAME_STATE_FOR xtensa_fallback_frame_state + +static _Unwind_Reason_Code +xtensa_fallback_frame_state (struct _Unwind_Context *context, + _Unwind_FrameState *fs) +{ + unsigned char *pc = context->ra; + struct sigcontext *sc; + + struct rt_sigframe { + struct siginfo info; + struct ucontext uc; + } *rt_; + + /* movi a2, __NR_rt_sigreturn; syscall */ + if (pc[0] != MOVI_BYTE0 + || pc[1] != MOVI_BYTE1 + || pc[2] != MOVI_BYTE2 + || pc[3] != SYSC_BYTE0 + || pc[4] != SYSC_BYTE1 + || pc[5] != SYSC_BYTE2) + return _URC_END_OF_STACK; + + rt_ = context->sp; + sc = &rt_->uc.uc_mcontext; + fs->signal_regs = (_Unwind_Word *) sc->sc_a; + + /* If the signal arrived just before an ENTRY instruction, find the return + address and pretend the signal arrived before executing the CALL. */ + if (*(unsigned char *) sc->sc_pc == ENTRY_BYTE) + { + unsigned callinc = (sc->sc_ps >> 16) & 3; + fs->signal_ra = ((sc->sc_a[callinc << 2] & XTENSA_RA_FIELD_MASK) + | context->ra_high_bits) - 3; + } + else + fs->signal_ra = sc->sc_pc; + + fs->signal_frame = 1; + return _URC_NO_REASON; +} + +#endif /* ifdef inhibit_libc */ diff --git a/gcc/config/xtensa/linux.h b/gcc/config/xtensa/linux.h index 6a2c81a1d5dc..69ab626b2011 100644 --- a/gcc/config/xtensa/linux.h +++ b/gcc/config/xtensa/linux.h @@ -1,6 +1,7 @@ /* Xtensa Linux configuration. Derived from the configuration for GCC for Intel i386 running Linux. - Copyright (C) 2001, 2002, 2003, 2006, 2007 Free Software Foundation, Inc. + Copyright (C) 2001, 2002, 2003, 2006, 2007, 2008 + Free Software Foundation, Inc. This file is part of GCC. @@ -59,3 +60,6 @@ along with GCC; see the file COPYING3. If not see /* Always enable "-fpic" for Xtensa Linux. */ #define XTENSA_ALWAYS_PIC 1 + +#define MD_UNWIND_SUPPORT "config/xtensa/linux-unwind.h" + diff --git a/gcc/config/xtensa/unwind-dw2-xtensa.c b/gcc/config/xtensa/unwind-dw2-xtensa.c index 1dd4f9dee3f1..22b492f9eadf 100644 --- a/gcc/config/xtensa/unwind-dw2-xtensa.c +++ b/gcc/config/xtensa/unwind-dw2-xtensa.c @@ -1,6 +1,6 @@ /* DWARF2 exception handling and frame unwinding for Xtensa. Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, - 2007 + 2007, 2008 Free Software Foundation, Inc. This file is part of GCC. @@ -325,10 +325,6 @@ uw_frame_state_for (struct _Unwind_Context *context, _Unwind_FrameState *fs) memset (fs, 0, sizeof (*fs)); context->lsda = 0; - ra_ptr = context->reg[0]; - if (ra_ptr && *ra_ptr == 0) - return _URC_END_OF_STACK; - fde = _Unwind_Find_FDE (context->ra + _Unwind_IsSignalFrame (context) - 1, &context->bases); if (fde == NULL) @@ -341,16 +337,13 @@ uw_frame_state_for (struct _Unwind_Context *context, _Unwind_FrameState *fs) reason = MD_FALLBACK_FRAME_STATE_FOR (context, fs); if (reason != _URC_END_OF_STACK) return reason; +#endif /* The frame was not recognized and handled by the fallback function, but it is not really the end of the stack. Fall through here and unwind it anyway. */ -#endif - fs->pc = context->ra; } else { - fs->pc = context->bases.func; - cie = get_cie (fde); if (extract_cie_info (cie, context, fs) == NULL) /* CIE contained unknown augmentation. */ @@ -373,6 +366,15 @@ uw_frame_state_for (struct _Unwind_Context *context, _Unwind_FrameState *fs) } } + /* Check for the end of the stack. This needs to be checked after + the MD_FALLBACK_FRAME_STATE_FOR check for signal frames because + the contents of context->reg[0] are undefined at a signal frame, + and register a0 may appear to be zero. (The return address in + context->ra comes from register a4 or a8). */ + ra_ptr = context->reg[0]; + if (ra_ptr && *ra_ptr == 0) + return _URC_END_OF_STACK; + /* Find the window size from the high bits of the return address. */ if (ra_ptr) window_size = (*ra_ptr >> 30) * 4; @@ -391,7 +393,7 @@ uw_update_context_1 (struct _Unwind_Context *context, _Unwind_FrameState *fs) _Unwind_Word *sp, *cfa, *next_cfa; int i; - if (fs->signal_frame) + if (fs->signal_regs) { cfa = (_Unwind_Word *) fs->signal_regs[1]; next_cfa = (_Unwind_Word *) cfa[-3]; @@ -437,8 +439,11 @@ uw_update_context (struct _Unwind_Context *context, _Unwind_FrameState *fs) /* Compute the return address now, since the return address column can change from frame to frame. */ - context->ra = (void *) ((_Unwind_GetGR (context, fs->retaddr_column) - & XTENSA_RA_FIELD_MASK) | context->ra_high_bits); + if (fs->signal_ra != 0) + context->ra = (void *) fs->signal_ra; + else + context->ra = (void *) ((_Unwind_GetGR (context, fs->retaddr_column) + & XTENSA_RA_FIELD_MASK) | context->ra_high_bits); } static void diff --git a/gcc/config/xtensa/unwind-dw2-xtensa.h b/gcc/config/xtensa/unwind-dw2-xtensa.h index 99341172eac4..f88f7f3a84ab 100644 --- a/gcc/config/xtensa/unwind-dw2-xtensa.h +++ b/gcc/config/xtensa/unwind-dw2-xtensa.h @@ -1,5 +1,5 @@ /* DWARF2 frame unwind data structure for Xtensa. - Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2007 + Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2007, 2008 Free Software Foundation, Inc. This file is part of GCC. @@ -39,9 +39,6 @@ _Unwind_FrameState. */ typedef struct { - /* The PC described by the current frame state. */ - void *pc; - /* The information we care about from the CIE/FDE. */ _Unwind_Personality_Fn personality; _Unwind_Word retaddr_column; @@ -53,5 +50,6 @@ typedef struct /* Saved registers for a signal frame. */ _Unwind_Word *signal_regs; + _Unwind_Word signal_ra; } _Unwind_FrameState; -- GitLab