1*e4b17023SJohn Marino /* Implements exception handling.
2*e4b17023SJohn Marino Copyright (C) 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3*e4b17023SJohn Marino 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011
4*e4b17023SJohn Marino Free Software Foundation, Inc.
5*e4b17023SJohn Marino Contributed by Mike Stump <mrs@cygnus.com>.
6*e4b17023SJohn Marino
7*e4b17023SJohn Marino This file is part of GCC.
8*e4b17023SJohn Marino
9*e4b17023SJohn Marino GCC is free software; you can redistribute it and/or modify it under
10*e4b17023SJohn Marino the terms of the GNU General Public License as published by the Free
11*e4b17023SJohn Marino Software Foundation; either version 3, or (at your option) any later
12*e4b17023SJohn Marino version.
13*e4b17023SJohn Marino
14*e4b17023SJohn Marino GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15*e4b17023SJohn Marino WARRANTY; without even the implied warranty of MERCHANTABILITY or
16*e4b17023SJohn Marino FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
17*e4b17023SJohn Marino for more details.
18*e4b17023SJohn Marino
19*e4b17023SJohn Marino You should have received a copy of the GNU General Public License
20*e4b17023SJohn Marino along with GCC; see the file COPYING3. If not see
21*e4b17023SJohn Marino <http://www.gnu.org/licenses/>. */
22*e4b17023SJohn Marino
23*e4b17023SJohn Marino
24*e4b17023SJohn Marino /* An exception is an event that can be "thrown" from within a
25*e4b17023SJohn Marino function. This event can then be "caught" by the callers of
26*e4b17023SJohn Marino the function.
27*e4b17023SJohn Marino
28*e4b17023SJohn Marino The representation of exceptions changes several times during
29*e4b17023SJohn Marino the compilation process:
30*e4b17023SJohn Marino
31*e4b17023SJohn Marino In the beginning, in the front end, we have the GENERIC trees
32*e4b17023SJohn Marino TRY_CATCH_EXPR, TRY_FINALLY_EXPR, WITH_CLEANUP_EXPR,
33*e4b17023SJohn Marino CLEANUP_POINT_EXPR, CATCH_EXPR, and EH_FILTER_EXPR.
34*e4b17023SJohn Marino
35*e4b17023SJohn Marino During initial gimplification (gimplify.c) these are lowered
36*e4b17023SJohn Marino to the GIMPLE_TRY, GIMPLE_CATCH, and GIMPLE_EH_FILTER nodes.
37*e4b17023SJohn Marino The WITH_CLEANUP_EXPR and CLEANUP_POINT_EXPR nodes are converted
38*e4b17023SJohn Marino into GIMPLE_TRY_FINALLY nodes; the others are a more direct 1-1
39*e4b17023SJohn Marino conversion.
40*e4b17023SJohn Marino
41*e4b17023SJohn Marino During pass_lower_eh (tree-eh.c) we record the nested structure
42*e4b17023SJohn Marino of the TRY nodes in EH_REGION nodes in CFUN->EH->REGION_TREE.
43*e4b17023SJohn Marino We expand the eh_protect_cleanup_actions langhook into MUST_NOT_THROW
44*e4b17023SJohn Marino regions at this time. We can then flatten the statements within
45*e4b17023SJohn Marino the TRY nodes to straight-line code. Statements that had been within
46*e4b17023SJohn Marino TRY nodes that can throw are recorded within CFUN->EH->THROW_STMT_TABLE,
47*e4b17023SJohn Marino so that we may remember what action is supposed to be taken if
48*e4b17023SJohn Marino a given statement does throw. During this lowering process,
49*e4b17023SJohn Marino we create an EH_LANDING_PAD node for each EH_REGION that has
50*e4b17023SJohn Marino some code within the function that needs to be executed if a
51*e4b17023SJohn Marino throw does happen. We also create RESX statements that are
52*e4b17023SJohn Marino used to transfer control from an inner EH_REGION to an outer
53*e4b17023SJohn Marino EH_REGION. We also create EH_DISPATCH statements as placeholders
54*e4b17023SJohn Marino for a runtime type comparison that should be made in order to
55*e4b17023SJohn Marino select the action to perform among different CATCH and EH_FILTER
56*e4b17023SJohn Marino regions.
57*e4b17023SJohn Marino
58*e4b17023SJohn Marino During pass_lower_eh_dispatch (tree-eh.c), which is run after
59*e4b17023SJohn Marino all inlining is complete, we are able to run assign_filter_values,
60*e4b17023SJohn Marino which allows us to map the set of types manipulated by all of the
61*e4b17023SJohn Marino CATCH and EH_FILTER regions to a set of integers. This set of integers
62*e4b17023SJohn Marino will be how the exception runtime communicates with the code generated
63*e4b17023SJohn Marino within the function. We then expand the GIMPLE_EH_DISPATCH statements
64*e4b17023SJohn Marino to a switch or conditional branches that use the argument provided by
65*e4b17023SJohn Marino the runtime (__builtin_eh_filter) and the set of integers we computed
66*e4b17023SJohn Marino in assign_filter_values.
67*e4b17023SJohn Marino
68*e4b17023SJohn Marino During pass_lower_resx (tree-eh.c), which is run near the end
69*e4b17023SJohn Marino of optimization, we expand RESX statements. If the eh region
70*e4b17023SJohn Marino that is outer to the RESX statement is a MUST_NOT_THROW, then
71*e4b17023SJohn Marino the RESX expands to some form of abort statement. If the eh
72*e4b17023SJohn Marino region that is outer to the RESX statement is within the current
73*e4b17023SJohn Marino function, then the RESX expands to a bookkeeping call
74*e4b17023SJohn Marino (__builtin_eh_copy_values) and a goto. Otherwise, the next
75*e4b17023SJohn Marino handler for the exception must be within a function somewhere
76*e4b17023SJohn Marino up the call chain, so we call back into the exception runtime
77*e4b17023SJohn Marino (__builtin_unwind_resume).
78*e4b17023SJohn Marino
79*e4b17023SJohn Marino During pass_expand (cfgexpand.c), we generate REG_EH_REGION notes
80*e4b17023SJohn Marino that create an rtl to eh_region mapping that corresponds to the
81*e4b17023SJohn Marino gimple to eh_region mapping that had been recorded in the
82*e4b17023SJohn Marino THROW_STMT_TABLE.
83*e4b17023SJohn Marino
84*e4b17023SJohn Marino During pass_rtl_eh (except.c), we generate the real landing pads
85*e4b17023SJohn Marino to which the runtime will actually transfer control. These new
86*e4b17023SJohn Marino landing pads perform whatever bookkeeping is needed by the target
87*e4b17023SJohn Marino backend in order to resume execution within the current function.
88*e4b17023SJohn Marino Each of these new landing pads falls through into the post_landing_pad
89*e4b17023SJohn Marino label which had been used within the CFG up to this point. All
90*e4b17023SJohn Marino exception edges within the CFG are redirected to the new landing pads.
91*e4b17023SJohn Marino If the target uses setjmp to implement exceptions, the various extra
92*e4b17023SJohn Marino calls into the runtime to register and unregister the current stack
93*e4b17023SJohn Marino frame are emitted at this time.
94*e4b17023SJohn Marino
95*e4b17023SJohn Marino During pass_convert_to_eh_region_ranges (except.c), we transform
96*e4b17023SJohn Marino the REG_EH_REGION notes attached to individual insns into
97*e4b17023SJohn Marino non-overlapping ranges of insns bounded by NOTE_INSN_EH_REGION_BEG
98*e4b17023SJohn Marino and NOTE_INSN_EH_REGION_END. Each insn within such ranges has the
99*e4b17023SJohn Marino same associated action within the exception region tree, meaning
100*e4b17023SJohn Marino that (1) the exception is caught by the same landing pad within the
101*e4b17023SJohn Marino current function, (2) the exception is blocked by the runtime with
102*e4b17023SJohn Marino a MUST_NOT_THROW region, or (3) the exception is not handled at all
103*e4b17023SJohn Marino within the current function.
104*e4b17023SJohn Marino
105*e4b17023SJohn Marino Finally, during assembly generation, we call
106*e4b17023SJohn Marino output_function_exception_table (except.c) to emit the tables with
107*e4b17023SJohn Marino which the exception runtime can determine if a given stack frame
108*e4b17023SJohn Marino handles a given exception, and if so what filter value to provide
109*e4b17023SJohn Marino to the function when the non-local control transfer is effected.
110*e4b17023SJohn Marino If the target uses dwarf2 unwinding to implement exceptions, then
111*e4b17023SJohn Marino output_call_frame_info (dwarf2out.c) emits the required unwind data. */
112*e4b17023SJohn Marino
113*e4b17023SJohn Marino
114*e4b17023SJohn Marino #include "config.h"
115*e4b17023SJohn Marino #include "system.h"
116*e4b17023SJohn Marino #include "coretypes.h"
117*e4b17023SJohn Marino #include "tm.h"
118*e4b17023SJohn Marino #include "rtl.h"
119*e4b17023SJohn Marino #include "tree.h"
120*e4b17023SJohn Marino #include "flags.h"
121*e4b17023SJohn Marino #include "function.h"
122*e4b17023SJohn Marino #include "expr.h"
123*e4b17023SJohn Marino #include "libfuncs.h"
124*e4b17023SJohn Marino #include "insn-config.h"
125*e4b17023SJohn Marino #include "except.h"
126*e4b17023SJohn Marino #include "integrate.h"
127*e4b17023SJohn Marino #include "hard-reg-set.h"
128*e4b17023SJohn Marino #include "basic-block.h"
129*e4b17023SJohn Marino #include "output.h"
130*e4b17023SJohn Marino #include "dwarf2asm.h"
131*e4b17023SJohn Marino #include "dwarf2out.h"
132*e4b17023SJohn Marino #include "dwarf2.h"
133*e4b17023SJohn Marino #include "toplev.h"
134*e4b17023SJohn Marino #include "hashtab.h"
135*e4b17023SJohn Marino #include "intl.h"
136*e4b17023SJohn Marino #include "ggc.h"
137*e4b17023SJohn Marino #include "tm_p.h"
138*e4b17023SJohn Marino #include "target.h"
139*e4b17023SJohn Marino #include "common/common-target.h"
140*e4b17023SJohn Marino #include "langhooks.h"
141*e4b17023SJohn Marino #include "cgraph.h"
142*e4b17023SJohn Marino #include "diagnostic.h"
143*e4b17023SJohn Marino #include "tree-pretty-print.h"
144*e4b17023SJohn Marino #include "tree-pass.h"
145*e4b17023SJohn Marino #include "timevar.h"
146*e4b17023SJohn Marino #include "tree-flow.h"
147*e4b17023SJohn Marino
148*e4b17023SJohn Marino /* Provide defaults for stuff that may not be defined when using
149*e4b17023SJohn Marino sjlj exceptions. */
150*e4b17023SJohn Marino #ifndef EH_RETURN_DATA_REGNO
151*e4b17023SJohn Marino #define EH_RETURN_DATA_REGNO(N) INVALID_REGNUM
152*e4b17023SJohn Marino #endif
153*e4b17023SJohn Marino
154*e4b17023SJohn Marino static GTY(()) int call_site_base;
155*e4b17023SJohn Marino static GTY ((param_is (union tree_node)))
156*e4b17023SJohn Marino htab_t type_to_runtime_map;
157*e4b17023SJohn Marino
158*e4b17023SJohn Marino /* Describe the SjLj_Function_Context structure. */
159*e4b17023SJohn Marino static GTY(()) tree sjlj_fc_type_node;
160*e4b17023SJohn Marino static int sjlj_fc_call_site_ofs;
161*e4b17023SJohn Marino static int sjlj_fc_data_ofs;
162*e4b17023SJohn Marino static int sjlj_fc_personality_ofs;
163*e4b17023SJohn Marino static int sjlj_fc_lsda_ofs;
164*e4b17023SJohn Marino static int sjlj_fc_jbuf_ofs;
165*e4b17023SJohn Marino
166*e4b17023SJohn Marino
167*e4b17023SJohn Marino struct GTY(()) call_site_record_d
168*e4b17023SJohn Marino {
169*e4b17023SJohn Marino rtx landing_pad;
170*e4b17023SJohn Marino int action;
171*e4b17023SJohn Marino };
172*e4b17023SJohn Marino
173*e4b17023SJohn Marino static bool get_eh_region_and_lp_from_rtx (const_rtx, eh_region *,
174*e4b17023SJohn Marino eh_landing_pad *);
175*e4b17023SJohn Marino
176*e4b17023SJohn Marino static int t2r_eq (const void *, const void *);
177*e4b17023SJohn Marino static hashval_t t2r_hash (const void *);
178*e4b17023SJohn Marino
179*e4b17023SJohn Marino static int ttypes_filter_eq (const void *, const void *);
180*e4b17023SJohn Marino static hashval_t ttypes_filter_hash (const void *);
181*e4b17023SJohn Marino static int ehspec_filter_eq (const void *, const void *);
182*e4b17023SJohn Marino static hashval_t ehspec_filter_hash (const void *);
183*e4b17023SJohn Marino static int add_ttypes_entry (htab_t, tree);
184*e4b17023SJohn Marino static int add_ehspec_entry (htab_t, htab_t, tree);
185*e4b17023SJohn Marino static void dw2_build_landing_pads (void);
186*e4b17023SJohn Marino
187*e4b17023SJohn Marino static int action_record_eq (const void *, const void *);
188*e4b17023SJohn Marino static hashval_t action_record_hash (const void *);
189*e4b17023SJohn Marino static int add_action_record (htab_t, int, int);
190*e4b17023SJohn Marino static int collect_one_action_chain (htab_t, eh_region);
191*e4b17023SJohn Marino static int add_call_site (rtx, int, int);
192*e4b17023SJohn Marino
193*e4b17023SJohn Marino static void push_uleb128 (VEC (uchar, gc) **, unsigned int);
194*e4b17023SJohn Marino static void push_sleb128 (VEC (uchar, gc) **, int);
195*e4b17023SJohn Marino #ifndef HAVE_AS_LEB128
196*e4b17023SJohn Marino static int dw2_size_of_call_site_table (int);
197*e4b17023SJohn Marino static int sjlj_size_of_call_site_table (void);
198*e4b17023SJohn Marino #endif
199*e4b17023SJohn Marino static void dw2_output_call_site_table (int, int);
200*e4b17023SJohn Marino static void sjlj_output_call_site_table (void);
201*e4b17023SJohn Marino
202*e4b17023SJohn Marino
203*e4b17023SJohn Marino void
init_eh(void)204*e4b17023SJohn Marino init_eh (void)
205*e4b17023SJohn Marino {
206*e4b17023SJohn Marino if (! flag_exceptions)
207*e4b17023SJohn Marino return;
208*e4b17023SJohn Marino
209*e4b17023SJohn Marino type_to_runtime_map = htab_create_ggc (31, t2r_hash, t2r_eq, NULL);
210*e4b17023SJohn Marino
211*e4b17023SJohn Marino /* Create the SjLj_Function_Context structure. This should match
212*e4b17023SJohn Marino the definition in unwind-sjlj.c. */
213*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
214*e4b17023SJohn Marino {
215*e4b17023SJohn Marino tree f_jbuf, f_per, f_lsda, f_prev, f_cs, f_data, tmp;
216*e4b17023SJohn Marino
217*e4b17023SJohn Marino sjlj_fc_type_node = lang_hooks.types.make_type (RECORD_TYPE);
218*e4b17023SJohn Marino
219*e4b17023SJohn Marino f_prev = build_decl (BUILTINS_LOCATION,
220*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__prev"),
221*e4b17023SJohn Marino build_pointer_type (sjlj_fc_type_node));
222*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_prev) = sjlj_fc_type_node;
223*e4b17023SJohn Marino
224*e4b17023SJohn Marino f_cs = build_decl (BUILTINS_LOCATION,
225*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__call_site"),
226*e4b17023SJohn Marino integer_type_node);
227*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_cs) = sjlj_fc_type_node;
228*e4b17023SJohn Marino
229*e4b17023SJohn Marino tmp = build_index_type (size_int (4 - 1));
230*e4b17023SJohn Marino tmp = build_array_type (lang_hooks.types.type_for_mode
231*e4b17023SJohn Marino (targetm.unwind_word_mode (), 1),
232*e4b17023SJohn Marino tmp);
233*e4b17023SJohn Marino f_data = build_decl (BUILTINS_LOCATION,
234*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__data"), tmp);
235*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_data) = sjlj_fc_type_node;
236*e4b17023SJohn Marino
237*e4b17023SJohn Marino f_per = build_decl (BUILTINS_LOCATION,
238*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__personality"),
239*e4b17023SJohn Marino ptr_type_node);
240*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_per) = sjlj_fc_type_node;
241*e4b17023SJohn Marino
242*e4b17023SJohn Marino f_lsda = build_decl (BUILTINS_LOCATION,
243*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__lsda"),
244*e4b17023SJohn Marino ptr_type_node);
245*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_lsda) = sjlj_fc_type_node;
246*e4b17023SJohn Marino
247*e4b17023SJohn Marino #ifdef DONT_USE_BUILTIN_SETJMP
248*e4b17023SJohn Marino #ifdef JMP_BUF_SIZE
249*e4b17023SJohn Marino tmp = size_int (JMP_BUF_SIZE - 1);
250*e4b17023SJohn Marino #else
251*e4b17023SJohn Marino /* Should be large enough for most systems, if it is not,
252*e4b17023SJohn Marino JMP_BUF_SIZE should be defined with the proper value. It will
253*e4b17023SJohn Marino also tend to be larger than necessary for most systems, a more
254*e4b17023SJohn Marino optimal port will define JMP_BUF_SIZE. */
255*e4b17023SJohn Marino tmp = size_int (FIRST_PSEUDO_REGISTER + 2 - 1);
256*e4b17023SJohn Marino #endif
257*e4b17023SJohn Marino #else
258*e4b17023SJohn Marino /* builtin_setjmp takes a pointer to 5 words. */
259*e4b17023SJohn Marino tmp = size_int (5 * BITS_PER_WORD / POINTER_SIZE - 1);
260*e4b17023SJohn Marino #endif
261*e4b17023SJohn Marino tmp = build_index_type (tmp);
262*e4b17023SJohn Marino tmp = build_array_type (ptr_type_node, tmp);
263*e4b17023SJohn Marino f_jbuf = build_decl (BUILTINS_LOCATION,
264*e4b17023SJohn Marino FIELD_DECL, get_identifier ("__jbuf"), tmp);
265*e4b17023SJohn Marino #ifdef DONT_USE_BUILTIN_SETJMP
266*e4b17023SJohn Marino /* We don't know what the alignment requirements of the
267*e4b17023SJohn Marino runtime's jmp_buf has. Overestimate. */
268*e4b17023SJohn Marino DECL_ALIGN (f_jbuf) = BIGGEST_ALIGNMENT;
269*e4b17023SJohn Marino DECL_USER_ALIGN (f_jbuf) = 1;
270*e4b17023SJohn Marino #endif
271*e4b17023SJohn Marino DECL_FIELD_CONTEXT (f_jbuf) = sjlj_fc_type_node;
272*e4b17023SJohn Marino
273*e4b17023SJohn Marino TYPE_FIELDS (sjlj_fc_type_node) = f_prev;
274*e4b17023SJohn Marino TREE_CHAIN (f_prev) = f_cs;
275*e4b17023SJohn Marino TREE_CHAIN (f_cs) = f_data;
276*e4b17023SJohn Marino TREE_CHAIN (f_data) = f_per;
277*e4b17023SJohn Marino TREE_CHAIN (f_per) = f_lsda;
278*e4b17023SJohn Marino TREE_CHAIN (f_lsda) = f_jbuf;
279*e4b17023SJohn Marino
280*e4b17023SJohn Marino layout_type (sjlj_fc_type_node);
281*e4b17023SJohn Marino
282*e4b17023SJohn Marino /* Cache the interesting field offsets so that we have
283*e4b17023SJohn Marino easy access from rtl. */
284*e4b17023SJohn Marino sjlj_fc_call_site_ofs
285*e4b17023SJohn Marino = (tree_low_cst (DECL_FIELD_OFFSET (f_cs), 1)
286*e4b17023SJohn Marino + tree_low_cst (DECL_FIELD_BIT_OFFSET (f_cs), 1) / BITS_PER_UNIT);
287*e4b17023SJohn Marino sjlj_fc_data_ofs
288*e4b17023SJohn Marino = (tree_low_cst (DECL_FIELD_OFFSET (f_data), 1)
289*e4b17023SJohn Marino + tree_low_cst (DECL_FIELD_BIT_OFFSET (f_data), 1) / BITS_PER_UNIT);
290*e4b17023SJohn Marino sjlj_fc_personality_ofs
291*e4b17023SJohn Marino = (tree_low_cst (DECL_FIELD_OFFSET (f_per), 1)
292*e4b17023SJohn Marino + tree_low_cst (DECL_FIELD_BIT_OFFSET (f_per), 1) / BITS_PER_UNIT);
293*e4b17023SJohn Marino sjlj_fc_lsda_ofs
294*e4b17023SJohn Marino = (tree_low_cst (DECL_FIELD_OFFSET (f_lsda), 1)
295*e4b17023SJohn Marino + tree_low_cst (DECL_FIELD_BIT_OFFSET (f_lsda), 1) / BITS_PER_UNIT);
296*e4b17023SJohn Marino sjlj_fc_jbuf_ofs
297*e4b17023SJohn Marino = (tree_low_cst (DECL_FIELD_OFFSET (f_jbuf), 1)
298*e4b17023SJohn Marino + tree_low_cst (DECL_FIELD_BIT_OFFSET (f_jbuf), 1) / BITS_PER_UNIT);
299*e4b17023SJohn Marino }
300*e4b17023SJohn Marino }
301*e4b17023SJohn Marino
302*e4b17023SJohn Marino void
init_eh_for_function(void)303*e4b17023SJohn Marino init_eh_for_function (void)
304*e4b17023SJohn Marino {
305*e4b17023SJohn Marino cfun->eh = ggc_alloc_cleared_eh_status ();
306*e4b17023SJohn Marino
307*e4b17023SJohn Marino /* Make sure zero'th entries are used. */
308*e4b17023SJohn Marino VEC_safe_push (eh_region, gc, cfun->eh->region_array, NULL);
309*e4b17023SJohn Marino VEC_safe_push (eh_landing_pad, gc, cfun->eh->lp_array, NULL);
310*e4b17023SJohn Marino }
311*e4b17023SJohn Marino
312*e4b17023SJohn Marino /* Routines to generate the exception tree somewhat directly.
313*e4b17023SJohn Marino These are used from tree-eh.c when processing exception related
314*e4b17023SJohn Marino nodes during tree optimization. */
315*e4b17023SJohn Marino
316*e4b17023SJohn Marino static eh_region
gen_eh_region(enum eh_region_type type,eh_region outer)317*e4b17023SJohn Marino gen_eh_region (enum eh_region_type type, eh_region outer)
318*e4b17023SJohn Marino {
319*e4b17023SJohn Marino eh_region new_eh;
320*e4b17023SJohn Marino
321*e4b17023SJohn Marino /* Insert a new blank region as a leaf in the tree. */
322*e4b17023SJohn Marino new_eh = ggc_alloc_cleared_eh_region_d ();
323*e4b17023SJohn Marino new_eh->type = type;
324*e4b17023SJohn Marino new_eh->outer = outer;
325*e4b17023SJohn Marino if (outer)
326*e4b17023SJohn Marino {
327*e4b17023SJohn Marino new_eh->next_peer = outer->inner;
328*e4b17023SJohn Marino outer->inner = new_eh;
329*e4b17023SJohn Marino }
330*e4b17023SJohn Marino else
331*e4b17023SJohn Marino {
332*e4b17023SJohn Marino new_eh->next_peer = cfun->eh->region_tree;
333*e4b17023SJohn Marino cfun->eh->region_tree = new_eh;
334*e4b17023SJohn Marino }
335*e4b17023SJohn Marino
336*e4b17023SJohn Marino new_eh->index = VEC_length (eh_region, cfun->eh->region_array);
337*e4b17023SJohn Marino VEC_safe_push (eh_region, gc, cfun->eh->region_array, new_eh);
338*e4b17023SJohn Marino
339*e4b17023SJohn Marino /* Copy the language's notion of whether to use __cxa_end_cleanup. */
340*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder && lang_hooks.eh_use_cxa_end_cleanup)
341*e4b17023SJohn Marino new_eh->use_cxa_end_cleanup = true;
342*e4b17023SJohn Marino
343*e4b17023SJohn Marino return new_eh;
344*e4b17023SJohn Marino }
345*e4b17023SJohn Marino
346*e4b17023SJohn Marino eh_region
gen_eh_region_cleanup(eh_region outer)347*e4b17023SJohn Marino gen_eh_region_cleanup (eh_region outer)
348*e4b17023SJohn Marino {
349*e4b17023SJohn Marino return gen_eh_region (ERT_CLEANUP, outer);
350*e4b17023SJohn Marino }
351*e4b17023SJohn Marino
352*e4b17023SJohn Marino eh_region
gen_eh_region_try(eh_region outer)353*e4b17023SJohn Marino gen_eh_region_try (eh_region outer)
354*e4b17023SJohn Marino {
355*e4b17023SJohn Marino return gen_eh_region (ERT_TRY, outer);
356*e4b17023SJohn Marino }
357*e4b17023SJohn Marino
358*e4b17023SJohn Marino eh_catch
gen_eh_region_catch(eh_region t,tree type_or_list)359*e4b17023SJohn Marino gen_eh_region_catch (eh_region t, tree type_or_list)
360*e4b17023SJohn Marino {
361*e4b17023SJohn Marino eh_catch c, l;
362*e4b17023SJohn Marino tree type_list, type_node;
363*e4b17023SJohn Marino
364*e4b17023SJohn Marino gcc_assert (t->type == ERT_TRY);
365*e4b17023SJohn Marino
366*e4b17023SJohn Marino /* Ensure to always end up with a type list to normalize further
367*e4b17023SJohn Marino processing, then register each type against the runtime types map. */
368*e4b17023SJohn Marino type_list = type_or_list;
369*e4b17023SJohn Marino if (type_or_list)
370*e4b17023SJohn Marino {
371*e4b17023SJohn Marino if (TREE_CODE (type_or_list) != TREE_LIST)
372*e4b17023SJohn Marino type_list = tree_cons (NULL_TREE, type_or_list, NULL_TREE);
373*e4b17023SJohn Marino
374*e4b17023SJohn Marino type_node = type_list;
375*e4b17023SJohn Marino for (; type_node; type_node = TREE_CHAIN (type_node))
376*e4b17023SJohn Marino add_type_for_runtime (TREE_VALUE (type_node));
377*e4b17023SJohn Marino }
378*e4b17023SJohn Marino
379*e4b17023SJohn Marino c = ggc_alloc_cleared_eh_catch_d ();
380*e4b17023SJohn Marino c->type_list = type_list;
381*e4b17023SJohn Marino l = t->u.eh_try.last_catch;
382*e4b17023SJohn Marino c->prev_catch = l;
383*e4b17023SJohn Marino if (l)
384*e4b17023SJohn Marino l->next_catch = c;
385*e4b17023SJohn Marino else
386*e4b17023SJohn Marino t->u.eh_try.first_catch = c;
387*e4b17023SJohn Marino t->u.eh_try.last_catch = c;
388*e4b17023SJohn Marino
389*e4b17023SJohn Marino return c;
390*e4b17023SJohn Marino }
391*e4b17023SJohn Marino
392*e4b17023SJohn Marino eh_region
gen_eh_region_allowed(eh_region outer,tree allowed)393*e4b17023SJohn Marino gen_eh_region_allowed (eh_region outer, tree allowed)
394*e4b17023SJohn Marino {
395*e4b17023SJohn Marino eh_region region = gen_eh_region (ERT_ALLOWED_EXCEPTIONS, outer);
396*e4b17023SJohn Marino region->u.allowed.type_list = allowed;
397*e4b17023SJohn Marino
398*e4b17023SJohn Marino for (; allowed ; allowed = TREE_CHAIN (allowed))
399*e4b17023SJohn Marino add_type_for_runtime (TREE_VALUE (allowed));
400*e4b17023SJohn Marino
401*e4b17023SJohn Marino return region;
402*e4b17023SJohn Marino }
403*e4b17023SJohn Marino
404*e4b17023SJohn Marino eh_region
gen_eh_region_must_not_throw(eh_region outer)405*e4b17023SJohn Marino gen_eh_region_must_not_throw (eh_region outer)
406*e4b17023SJohn Marino {
407*e4b17023SJohn Marino return gen_eh_region (ERT_MUST_NOT_THROW, outer);
408*e4b17023SJohn Marino }
409*e4b17023SJohn Marino
410*e4b17023SJohn Marino eh_landing_pad
gen_eh_landing_pad(eh_region region)411*e4b17023SJohn Marino gen_eh_landing_pad (eh_region region)
412*e4b17023SJohn Marino {
413*e4b17023SJohn Marino eh_landing_pad lp = ggc_alloc_cleared_eh_landing_pad_d ();
414*e4b17023SJohn Marino
415*e4b17023SJohn Marino lp->next_lp = region->landing_pads;
416*e4b17023SJohn Marino lp->region = region;
417*e4b17023SJohn Marino lp->index = VEC_length (eh_landing_pad, cfun->eh->lp_array);
418*e4b17023SJohn Marino region->landing_pads = lp;
419*e4b17023SJohn Marino
420*e4b17023SJohn Marino VEC_safe_push (eh_landing_pad, gc, cfun->eh->lp_array, lp);
421*e4b17023SJohn Marino
422*e4b17023SJohn Marino return lp;
423*e4b17023SJohn Marino }
424*e4b17023SJohn Marino
425*e4b17023SJohn Marino eh_region
get_eh_region_from_number_fn(struct function * ifun,int i)426*e4b17023SJohn Marino get_eh_region_from_number_fn (struct function *ifun, int i)
427*e4b17023SJohn Marino {
428*e4b17023SJohn Marino return VEC_index (eh_region, ifun->eh->region_array, i);
429*e4b17023SJohn Marino }
430*e4b17023SJohn Marino
431*e4b17023SJohn Marino eh_region
get_eh_region_from_number(int i)432*e4b17023SJohn Marino get_eh_region_from_number (int i)
433*e4b17023SJohn Marino {
434*e4b17023SJohn Marino return get_eh_region_from_number_fn (cfun, i);
435*e4b17023SJohn Marino }
436*e4b17023SJohn Marino
437*e4b17023SJohn Marino eh_landing_pad
get_eh_landing_pad_from_number_fn(struct function * ifun,int i)438*e4b17023SJohn Marino get_eh_landing_pad_from_number_fn (struct function *ifun, int i)
439*e4b17023SJohn Marino {
440*e4b17023SJohn Marino return VEC_index (eh_landing_pad, ifun->eh->lp_array, i);
441*e4b17023SJohn Marino }
442*e4b17023SJohn Marino
443*e4b17023SJohn Marino eh_landing_pad
get_eh_landing_pad_from_number(int i)444*e4b17023SJohn Marino get_eh_landing_pad_from_number (int i)
445*e4b17023SJohn Marino {
446*e4b17023SJohn Marino return get_eh_landing_pad_from_number_fn (cfun, i);
447*e4b17023SJohn Marino }
448*e4b17023SJohn Marino
449*e4b17023SJohn Marino eh_region
get_eh_region_from_lp_number_fn(struct function * ifun,int i)450*e4b17023SJohn Marino get_eh_region_from_lp_number_fn (struct function *ifun, int i)
451*e4b17023SJohn Marino {
452*e4b17023SJohn Marino if (i < 0)
453*e4b17023SJohn Marino return VEC_index (eh_region, ifun->eh->region_array, -i);
454*e4b17023SJohn Marino else if (i == 0)
455*e4b17023SJohn Marino return NULL;
456*e4b17023SJohn Marino else
457*e4b17023SJohn Marino {
458*e4b17023SJohn Marino eh_landing_pad lp;
459*e4b17023SJohn Marino lp = VEC_index (eh_landing_pad, ifun->eh->lp_array, i);
460*e4b17023SJohn Marino return lp->region;
461*e4b17023SJohn Marino }
462*e4b17023SJohn Marino }
463*e4b17023SJohn Marino
464*e4b17023SJohn Marino eh_region
get_eh_region_from_lp_number(int i)465*e4b17023SJohn Marino get_eh_region_from_lp_number (int i)
466*e4b17023SJohn Marino {
467*e4b17023SJohn Marino return get_eh_region_from_lp_number_fn (cfun, i);
468*e4b17023SJohn Marino }
469*e4b17023SJohn Marino
470*e4b17023SJohn Marino /* Returns true if the current function has exception handling regions. */
471*e4b17023SJohn Marino
472*e4b17023SJohn Marino bool
current_function_has_exception_handlers(void)473*e4b17023SJohn Marino current_function_has_exception_handlers (void)
474*e4b17023SJohn Marino {
475*e4b17023SJohn Marino return cfun->eh->region_tree != NULL;
476*e4b17023SJohn Marino }
477*e4b17023SJohn Marino
478*e4b17023SJohn Marino /* A subroutine of duplicate_eh_regions. Copy the eh_region tree at OLD.
479*e4b17023SJohn Marino Root it at OUTER, and apply LP_OFFSET to the lp numbers. */
480*e4b17023SJohn Marino
481*e4b17023SJohn Marino struct duplicate_eh_regions_data
482*e4b17023SJohn Marino {
483*e4b17023SJohn Marino duplicate_eh_regions_map label_map;
484*e4b17023SJohn Marino void *label_map_data;
485*e4b17023SJohn Marino struct pointer_map_t *eh_map;
486*e4b17023SJohn Marino };
487*e4b17023SJohn Marino
488*e4b17023SJohn Marino static void
duplicate_eh_regions_1(struct duplicate_eh_regions_data * data,eh_region old_r,eh_region outer)489*e4b17023SJohn Marino duplicate_eh_regions_1 (struct duplicate_eh_regions_data *data,
490*e4b17023SJohn Marino eh_region old_r, eh_region outer)
491*e4b17023SJohn Marino {
492*e4b17023SJohn Marino eh_landing_pad old_lp, new_lp;
493*e4b17023SJohn Marino eh_region new_r;
494*e4b17023SJohn Marino void **slot;
495*e4b17023SJohn Marino
496*e4b17023SJohn Marino new_r = gen_eh_region (old_r->type, outer);
497*e4b17023SJohn Marino slot = pointer_map_insert (data->eh_map, (void *)old_r);
498*e4b17023SJohn Marino gcc_assert (*slot == NULL);
499*e4b17023SJohn Marino *slot = (void *)new_r;
500*e4b17023SJohn Marino
501*e4b17023SJohn Marino switch (old_r->type)
502*e4b17023SJohn Marino {
503*e4b17023SJohn Marino case ERT_CLEANUP:
504*e4b17023SJohn Marino break;
505*e4b17023SJohn Marino
506*e4b17023SJohn Marino case ERT_TRY:
507*e4b17023SJohn Marino {
508*e4b17023SJohn Marino eh_catch oc, nc;
509*e4b17023SJohn Marino for (oc = old_r->u.eh_try.first_catch; oc ; oc = oc->next_catch)
510*e4b17023SJohn Marino {
511*e4b17023SJohn Marino /* We should be doing all our region duplication before and
512*e4b17023SJohn Marino during inlining, which is before filter lists are created. */
513*e4b17023SJohn Marino gcc_assert (oc->filter_list == NULL);
514*e4b17023SJohn Marino nc = gen_eh_region_catch (new_r, oc->type_list);
515*e4b17023SJohn Marino nc->label = data->label_map (oc->label, data->label_map_data);
516*e4b17023SJohn Marino }
517*e4b17023SJohn Marino }
518*e4b17023SJohn Marino break;
519*e4b17023SJohn Marino
520*e4b17023SJohn Marino case ERT_ALLOWED_EXCEPTIONS:
521*e4b17023SJohn Marino new_r->u.allowed.type_list = old_r->u.allowed.type_list;
522*e4b17023SJohn Marino if (old_r->u.allowed.label)
523*e4b17023SJohn Marino new_r->u.allowed.label
524*e4b17023SJohn Marino = data->label_map (old_r->u.allowed.label, data->label_map_data);
525*e4b17023SJohn Marino else
526*e4b17023SJohn Marino new_r->u.allowed.label = NULL_TREE;
527*e4b17023SJohn Marino break;
528*e4b17023SJohn Marino
529*e4b17023SJohn Marino case ERT_MUST_NOT_THROW:
530*e4b17023SJohn Marino new_r->u.must_not_throw = old_r->u.must_not_throw;
531*e4b17023SJohn Marino break;
532*e4b17023SJohn Marino }
533*e4b17023SJohn Marino
534*e4b17023SJohn Marino for (old_lp = old_r->landing_pads; old_lp ; old_lp = old_lp->next_lp)
535*e4b17023SJohn Marino {
536*e4b17023SJohn Marino /* Don't bother copying unused landing pads. */
537*e4b17023SJohn Marino if (old_lp->post_landing_pad == NULL)
538*e4b17023SJohn Marino continue;
539*e4b17023SJohn Marino
540*e4b17023SJohn Marino new_lp = gen_eh_landing_pad (new_r);
541*e4b17023SJohn Marino slot = pointer_map_insert (data->eh_map, (void *)old_lp);
542*e4b17023SJohn Marino gcc_assert (*slot == NULL);
543*e4b17023SJohn Marino *slot = (void *)new_lp;
544*e4b17023SJohn Marino
545*e4b17023SJohn Marino new_lp->post_landing_pad
546*e4b17023SJohn Marino = data->label_map (old_lp->post_landing_pad, data->label_map_data);
547*e4b17023SJohn Marino EH_LANDING_PAD_NR (new_lp->post_landing_pad) = new_lp->index;
548*e4b17023SJohn Marino }
549*e4b17023SJohn Marino
550*e4b17023SJohn Marino /* Make sure to preserve the original use of __cxa_end_cleanup. */
551*e4b17023SJohn Marino new_r->use_cxa_end_cleanup = old_r->use_cxa_end_cleanup;
552*e4b17023SJohn Marino
553*e4b17023SJohn Marino for (old_r = old_r->inner; old_r ; old_r = old_r->next_peer)
554*e4b17023SJohn Marino duplicate_eh_regions_1 (data, old_r, new_r);
555*e4b17023SJohn Marino }
556*e4b17023SJohn Marino
557*e4b17023SJohn Marino /* Duplicate the EH regions from IFUN rooted at COPY_REGION into
558*e4b17023SJohn Marino the current function and root the tree below OUTER_REGION.
559*e4b17023SJohn Marino The special case of COPY_REGION of NULL means all regions.
560*e4b17023SJohn Marino Remap labels using MAP/MAP_DATA callback. Return a pointer map
561*e4b17023SJohn Marino that allows the caller to remap uses of both EH regions and
562*e4b17023SJohn Marino EH landing pads. */
563*e4b17023SJohn Marino
564*e4b17023SJohn Marino struct pointer_map_t *
duplicate_eh_regions(struct function * ifun,eh_region copy_region,int outer_lp,duplicate_eh_regions_map map,void * map_data)565*e4b17023SJohn Marino duplicate_eh_regions (struct function *ifun,
566*e4b17023SJohn Marino eh_region copy_region, int outer_lp,
567*e4b17023SJohn Marino duplicate_eh_regions_map map, void *map_data)
568*e4b17023SJohn Marino {
569*e4b17023SJohn Marino struct duplicate_eh_regions_data data;
570*e4b17023SJohn Marino eh_region outer_region;
571*e4b17023SJohn Marino
572*e4b17023SJohn Marino #ifdef ENABLE_CHECKING
573*e4b17023SJohn Marino verify_eh_tree (ifun);
574*e4b17023SJohn Marino #endif
575*e4b17023SJohn Marino
576*e4b17023SJohn Marino data.label_map = map;
577*e4b17023SJohn Marino data.label_map_data = map_data;
578*e4b17023SJohn Marino data.eh_map = pointer_map_create ();
579*e4b17023SJohn Marino
580*e4b17023SJohn Marino outer_region = get_eh_region_from_lp_number (outer_lp);
581*e4b17023SJohn Marino
582*e4b17023SJohn Marino /* Copy all the regions in the subtree. */
583*e4b17023SJohn Marino if (copy_region)
584*e4b17023SJohn Marino duplicate_eh_regions_1 (&data, copy_region, outer_region);
585*e4b17023SJohn Marino else
586*e4b17023SJohn Marino {
587*e4b17023SJohn Marino eh_region r;
588*e4b17023SJohn Marino for (r = ifun->eh->region_tree; r ; r = r->next_peer)
589*e4b17023SJohn Marino duplicate_eh_regions_1 (&data, r, outer_region);
590*e4b17023SJohn Marino }
591*e4b17023SJohn Marino
592*e4b17023SJohn Marino #ifdef ENABLE_CHECKING
593*e4b17023SJohn Marino verify_eh_tree (cfun);
594*e4b17023SJohn Marino #endif
595*e4b17023SJohn Marino
596*e4b17023SJohn Marino return data.eh_map;
597*e4b17023SJohn Marino }
598*e4b17023SJohn Marino
599*e4b17023SJohn Marino /* Return the region that is outer to both REGION_A and REGION_B in IFUN. */
600*e4b17023SJohn Marino
601*e4b17023SJohn Marino eh_region
eh_region_outermost(struct function * ifun,eh_region region_a,eh_region region_b)602*e4b17023SJohn Marino eh_region_outermost (struct function *ifun, eh_region region_a,
603*e4b17023SJohn Marino eh_region region_b)
604*e4b17023SJohn Marino {
605*e4b17023SJohn Marino sbitmap b_outer;
606*e4b17023SJohn Marino
607*e4b17023SJohn Marino gcc_assert (ifun->eh->region_array);
608*e4b17023SJohn Marino gcc_assert (ifun->eh->region_tree);
609*e4b17023SJohn Marino
610*e4b17023SJohn Marino b_outer = sbitmap_alloc (VEC_length (eh_region, ifun->eh->region_array));
611*e4b17023SJohn Marino sbitmap_zero (b_outer);
612*e4b17023SJohn Marino
613*e4b17023SJohn Marino do
614*e4b17023SJohn Marino {
615*e4b17023SJohn Marino SET_BIT (b_outer, region_b->index);
616*e4b17023SJohn Marino region_b = region_b->outer;
617*e4b17023SJohn Marino }
618*e4b17023SJohn Marino while (region_b);
619*e4b17023SJohn Marino
620*e4b17023SJohn Marino do
621*e4b17023SJohn Marino {
622*e4b17023SJohn Marino if (TEST_BIT (b_outer, region_a->index))
623*e4b17023SJohn Marino break;
624*e4b17023SJohn Marino region_a = region_a->outer;
625*e4b17023SJohn Marino }
626*e4b17023SJohn Marino while (region_a);
627*e4b17023SJohn Marino
628*e4b17023SJohn Marino sbitmap_free (b_outer);
629*e4b17023SJohn Marino return region_a;
630*e4b17023SJohn Marino }
631*e4b17023SJohn Marino
632*e4b17023SJohn Marino static int
t2r_eq(const void * pentry,const void * pdata)633*e4b17023SJohn Marino t2r_eq (const void *pentry, const void *pdata)
634*e4b17023SJohn Marino {
635*e4b17023SJohn Marino const_tree const entry = (const_tree) pentry;
636*e4b17023SJohn Marino const_tree const data = (const_tree) pdata;
637*e4b17023SJohn Marino
638*e4b17023SJohn Marino return TREE_PURPOSE (entry) == data;
639*e4b17023SJohn Marino }
640*e4b17023SJohn Marino
641*e4b17023SJohn Marino static hashval_t
t2r_hash(const void * pentry)642*e4b17023SJohn Marino t2r_hash (const void *pentry)
643*e4b17023SJohn Marino {
644*e4b17023SJohn Marino const_tree const entry = (const_tree) pentry;
645*e4b17023SJohn Marino return TREE_HASH (TREE_PURPOSE (entry));
646*e4b17023SJohn Marino }
647*e4b17023SJohn Marino
648*e4b17023SJohn Marino void
add_type_for_runtime(tree type)649*e4b17023SJohn Marino add_type_for_runtime (tree type)
650*e4b17023SJohn Marino {
651*e4b17023SJohn Marino tree *slot;
652*e4b17023SJohn Marino
653*e4b17023SJohn Marino /* If TYPE is NOP_EXPR, it means that it already is a runtime type. */
654*e4b17023SJohn Marino if (TREE_CODE (type) == NOP_EXPR)
655*e4b17023SJohn Marino return;
656*e4b17023SJohn Marino
657*e4b17023SJohn Marino slot = (tree *) htab_find_slot_with_hash (type_to_runtime_map, type,
658*e4b17023SJohn Marino TREE_HASH (type), INSERT);
659*e4b17023SJohn Marino if (*slot == NULL)
660*e4b17023SJohn Marino {
661*e4b17023SJohn Marino tree runtime = lang_hooks.eh_runtime_type (type);
662*e4b17023SJohn Marino *slot = tree_cons (type, runtime, NULL_TREE);
663*e4b17023SJohn Marino }
664*e4b17023SJohn Marino }
665*e4b17023SJohn Marino
666*e4b17023SJohn Marino tree
lookup_type_for_runtime(tree type)667*e4b17023SJohn Marino lookup_type_for_runtime (tree type)
668*e4b17023SJohn Marino {
669*e4b17023SJohn Marino tree *slot;
670*e4b17023SJohn Marino
671*e4b17023SJohn Marino /* If TYPE is NOP_EXPR, it means that it already is a runtime type. */
672*e4b17023SJohn Marino if (TREE_CODE (type) == NOP_EXPR)
673*e4b17023SJohn Marino return type;
674*e4b17023SJohn Marino
675*e4b17023SJohn Marino slot = (tree *) htab_find_slot_with_hash (type_to_runtime_map, type,
676*e4b17023SJohn Marino TREE_HASH (type), NO_INSERT);
677*e4b17023SJohn Marino
678*e4b17023SJohn Marino /* We should have always inserted the data earlier. */
679*e4b17023SJohn Marino return TREE_VALUE (*slot);
680*e4b17023SJohn Marino }
681*e4b17023SJohn Marino
682*e4b17023SJohn Marino
683*e4b17023SJohn Marino /* Represent an entry in @TTypes for either catch actions
684*e4b17023SJohn Marino or exception filter actions. */
685*e4b17023SJohn Marino struct ttypes_filter {
686*e4b17023SJohn Marino tree t;
687*e4b17023SJohn Marino int filter;
688*e4b17023SJohn Marino };
689*e4b17023SJohn Marino
690*e4b17023SJohn Marino /* Compare ENTRY (a ttypes_filter entry in the hash table) with DATA
691*e4b17023SJohn Marino (a tree) for a @TTypes type node we are thinking about adding. */
692*e4b17023SJohn Marino
693*e4b17023SJohn Marino static int
ttypes_filter_eq(const void * pentry,const void * pdata)694*e4b17023SJohn Marino ttypes_filter_eq (const void *pentry, const void *pdata)
695*e4b17023SJohn Marino {
696*e4b17023SJohn Marino const struct ttypes_filter *const entry
697*e4b17023SJohn Marino = (const struct ttypes_filter *) pentry;
698*e4b17023SJohn Marino const_tree const data = (const_tree) pdata;
699*e4b17023SJohn Marino
700*e4b17023SJohn Marino return entry->t == data;
701*e4b17023SJohn Marino }
702*e4b17023SJohn Marino
703*e4b17023SJohn Marino static hashval_t
ttypes_filter_hash(const void * pentry)704*e4b17023SJohn Marino ttypes_filter_hash (const void *pentry)
705*e4b17023SJohn Marino {
706*e4b17023SJohn Marino const struct ttypes_filter *entry = (const struct ttypes_filter *) pentry;
707*e4b17023SJohn Marino return TREE_HASH (entry->t);
708*e4b17023SJohn Marino }
709*e4b17023SJohn Marino
710*e4b17023SJohn Marino /* Compare ENTRY with DATA (both struct ttypes_filter) for a @TTypes
711*e4b17023SJohn Marino exception specification list we are thinking about adding. */
712*e4b17023SJohn Marino /* ??? Currently we use the type lists in the order given. Someone
713*e4b17023SJohn Marino should put these in some canonical order. */
714*e4b17023SJohn Marino
715*e4b17023SJohn Marino static int
ehspec_filter_eq(const void * pentry,const void * pdata)716*e4b17023SJohn Marino ehspec_filter_eq (const void *pentry, const void *pdata)
717*e4b17023SJohn Marino {
718*e4b17023SJohn Marino const struct ttypes_filter *entry = (const struct ttypes_filter *) pentry;
719*e4b17023SJohn Marino const struct ttypes_filter *data = (const struct ttypes_filter *) pdata;
720*e4b17023SJohn Marino
721*e4b17023SJohn Marino return type_list_equal (entry->t, data->t);
722*e4b17023SJohn Marino }
723*e4b17023SJohn Marino
724*e4b17023SJohn Marino /* Hash function for exception specification lists. */
725*e4b17023SJohn Marino
726*e4b17023SJohn Marino static hashval_t
ehspec_filter_hash(const void * pentry)727*e4b17023SJohn Marino ehspec_filter_hash (const void *pentry)
728*e4b17023SJohn Marino {
729*e4b17023SJohn Marino const struct ttypes_filter *entry = (const struct ttypes_filter *) pentry;
730*e4b17023SJohn Marino hashval_t h = 0;
731*e4b17023SJohn Marino tree list;
732*e4b17023SJohn Marino
733*e4b17023SJohn Marino for (list = entry->t; list ; list = TREE_CHAIN (list))
734*e4b17023SJohn Marino h = (h << 5) + (h >> 27) + TREE_HASH (TREE_VALUE (list));
735*e4b17023SJohn Marino return h;
736*e4b17023SJohn Marino }
737*e4b17023SJohn Marino
738*e4b17023SJohn Marino /* Add TYPE (which may be NULL) to cfun->eh->ttype_data, using TYPES_HASH
739*e4b17023SJohn Marino to speed up the search. Return the filter value to be used. */
740*e4b17023SJohn Marino
741*e4b17023SJohn Marino static int
add_ttypes_entry(htab_t ttypes_hash,tree type)742*e4b17023SJohn Marino add_ttypes_entry (htab_t ttypes_hash, tree type)
743*e4b17023SJohn Marino {
744*e4b17023SJohn Marino struct ttypes_filter **slot, *n;
745*e4b17023SJohn Marino
746*e4b17023SJohn Marino slot = (struct ttypes_filter **)
747*e4b17023SJohn Marino htab_find_slot_with_hash (ttypes_hash, type, TREE_HASH (type), INSERT);
748*e4b17023SJohn Marino
749*e4b17023SJohn Marino if ((n = *slot) == NULL)
750*e4b17023SJohn Marino {
751*e4b17023SJohn Marino /* Filter value is a 1 based table index. */
752*e4b17023SJohn Marino
753*e4b17023SJohn Marino n = XNEW (struct ttypes_filter);
754*e4b17023SJohn Marino n->t = type;
755*e4b17023SJohn Marino n->filter = VEC_length (tree, cfun->eh->ttype_data) + 1;
756*e4b17023SJohn Marino *slot = n;
757*e4b17023SJohn Marino
758*e4b17023SJohn Marino VEC_safe_push (tree, gc, cfun->eh->ttype_data, type);
759*e4b17023SJohn Marino }
760*e4b17023SJohn Marino
761*e4b17023SJohn Marino return n->filter;
762*e4b17023SJohn Marino }
763*e4b17023SJohn Marino
764*e4b17023SJohn Marino /* Add LIST to cfun->eh->ehspec_data, using EHSPEC_HASH and TYPES_HASH
765*e4b17023SJohn Marino to speed up the search. Return the filter value to be used. */
766*e4b17023SJohn Marino
767*e4b17023SJohn Marino static int
add_ehspec_entry(htab_t ehspec_hash,htab_t ttypes_hash,tree list)768*e4b17023SJohn Marino add_ehspec_entry (htab_t ehspec_hash, htab_t ttypes_hash, tree list)
769*e4b17023SJohn Marino {
770*e4b17023SJohn Marino struct ttypes_filter **slot, *n;
771*e4b17023SJohn Marino struct ttypes_filter dummy;
772*e4b17023SJohn Marino
773*e4b17023SJohn Marino dummy.t = list;
774*e4b17023SJohn Marino slot = (struct ttypes_filter **)
775*e4b17023SJohn Marino htab_find_slot (ehspec_hash, &dummy, INSERT);
776*e4b17023SJohn Marino
777*e4b17023SJohn Marino if ((n = *slot) == NULL)
778*e4b17023SJohn Marino {
779*e4b17023SJohn Marino int len;
780*e4b17023SJohn Marino
781*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder)
782*e4b17023SJohn Marino len = VEC_length (tree, cfun->eh->ehspec_data.arm_eabi);
783*e4b17023SJohn Marino else
784*e4b17023SJohn Marino len = VEC_length (uchar, cfun->eh->ehspec_data.other);
785*e4b17023SJohn Marino
786*e4b17023SJohn Marino /* Filter value is a -1 based byte index into a uleb128 buffer. */
787*e4b17023SJohn Marino
788*e4b17023SJohn Marino n = XNEW (struct ttypes_filter);
789*e4b17023SJohn Marino n->t = list;
790*e4b17023SJohn Marino n->filter = -(len + 1);
791*e4b17023SJohn Marino *slot = n;
792*e4b17023SJohn Marino
793*e4b17023SJohn Marino /* Generate a 0 terminated list of filter values. */
794*e4b17023SJohn Marino for (; list ; list = TREE_CHAIN (list))
795*e4b17023SJohn Marino {
796*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder)
797*e4b17023SJohn Marino VEC_safe_push (tree, gc, cfun->eh->ehspec_data.arm_eabi,
798*e4b17023SJohn Marino TREE_VALUE (list));
799*e4b17023SJohn Marino else
800*e4b17023SJohn Marino {
801*e4b17023SJohn Marino /* Look up each type in the list and encode its filter
802*e4b17023SJohn Marino value as a uleb128. */
803*e4b17023SJohn Marino push_uleb128 (&cfun->eh->ehspec_data.other,
804*e4b17023SJohn Marino add_ttypes_entry (ttypes_hash, TREE_VALUE (list)));
805*e4b17023SJohn Marino }
806*e4b17023SJohn Marino }
807*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder)
808*e4b17023SJohn Marino VEC_safe_push (tree, gc, cfun->eh->ehspec_data.arm_eabi, NULL_TREE);
809*e4b17023SJohn Marino else
810*e4b17023SJohn Marino VEC_safe_push (uchar, gc, cfun->eh->ehspec_data.other, 0);
811*e4b17023SJohn Marino }
812*e4b17023SJohn Marino
813*e4b17023SJohn Marino return n->filter;
814*e4b17023SJohn Marino }
815*e4b17023SJohn Marino
816*e4b17023SJohn Marino /* Generate the action filter values to be used for CATCH and
817*e4b17023SJohn Marino ALLOWED_EXCEPTIONS regions. When using dwarf2 exception regions,
818*e4b17023SJohn Marino we use lots of landing pads, and so every type or list can share
819*e4b17023SJohn Marino the same filter value, which saves table space. */
820*e4b17023SJohn Marino
821*e4b17023SJohn Marino void
assign_filter_values(void)822*e4b17023SJohn Marino assign_filter_values (void)
823*e4b17023SJohn Marino {
824*e4b17023SJohn Marino int i;
825*e4b17023SJohn Marino htab_t ttypes, ehspec;
826*e4b17023SJohn Marino eh_region r;
827*e4b17023SJohn Marino eh_catch c;
828*e4b17023SJohn Marino
829*e4b17023SJohn Marino cfun->eh->ttype_data = VEC_alloc (tree, gc, 16);
830*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder)
831*e4b17023SJohn Marino cfun->eh->ehspec_data.arm_eabi = VEC_alloc (tree, gc, 64);
832*e4b17023SJohn Marino else
833*e4b17023SJohn Marino cfun->eh->ehspec_data.other = VEC_alloc (uchar, gc, 64);
834*e4b17023SJohn Marino
835*e4b17023SJohn Marino ttypes = htab_create (31, ttypes_filter_hash, ttypes_filter_eq, free);
836*e4b17023SJohn Marino ehspec = htab_create (31, ehspec_filter_hash, ehspec_filter_eq, free);
837*e4b17023SJohn Marino
838*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_region, cfun->eh->region_array, i, r); ++i)
839*e4b17023SJohn Marino {
840*e4b17023SJohn Marino if (r == NULL)
841*e4b17023SJohn Marino continue;
842*e4b17023SJohn Marino
843*e4b17023SJohn Marino switch (r->type)
844*e4b17023SJohn Marino {
845*e4b17023SJohn Marino case ERT_TRY:
846*e4b17023SJohn Marino for (c = r->u.eh_try.first_catch; c ; c = c->next_catch)
847*e4b17023SJohn Marino {
848*e4b17023SJohn Marino /* Whatever type_list is (NULL or true list), we build a list
849*e4b17023SJohn Marino of filters for the region. */
850*e4b17023SJohn Marino c->filter_list = NULL_TREE;
851*e4b17023SJohn Marino
852*e4b17023SJohn Marino if (c->type_list != NULL)
853*e4b17023SJohn Marino {
854*e4b17023SJohn Marino /* Get a filter value for each of the types caught and store
855*e4b17023SJohn Marino them in the region's dedicated list. */
856*e4b17023SJohn Marino tree tp_node = c->type_list;
857*e4b17023SJohn Marino
858*e4b17023SJohn Marino for ( ; tp_node; tp_node = TREE_CHAIN (tp_node))
859*e4b17023SJohn Marino {
860*e4b17023SJohn Marino int flt = add_ttypes_entry (ttypes, TREE_VALUE (tp_node));
861*e4b17023SJohn Marino tree flt_node = build_int_cst (integer_type_node, flt);
862*e4b17023SJohn Marino
863*e4b17023SJohn Marino c->filter_list
864*e4b17023SJohn Marino = tree_cons (NULL_TREE, flt_node, c->filter_list);
865*e4b17023SJohn Marino }
866*e4b17023SJohn Marino }
867*e4b17023SJohn Marino else
868*e4b17023SJohn Marino {
869*e4b17023SJohn Marino /* Get a filter value for the NULL list also since it
870*e4b17023SJohn Marino will need an action record anyway. */
871*e4b17023SJohn Marino int flt = add_ttypes_entry (ttypes, NULL);
872*e4b17023SJohn Marino tree flt_node = build_int_cst (integer_type_node, flt);
873*e4b17023SJohn Marino
874*e4b17023SJohn Marino c->filter_list
875*e4b17023SJohn Marino = tree_cons (NULL_TREE, flt_node, NULL);
876*e4b17023SJohn Marino }
877*e4b17023SJohn Marino }
878*e4b17023SJohn Marino break;
879*e4b17023SJohn Marino
880*e4b17023SJohn Marino case ERT_ALLOWED_EXCEPTIONS:
881*e4b17023SJohn Marino r->u.allowed.filter
882*e4b17023SJohn Marino = add_ehspec_entry (ehspec, ttypes, r->u.allowed.type_list);
883*e4b17023SJohn Marino break;
884*e4b17023SJohn Marino
885*e4b17023SJohn Marino default:
886*e4b17023SJohn Marino break;
887*e4b17023SJohn Marino }
888*e4b17023SJohn Marino }
889*e4b17023SJohn Marino
890*e4b17023SJohn Marino htab_delete (ttypes);
891*e4b17023SJohn Marino htab_delete (ehspec);
892*e4b17023SJohn Marino }
893*e4b17023SJohn Marino
894*e4b17023SJohn Marino /* Emit SEQ into basic block just before INSN (that is assumed to be
895*e4b17023SJohn Marino first instruction of some existing BB and return the newly
896*e4b17023SJohn Marino produced block. */
897*e4b17023SJohn Marino static basic_block
emit_to_new_bb_before(rtx seq,rtx insn)898*e4b17023SJohn Marino emit_to_new_bb_before (rtx seq, rtx insn)
899*e4b17023SJohn Marino {
900*e4b17023SJohn Marino rtx last;
901*e4b17023SJohn Marino basic_block bb;
902*e4b17023SJohn Marino edge e;
903*e4b17023SJohn Marino edge_iterator ei;
904*e4b17023SJohn Marino
905*e4b17023SJohn Marino /* If there happens to be a fallthru edge (possibly created by cleanup_cfg
906*e4b17023SJohn Marino call), we don't want it to go into newly created landing pad or other EH
907*e4b17023SJohn Marino construct. */
908*e4b17023SJohn Marino for (ei = ei_start (BLOCK_FOR_INSN (insn)->preds); (e = ei_safe_edge (ei)); )
909*e4b17023SJohn Marino if (e->flags & EDGE_FALLTHRU)
910*e4b17023SJohn Marino force_nonfallthru (e);
911*e4b17023SJohn Marino else
912*e4b17023SJohn Marino ei_next (&ei);
913*e4b17023SJohn Marino last = emit_insn_before (seq, insn);
914*e4b17023SJohn Marino if (BARRIER_P (last))
915*e4b17023SJohn Marino last = PREV_INSN (last);
916*e4b17023SJohn Marino bb = create_basic_block (seq, last, BLOCK_FOR_INSN (insn)->prev_bb);
917*e4b17023SJohn Marino update_bb_for_insn (bb);
918*e4b17023SJohn Marino bb->flags |= BB_SUPERBLOCK;
919*e4b17023SJohn Marino return bb;
920*e4b17023SJohn Marino }
921*e4b17023SJohn Marino
922*e4b17023SJohn Marino /* A subroutine of dw2_build_landing_pads, also used for edge splitting
923*e4b17023SJohn Marino at the rtl level. Emit the code required by the target at a landing
924*e4b17023SJohn Marino pad for the given region. */
925*e4b17023SJohn Marino
926*e4b17023SJohn Marino void
expand_dw2_landing_pad_for_region(eh_region region)927*e4b17023SJohn Marino expand_dw2_landing_pad_for_region (eh_region region)
928*e4b17023SJohn Marino {
929*e4b17023SJohn Marino #ifdef HAVE_exception_receiver
930*e4b17023SJohn Marino if (HAVE_exception_receiver)
931*e4b17023SJohn Marino emit_insn (gen_exception_receiver ());
932*e4b17023SJohn Marino else
933*e4b17023SJohn Marino #endif
934*e4b17023SJohn Marino #ifdef HAVE_nonlocal_goto_receiver
935*e4b17023SJohn Marino if (HAVE_nonlocal_goto_receiver)
936*e4b17023SJohn Marino emit_insn (gen_nonlocal_goto_receiver ());
937*e4b17023SJohn Marino else
938*e4b17023SJohn Marino #endif
939*e4b17023SJohn Marino { /* Nothing */ }
940*e4b17023SJohn Marino
941*e4b17023SJohn Marino if (region->exc_ptr_reg)
942*e4b17023SJohn Marino emit_move_insn (region->exc_ptr_reg,
943*e4b17023SJohn Marino gen_rtx_REG (ptr_mode, EH_RETURN_DATA_REGNO (0)));
944*e4b17023SJohn Marino if (region->filter_reg)
945*e4b17023SJohn Marino emit_move_insn (region->filter_reg,
946*e4b17023SJohn Marino gen_rtx_REG (targetm.eh_return_filter_mode (),
947*e4b17023SJohn Marino EH_RETURN_DATA_REGNO (1)));
948*e4b17023SJohn Marino }
949*e4b17023SJohn Marino
950*e4b17023SJohn Marino /* Expand the extra code needed at landing pads for dwarf2 unwinding. */
951*e4b17023SJohn Marino
952*e4b17023SJohn Marino static void
dw2_build_landing_pads(void)953*e4b17023SJohn Marino dw2_build_landing_pads (void)
954*e4b17023SJohn Marino {
955*e4b17023SJohn Marino int i;
956*e4b17023SJohn Marino eh_landing_pad lp;
957*e4b17023SJohn Marino int e_flags = EDGE_FALLTHRU;
958*e4b17023SJohn Marino
959*e4b17023SJohn Marino /* If we're going to partition blocks, we need to be able to add
960*e4b17023SJohn Marino new landing pads later, which means that we need to hold on to
961*e4b17023SJohn Marino the post-landing-pad block. Prevent it from being merged away.
962*e4b17023SJohn Marino We'll remove this bit after partitioning. */
963*e4b17023SJohn Marino if (flag_reorder_blocks_and_partition)
964*e4b17023SJohn Marino e_flags |= EDGE_PRESERVE;
965*e4b17023SJohn Marino
966*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_landing_pad, cfun->eh->lp_array, i, lp); ++i)
967*e4b17023SJohn Marino {
968*e4b17023SJohn Marino basic_block bb;
969*e4b17023SJohn Marino rtx seq;
970*e4b17023SJohn Marino edge e;
971*e4b17023SJohn Marino
972*e4b17023SJohn Marino if (lp == NULL || lp->post_landing_pad == NULL)
973*e4b17023SJohn Marino continue;
974*e4b17023SJohn Marino
975*e4b17023SJohn Marino start_sequence ();
976*e4b17023SJohn Marino
977*e4b17023SJohn Marino lp->landing_pad = gen_label_rtx ();
978*e4b17023SJohn Marino emit_label (lp->landing_pad);
979*e4b17023SJohn Marino LABEL_PRESERVE_P (lp->landing_pad) = 1;
980*e4b17023SJohn Marino
981*e4b17023SJohn Marino expand_dw2_landing_pad_for_region (lp->region);
982*e4b17023SJohn Marino
983*e4b17023SJohn Marino seq = get_insns ();
984*e4b17023SJohn Marino end_sequence ();
985*e4b17023SJohn Marino
986*e4b17023SJohn Marino bb = emit_to_new_bb_before (seq, label_rtx (lp->post_landing_pad));
987*e4b17023SJohn Marino e = make_edge (bb, bb->next_bb, e_flags);
988*e4b17023SJohn Marino e->count = bb->count;
989*e4b17023SJohn Marino e->probability = REG_BR_PROB_BASE;
990*e4b17023SJohn Marino }
991*e4b17023SJohn Marino }
992*e4b17023SJohn Marino
993*e4b17023SJohn Marino
994*e4b17023SJohn Marino static VEC (int, heap) *sjlj_lp_call_site_index;
995*e4b17023SJohn Marino
996*e4b17023SJohn Marino /* Process all active landing pads. Assign each one a compact dispatch
997*e4b17023SJohn Marino index, and a call-site index. */
998*e4b17023SJohn Marino
999*e4b17023SJohn Marino static int
sjlj_assign_call_site_values(void)1000*e4b17023SJohn Marino sjlj_assign_call_site_values (void)
1001*e4b17023SJohn Marino {
1002*e4b17023SJohn Marino htab_t ar_hash;
1003*e4b17023SJohn Marino int i, disp_index;
1004*e4b17023SJohn Marino eh_landing_pad lp;
1005*e4b17023SJohn Marino
1006*e4b17023SJohn Marino crtl->eh.action_record_data = VEC_alloc (uchar, gc, 64);
1007*e4b17023SJohn Marino ar_hash = htab_create (31, action_record_hash, action_record_eq, free);
1008*e4b17023SJohn Marino
1009*e4b17023SJohn Marino disp_index = 0;
1010*e4b17023SJohn Marino call_site_base = 1;
1011*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_landing_pad, cfun->eh->lp_array, i, lp); ++i)
1012*e4b17023SJohn Marino if (lp && lp->post_landing_pad)
1013*e4b17023SJohn Marino {
1014*e4b17023SJohn Marino int action, call_site;
1015*e4b17023SJohn Marino
1016*e4b17023SJohn Marino /* First: build the action table. */
1017*e4b17023SJohn Marino action = collect_one_action_chain (ar_hash, lp->region);
1018*e4b17023SJohn Marino
1019*e4b17023SJohn Marino /* Next: assign call-site values. If dwarf2 terms, this would be
1020*e4b17023SJohn Marino the region number assigned by convert_to_eh_region_ranges, but
1021*e4b17023SJohn Marino handles no-action and must-not-throw differently. */
1022*e4b17023SJohn Marino /* Map must-not-throw to otherwise unused call-site index 0. */
1023*e4b17023SJohn Marino if (action == -2)
1024*e4b17023SJohn Marino call_site = 0;
1025*e4b17023SJohn Marino /* Map no-action to otherwise unused call-site index -1. */
1026*e4b17023SJohn Marino else if (action == -1)
1027*e4b17023SJohn Marino call_site = -1;
1028*e4b17023SJohn Marino /* Otherwise, look it up in the table. */
1029*e4b17023SJohn Marino else
1030*e4b17023SJohn Marino call_site = add_call_site (GEN_INT (disp_index), action, 0);
1031*e4b17023SJohn Marino VEC_replace (int, sjlj_lp_call_site_index, i, call_site);
1032*e4b17023SJohn Marino
1033*e4b17023SJohn Marino disp_index++;
1034*e4b17023SJohn Marino }
1035*e4b17023SJohn Marino
1036*e4b17023SJohn Marino htab_delete (ar_hash);
1037*e4b17023SJohn Marino
1038*e4b17023SJohn Marino return disp_index;
1039*e4b17023SJohn Marino }
1040*e4b17023SJohn Marino
1041*e4b17023SJohn Marino /* Emit code to record the current call-site index before every
1042*e4b17023SJohn Marino insn that can throw. */
1043*e4b17023SJohn Marino
1044*e4b17023SJohn Marino static void
sjlj_mark_call_sites(void)1045*e4b17023SJohn Marino sjlj_mark_call_sites (void)
1046*e4b17023SJohn Marino {
1047*e4b17023SJohn Marino int last_call_site = -2;
1048*e4b17023SJohn Marino rtx insn, mem;
1049*e4b17023SJohn Marino
1050*e4b17023SJohn Marino for (insn = get_insns (); insn ; insn = NEXT_INSN (insn))
1051*e4b17023SJohn Marino {
1052*e4b17023SJohn Marino eh_landing_pad lp;
1053*e4b17023SJohn Marino eh_region r;
1054*e4b17023SJohn Marino bool nothrow;
1055*e4b17023SJohn Marino int this_call_site;
1056*e4b17023SJohn Marino rtx before, p;
1057*e4b17023SJohn Marino
1058*e4b17023SJohn Marino /* Reset value tracking at extended basic block boundaries. */
1059*e4b17023SJohn Marino if (LABEL_P (insn))
1060*e4b17023SJohn Marino last_call_site = -2;
1061*e4b17023SJohn Marino
1062*e4b17023SJohn Marino if (! INSN_P (insn))
1063*e4b17023SJohn Marino continue;
1064*e4b17023SJohn Marino
1065*e4b17023SJohn Marino nothrow = get_eh_region_and_lp_from_rtx (insn, &r, &lp);
1066*e4b17023SJohn Marino if (nothrow)
1067*e4b17023SJohn Marino continue;
1068*e4b17023SJohn Marino if (lp)
1069*e4b17023SJohn Marino this_call_site = VEC_index (int, sjlj_lp_call_site_index, lp->index);
1070*e4b17023SJohn Marino else if (r == NULL)
1071*e4b17023SJohn Marino {
1072*e4b17023SJohn Marino /* Calls (and trapping insns) without notes are outside any
1073*e4b17023SJohn Marino exception handling region in this function. Mark them as
1074*e4b17023SJohn Marino no action. */
1075*e4b17023SJohn Marino this_call_site = -1;
1076*e4b17023SJohn Marino }
1077*e4b17023SJohn Marino else
1078*e4b17023SJohn Marino {
1079*e4b17023SJohn Marino gcc_assert (r->type == ERT_MUST_NOT_THROW);
1080*e4b17023SJohn Marino this_call_site = 0;
1081*e4b17023SJohn Marino }
1082*e4b17023SJohn Marino
1083*e4b17023SJohn Marino if (this_call_site != -1)
1084*e4b17023SJohn Marino crtl->uses_eh_lsda = 1;
1085*e4b17023SJohn Marino
1086*e4b17023SJohn Marino if (this_call_site == last_call_site)
1087*e4b17023SJohn Marino continue;
1088*e4b17023SJohn Marino
1089*e4b17023SJohn Marino /* Don't separate a call from it's argument loads. */
1090*e4b17023SJohn Marino before = insn;
1091*e4b17023SJohn Marino if (CALL_P (insn))
1092*e4b17023SJohn Marino before = find_first_parameter_load (insn, NULL_RTX);
1093*e4b17023SJohn Marino
1094*e4b17023SJohn Marino start_sequence ();
1095*e4b17023SJohn Marino mem = adjust_address (crtl->eh.sjlj_fc, TYPE_MODE (integer_type_node),
1096*e4b17023SJohn Marino sjlj_fc_call_site_ofs);
1097*e4b17023SJohn Marino emit_move_insn (mem, GEN_INT (this_call_site));
1098*e4b17023SJohn Marino p = get_insns ();
1099*e4b17023SJohn Marino end_sequence ();
1100*e4b17023SJohn Marino
1101*e4b17023SJohn Marino emit_insn_before (p, before);
1102*e4b17023SJohn Marino last_call_site = this_call_site;
1103*e4b17023SJohn Marino }
1104*e4b17023SJohn Marino }
1105*e4b17023SJohn Marino
1106*e4b17023SJohn Marino /* Construct the SjLj_Function_Context. */
1107*e4b17023SJohn Marino
1108*e4b17023SJohn Marino static void
sjlj_emit_function_enter(rtx dispatch_label)1109*e4b17023SJohn Marino sjlj_emit_function_enter (rtx dispatch_label)
1110*e4b17023SJohn Marino {
1111*e4b17023SJohn Marino rtx fn_begin, fc, mem, seq;
1112*e4b17023SJohn Marino bool fn_begin_outside_block;
1113*e4b17023SJohn Marino rtx personality = get_personality_function (current_function_decl);
1114*e4b17023SJohn Marino
1115*e4b17023SJohn Marino fc = crtl->eh.sjlj_fc;
1116*e4b17023SJohn Marino
1117*e4b17023SJohn Marino start_sequence ();
1118*e4b17023SJohn Marino
1119*e4b17023SJohn Marino /* We're storing this libcall's address into memory instead of
1120*e4b17023SJohn Marino calling it directly. Thus, we must call assemble_external_libcall
1121*e4b17023SJohn Marino here, as we can not depend on emit_library_call to do it for us. */
1122*e4b17023SJohn Marino assemble_external_libcall (personality);
1123*e4b17023SJohn Marino mem = adjust_address (fc, Pmode, sjlj_fc_personality_ofs);
1124*e4b17023SJohn Marino emit_move_insn (mem, personality);
1125*e4b17023SJohn Marino
1126*e4b17023SJohn Marino mem = adjust_address (fc, Pmode, sjlj_fc_lsda_ofs);
1127*e4b17023SJohn Marino if (crtl->uses_eh_lsda)
1128*e4b17023SJohn Marino {
1129*e4b17023SJohn Marino char buf[20];
1130*e4b17023SJohn Marino rtx sym;
1131*e4b17023SJohn Marino
1132*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (buf, "LLSDA", current_function_funcdef_no);
1133*e4b17023SJohn Marino sym = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (buf));
1134*e4b17023SJohn Marino SYMBOL_REF_FLAGS (sym) = SYMBOL_FLAG_LOCAL;
1135*e4b17023SJohn Marino emit_move_insn (mem, sym);
1136*e4b17023SJohn Marino }
1137*e4b17023SJohn Marino else
1138*e4b17023SJohn Marino emit_move_insn (mem, const0_rtx);
1139*e4b17023SJohn Marino
1140*e4b17023SJohn Marino if (dispatch_label)
1141*e4b17023SJohn Marino {
1142*e4b17023SJohn Marino #ifdef DONT_USE_BUILTIN_SETJMP
1143*e4b17023SJohn Marino rtx x, last;
1144*e4b17023SJohn Marino x = emit_library_call_value (setjmp_libfunc, NULL_RTX, LCT_RETURNS_TWICE,
1145*e4b17023SJohn Marino TYPE_MODE (integer_type_node), 1,
1146*e4b17023SJohn Marino plus_constant (XEXP (fc, 0),
1147*e4b17023SJohn Marino sjlj_fc_jbuf_ofs), Pmode);
1148*e4b17023SJohn Marino
1149*e4b17023SJohn Marino emit_cmp_and_jump_insns (x, const0_rtx, NE, 0,
1150*e4b17023SJohn Marino TYPE_MODE (integer_type_node), 0,
1151*e4b17023SJohn Marino dispatch_label);
1152*e4b17023SJohn Marino last = get_last_insn ();
1153*e4b17023SJohn Marino if (JUMP_P (last) && any_condjump_p (last))
1154*e4b17023SJohn Marino {
1155*e4b17023SJohn Marino gcc_assert (!find_reg_note (last, REG_BR_PROB, 0));
1156*e4b17023SJohn Marino add_reg_note (last, REG_BR_PROB, GEN_INT (REG_BR_PROB_BASE / 100));
1157*e4b17023SJohn Marino }
1158*e4b17023SJohn Marino #else
1159*e4b17023SJohn Marino expand_builtin_setjmp_setup (plus_constant (XEXP (fc, 0),
1160*e4b17023SJohn Marino sjlj_fc_jbuf_ofs),
1161*e4b17023SJohn Marino dispatch_label);
1162*e4b17023SJohn Marino #endif
1163*e4b17023SJohn Marino }
1164*e4b17023SJohn Marino
1165*e4b17023SJohn Marino emit_library_call (unwind_sjlj_register_libfunc, LCT_NORMAL, VOIDmode,
1166*e4b17023SJohn Marino 1, XEXP (fc, 0), Pmode);
1167*e4b17023SJohn Marino
1168*e4b17023SJohn Marino seq = get_insns ();
1169*e4b17023SJohn Marino end_sequence ();
1170*e4b17023SJohn Marino
1171*e4b17023SJohn Marino /* ??? Instead of doing this at the beginning of the function,
1172*e4b17023SJohn Marino do this in a block that is at loop level 0 and dominates all
1173*e4b17023SJohn Marino can_throw_internal instructions. */
1174*e4b17023SJohn Marino
1175*e4b17023SJohn Marino fn_begin_outside_block = true;
1176*e4b17023SJohn Marino for (fn_begin = get_insns (); ; fn_begin = NEXT_INSN (fn_begin))
1177*e4b17023SJohn Marino if (NOTE_P (fn_begin))
1178*e4b17023SJohn Marino {
1179*e4b17023SJohn Marino if (NOTE_KIND (fn_begin) == NOTE_INSN_FUNCTION_BEG)
1180*e4b17023SJohn Marino break;
1181*e4b17023SJohn Marino else if (NOTE_INSN_BASIC_BLOCK_P (fn_begin))
1182*e4b17023SJohn Marino fn_begin_outside_block = false;
1183*e4b17023SJohn Marino }
1184*e4b17023SJohn Marino
1185*e4b17023SJohn Marino if (fn_begin_outside_block)
1186*e4b17023SJohn Marino insert_insn_on_edge (seq, single_succ_edge (ENTRY_BLOCK_PTR));
1187*e4b17023SJohn Marino else
1188*e4b17023SJohn Marino emit_insn_after (seq, fn_begin);
1189*e4b17023SJohn Marino }
1190*e4b17023SJohn Marino
1191*e4b17023SJohn Marino /* Call back from expand_function_end to know where we should put
1192*e4b17023SJohn Marino the call to unwind_sjlj_unregister_libfunc if needed. */
1193*e4b17023SJohn Marino
1194*e4b17023SJohn Marino void
sjlj_emit_function_exit_after(rtx after)1195*e4b17023SJohn Marino sjlj_emit_function_exit_after (rtx after)
1196*e4b17023SJohn Marino {
1197*e4b17023SJohn Marino crtl->eh.sjlj_exit_after = after;
1198*e4b17023SJohn Marino }
1199*e4b17023SJohn Marino
1200*e4b17023SJohn Marino static void
sjlj_emit_function_exit(void)1201*e4b17023SJohn Marino sjlj_emit_function_exit (void)
1202*e4b17023SJohn Marino {
1203*e4b17023SJohn Marino rtx seq, insn;
1204*e4b17023SJohn Marino
1205*e4b17023SJohn Marino start_sequence ();
1206*e4b17023SJohn Marino
1207*e4b17023SJohn Marino emit_library_call (unwind_sjlj_unregister_libfunc, LCT_NORMAL, VOIDmode,
1208*e4b17023SJohn Marino 1, XEXP (crtl->eh.sjlj_fc, 0), Pmode);
1209*e4b17023SJohn Marino
1210*e4b17023SJohn Marino seq = get_insns ();
1211*e4b17023SJohn Marino end_sequence ();
1212*e4b17023SJohn Marino
1213*e4b17023SJohn Marino /* ??? Really this can be done in any block at loop level 0 that
1214*e4b17023SJohn Marino post-dominates all can_throw_internal instructions. This is
1215*e4b17023SJohn Marino the last possible moment. */
1216*e4b17023SJohn Marino
1217*e4b17023SJohn Marino insn = crtl->eh.sjlj_exit_after;
1218*e4b17023SJohn Marino if (LABEL_P (insn))
1219*e4b17023SJohn Marino insn = NEXT_INSN (insn);
1220*e4b17023SJohn Marino
1221*e4b17023SJohn Marino emit_insn_after (seq, insn);
1222*e4b17023SJohn Marino }
1223*e4b17023SJohn Marino
1224*e4b17023SJohn Marino static void
sjlj_emit_dispatch_table(rtx dispatch_label,int num_dispatch)1225*e4b17023SJohn Marino sjlj_emit_dispatch_table (rtx dispatch_label, int num_dispatch)
1226*e4b17023SJohn Marino {
1227*e4b17023SJohn Marino enum machine_mode unwind_word_mode = targetm.unwind_word_mode ();
1228*e4b17023SJohn Marino enum machine_mode filter_mode = targetm.eh_return_filter_mode ();
1229*e4b17023SJohn Marino eh_landing_pad lp;
1230*e4b17023SJohn Marino rtx mem, seq, fc, before, exc_ptr_reg, filter_reg;
1231*e4b17023SJohn Marino rtx first_reachable_label;
1232*e4b17023SJohn Marino basic_block bb;
1233*e4b17023SJohn Marino eh_region r;
1234*e4b17023SJohn Marino edge e;
1235*e4b17023SJohn Marino int i, disp_index;
1236*e4b17023SJohn Marino gimple switch_stmt;
1237*e4b17023SJohn Marino
1238*e4b17023SJohn Marino fc = crtl->eh.sjlj_fc;
1239*e4b17023SJohn Marino
1240*e4b17023SJohn Marino start_sequence ();
1241*e4b17023SJohn Marino
1242*e4b17023SJohn Marino emit_label (dispatch_label);
1243*e4b17023SJohn Marino
1244*e4b17023SJohn Marino #ifndef DONT_USE_BUILTIN_SETJMP
1245*e4b17023SJohn Marino expand_builtin_setjmp_receiver (dispatch_label);
1246*e4b17023SJohn Marino
1247*e4b17023SJohn Marino /* The caller of expand_builtin_setjmp_receiver is responsible for
1248*e4b17023SJohn Marino making sure that the label doesn't vanish. The only other caller
1249*e4b17023SJohn Marino is the expander for __builtin_setjmp_receiver, which places this
1250*e4b17023SJohn Marino label on the nonlocal_goto_label list. Since we're modeling these
1251*e4b17023SJohn Marino CFG edges more exactly, we can use the forced_labels list instead. */
1252*e4b17023SJohn Marino LABEL_PRESERVE_P (dispatch_label) = 1;
1253*e4b17023SJohn Marino forced_labels
1254*e4b17023SJohn Marino = gen_rtx_EXPR_LIST (VOIDmode, dispatch_label, forced_labels);
1255*e4b17023SJohn Marino #endif
1256*e4b17023SJohn Marino
1257*e4b17023SJohn Marino /* Load up exc_ptr and filter values from the function context. */
1258*e4b17023SJohn Marino mem = adjust_address (fc, unwind_word_mode, sjlj_fc_data_ofs);
1259*e4b17023SJohn Marino if (unwind_word_mode != ptr_mode)
1260*e4b17023SJohn Marino {
1261*e4b17023SJohn Marino #ifdef POINTERS_EXTEND_UNSIGNED
1262*e4b17023SJohn Marino mem = convert_memory_address (ptr_mode, mem);
1263*e4b17023SJohn Marino #else
1264*e4b17023SJohn Marino mem = convert_to_mode (ptr_mode, mem, 0);
1265*e4b17023SJohn Marino #endif
1266*e4b17023SJohn Marino }
1267*e4b17023SJohn Marino exc_ptr_reg = force_reg (ptr_mode, mem);
1268*e4b17023SJohn Marino
1269*e4b17023SJohn Marino mem = adjust_address (fc, unwind_word_mode,
1270*e4b17023SJohn Marino sjlj_fc_data_ofs + GET_MODE_SIZE (unwind_word_mode));
1271*e4b17023SJohn Marino if (unwind_word_mode != filter_mode)
1272*e4b17023SJohn Marino mem = convert_to_mode (filter_mode, mem, 0);
1273*e4b17023SJohn Marino filter_reg = force_reg (filter_mode, mem);
1274*e4b17023SJohn Marino
1275*e4b17023SJohn Marino /* Jump to one of the directly reachable regions. */
1276*e4b17023SJohn Marino
1277*e4b17023SJohn Marino disp_index = 0;
1278*e4b17023SJohn Marino first_reachable_label = NULL;
1279*e4b17023SJohn Marino
1280*e4b17023SJohn Marino /* If there's exactly one call site in the function, don't bother
1281*e4b17023SJohn Marino generating a switch statement. */
1282*e4b17023SJohn Marino switch_stmt = NULL;
1283*e4b17023SJohn Marino if (num_dispatch > 1)
1284*e4b17023SJohn Marino {
1285*e4b17023SJohn Marino tree disp;
1286*e4b17023SJohn Marino
1287*e4b17023SJohn Marino mem = adjust_address (fc, TYPE_MODE (integer_type_node),
1288*e4b17023SJohn Marino sjlj_fc_call_site_ofs);
1289*e4b17023SJohn Marino disp = make_tree (integer_type_node, mem);
1290*e4b17023SJohn Marino
1291*e4b17023SJohn Marino switch_stmt = gimple_build_switch_nlabels (num_dispatch, disp, NULL);
1292*e4b17023SJohn Marino }
1293*e4b17023SJohn Marino
1294*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_landing_pad, cfun->eh->lp_array, i, lp); ++i)
1295*e4b17023SJohn Marino if (lp && lp->post_landing_pad)
1296*e4b17023SJohn Marino {
1297*e4b17023SJohn Marino rtx seq2, label;
1298*e4b17023SJohn Marino
1299*e4b17023SJohn Marino start_sequence ();
1300*e4b17023SJohn Marino
1301*e4b17023SJohn Marino lp->landing_pad = dispatch_label;
1302*e4b17023SJohn Marino
1303*e4b17023SJohn Marino if (num_dispatch > 1)
1304*e4b17023SJohn Marino {
1305*e4b17023SJohn Marino tree t_label, case_elt, t;
1306*e4b17023SJohn Marino
1307*e4b17023SJohn Marino t_label = create_artificial_label (UNKNOWN_LOCATION);
1308*e4b17023SJohn Marino t = build_int_cst (integer_type_node, disp_index);
1309*e4b17023SJohn Marino case_elt = build_case_label (t, NULL, t_label);
1310*e4b17023SJohn Marino gimple_switch_set_label (switch_stmt, disp_index, case_elt);
1311*e4b17023SJohn Marino
1312*e4b17023SJohn Marino label = label_rtx (t_label);
1313*e4b17023SJohn Marino }
1314*e4b17023SJohn Marino else
1315*e4b17023SJohn Marino label = gen_label_rtx ();
1316*e4b17023SJohn Marino
1317*e4b17023SJohn Marino if (disp_index == 0)
1318*e4b17023SJohn Marino first_reachable_label = label;
1319*e4b17023SJohn Marino emit_label (label);
1320*e4b17023SJohn Marino
1321*e4b17023SJohn Marino r = lp->region;
1322*e4b17023SJohn Marino if (r->exc_ptr_reg)
1323*e4b17023SJohn Marino emit_move_insn (r->exc_ptr_reg, exc_ptr_reg);
1324*e4b17023SJohn Marino if (r->filter_reg)
1325*e4b17023SJohn Marino emit_move_insn (r->filter_reg, filter_reg);
1326*e4b17023SJohn Marino
1327*e4b17023SJohn Marino seq2 = get_insns ();
1328*e4b17023SJohn Marino end_sequence ();
1329*e4b17023SJohn Marino
1330*e4b17023SJohn Marino before = label_rtx (lp->post_landing_pad);
1331*e4b17023SJohn Marino bb = emit_to_new_bb_before (seq2, before);
1332*e4b17023SJohn Marino e = make_edge (bb, bb->next_bb, EDGE_FALLTHRU);
1333*e4b17023SJohn Marino e->count = bb->count;
1334*e4b17023SJohn Marino e->probability = REG_BR_PROB_BASE;
1335*e4b17023SJohn Marino
1336*e4b17023SJohn Marino disp_index++;
1337*e4b17023SJohn Marino }
1338*e4b17023SJohn Marino gcc_assert (disp_index == num_dispatch);
1339*e4b17023SJohn Marino
1340*e4b17023SJohn Marino if (num_dispatch > 1)
1341*e4b17023SJohn Marino {
1342*e4b17023SJohn Marino expand_case (switch_stmt);
1343*e4b17023SJohn Marino expand_builtin_trap ();
1344*e4b17023SJohn Marino }
1345*e4b17023SJohn Marino
1346*e4b17023SJohn Marino seq = get_insns ();
1347*e4b17023SJohn Marino end_sequence ();
1348*e4b17023SJohn Marino
1349*e4b17023SJohn Marino bb = emit_to_new_bb_before (seq, first_reachable_label);
1350*e4b17023SJohn Marino if (num_dispatch == 1)
1351*e4b17023SJohn Marino {
1352*e4b17023SJohn Marino e = make_edge (bb, bb->next_bb, EDGE_FALLTHRU);
1353*e4b17023SJohn Marino e->count = bb->count;
1354*e4b17023SJohn Marino e->probability = REG_BR_PROB_BASE;
1355*e4b17023SJohn Marino }
1356*e4b17023SJohn Marino }
1357*e4b17023SJohn Marino
1358*e4b17023SJohn Marino static void
sjlj_build_landing_pads(void)1359*e4b17023SJohn Marino sjlj_build_landing_pads (void)
1360*e4b17023SJohn Marino {
1361*e4b17023SJohn Marino int num_dispatch;
1362*e4b17023SJohn Marino
1363*e4b17023SJohn Marino num_dispatch = VEC_length (eh_landing_pad, cfun->eh->lp_array);
1364*e4b17023SJohn Marino if (num_dispatch == 0)
1365*e4b17023SJohn Marino return;
1366*e4b17023SJohn Marino VEC_safe_grow (int, heap, sjlj_lp_call_site_index, num_dispatch);
1367*e4b17023SJohn Marino
1368*e4b17023SJohn Marino num_dispatch = sjlj_assign_call_site_values ();
1369*e4b17023SJohn Marino if (num_dispatch > 0)
1370*e4b17023SJohn Marino {
1371*e4b17023SJohn Marino rtx dispatch_label = gen_label_rtx ();
1372*e4b17023SJohn Marino int align = STACK_SLOT_ALIGNMENT (sjlj_fc_type_node,
1373*e4b17023SJohn Marino TYPE_MODE (sjlj_fc_type_node),
1374*e4b17023SJohn Marino TYPE_ALIGN (sjlj_fc_type_node));
1375*e4b17023SJohn Marino crtl->eh.sjlj_fc
1376*e4b17023SJohn Marino = assign_stack_local (TYPE_MODE (sjlj_fc_type_node),
1377*e4b17023SJohn Marino int_size_in_bytes (sjlj_fc_type_node),
1378*e4b17023SJohn Marino align);
1379*e4b17023SJohn Marino
1380*e4b17023SJohn Marino sjlj_mark_call_sites ();
1381*e4b17023SJohn Marino sjlj_emit_function_enter (dispatch_label);
1382*e4b17023SJohn Marino sjlj_emit_dispatch_table (dispatch_label, num_dispatch);
1383*e4b17023SJohn Marino sjlj_emit_function_exit ();
1384*e4b17023SJohn Marino }
1385*e4b17023SJohn Marino
1386*e4b17023SJohn Marino /* If we do not have any landing pads, we may still need to register a
1387*e4b17023SJohn Marino personality routine and (empty) LSDA to handle must-not-throw regions. */
1388*e4b17023SJohn Marino else if (function_needs_eh_personality (cfun) != eh_personality_none)
1389*e4b17023SJohn Marino {
1390*e4b17023SJohn Marino int align = STACK_SLOT_ALIGNMENT (sjlj_fc_type_node,
1391*e4b17023SJohn Marino TYPE_MODE (sjlj_fc_type_node),
1392*e4b17023SJohn Marino TYPE_ALIGN (sjlj_fc_type_node));
1393*e4b17023SJohn Marino crtl->eh.sjlj_fc
1394*e4b17023SJohn Marino = assign_stack_local (TYPE_MODE (sjlj_fc_type_node),
1395*e4b17023SJohn Marino int_size_in_bytes (sjlj_fc_type_node),
1396*e4b17023SJohn Marino align);
1397*e4b17023SJohn Marino
1398*e4b17023SJohn Marino sjlj_mark_call_sites ();
1399*e4b17023SJohn Marino sjlj_emit_function_enter (NULL_RTX);
1400*e4b17023SJohn Marino sjlj_emit_function_exit ();
1401*e4b17023SJohn Marino }
1402*e4b17023SJohn Marino
1403*e4b17023SJohn Marino VEC_free (int, heap, sjlj_lp_call_site_index);
1404*e4b17023SJohn Marino }
1405*e4b17023SJohn Marino
1406*e4b17023SJohn Marino /* After initial rtl generation, call back to finish generating
1407*e4b17023SJohn Marino exception support code. */
1408*e4b17023SJohn Marino
1409*e4b17023SJohn Marino static void
finish_eh_generation(void)1410*e4b17023SJohn Marino finish_eh_generation (void)
1411*e4b17023SJohn Marino {
1412*e4b17023SJohn Marino basic_block bb;
1413*e4b17023SJohn Marino
1414*e4b17023SJohn Marino /* Construct the landing pads. */
1415*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
1416*e4b17023SJohn Marino sjlj_build_landing_pads ();
1417*e4b17023SJohn Marino else
1418*e4b17023SJohn Marino dw2_build_landing_pads ();
1419*e4b17023SJohn Marino break_superblocks ();
1420*e4b17023SJohn Marino
1421*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ
1422*e4b17023SJohn Marino /* Kludge for Alpha/Tru64 (see alpha_gp_save_rtx). */
1423*e4b17023SJohn Marino || single_succ_edge (ENTRY_BLOCK_PTR)->insns.r)
1424*e4b17023SJohn Marino commit_edge_insertions ();
1425*e4b17023SJohn Marino
1426*e4b17023SJohn Marino /* Redirect all EH edges from the post_landing_pad to the landing pad. */
1427*e4b17023SJohn Marino FOR_EACH_BB (bb)
1428*e4b17023SJohn Marino {
1429*e4b17023SJohn Marino eh_landing_pad lp;
1430*e4b17023SJohn Marino edge_iterator ei;
1431*e4b17023SJohn Marino edge e;
1432*e4b17023SJohn Marino
1433*e4b17023SJohn Marino lp = get_eh_landing_pad_from_rtx (BB_END (bb));
1434*e4b17023SJohn Marino
1435*e4b17023SJohn Marino FOR_EACH_EDGE (e, ei, bb->succs)
1436*e4b17023SJohn Marino if (e->flags & EDGE_EH)
1437*e4b17023SJohn Marino break;
1438*e4b17023SJohn Marino
1439*e4b17023SJohn Marino /* We should not have generated any new throwing insns during this
1440*e4b17023SJohn Marino pass, and we should not have lost any EH edges, so we only need
1441*e4b17023SJohn Marino to handle two cases here:
1442*e4b17023SJohn Marino (1) reachable handler and an existing edge to post-landing-pad,
1443*e4b17023SJohn Marino (2) no reachable handler and no edge. */
1444*e4b17023SJohn Marino gcc_assert ((lp != NULL) == (e != NULL));
1445*e4b17023SJohn Marino if (lp != NULL)
1446*e4b17023SJohn Marino {
1447*e4b17023SJohn Marino gcc_assert (BB_HEAD (e->dest) == label_rtx (lp->post_landing_pad));
1448*e4b17023SJohn Marino
1449*e4b17023SJohn Marino redirect_edge_succ (e, BLOCK_FOR_INSN (lp->landing_pad));
1450*e4b17023SJohn Marino e->flags |= (CALL_P (BB_END (bb))
1451*e4b17023SJohn Marino ? EDGE_ABNORMAL | EDGE_ABNORMAL_CALL
1452*e4b17023SJohn Marino : EDGE_ABNORMAL);
1453*e4b17023SJohn Marino }
1454*e4b17023SJohn Marino }
1455*e4b17023SJohn Marino }
1456*e4b17023SJohn Marino
1457*e4b17023SJohn Marino static bool
gate_handle_eh(void)1458*e4b17023SJohn Marino gate_handle_eh (void)
1459*e4b17023SJohn Marino {
1460*e4b17023SJohn Marino /* Nothing to do if no regions created. */
1461*e4b17023SJohn Marino return cfun->eh->region_tree != NULL;
1462*e4b17023SJohn Marino }
1463*e4b17023SJohn Marino
1464*e4b17023SJohn Marino /* Complete generation of exception handling code. */
1465*e4b17023SJohn Marino static unsigned int
rest_of_handle_eh(void)1466*e4b17023SJohn Marino rest_of_handle_eh (void)
1467*e4b17023SJohn Marino {
1468*e4b17023SJohn Marino finish_eh_generation ();
1469*e4b17023SJohn Marino cleanup_cfg (CLEANUP_NO_INSN_DEL);
1470*e4b17023SJohn Marino return 0;
1471*e4b17023SJohn Marino }
1472*e4b17023SJohn Marino
1473*e4b17023SJohn Marino struct rtl_opt_pass pass_rtl_eh =
1474*e4b17023SJohn Marino {
1475*e4b17023SJohn Marino {
1476*e4b17023SJohn Marino RTL_PASS,
1477*e4b17023SJohn Marino "rtl_eh", /* name */
1478*e4b17023SJohn Marino gate_handle_eh, /* gate */
1479*e4b17023SJohn Marino rest_of_handle_eh, /* execute */
1480*e4b17023SJohn Marino NULL, /* sub */
1481*e4b17023SJohn Marino NULL, /* next */
1482*e4b17023SJohn Marino 0, /* static_pass_number */
1483*e4b17023SJohn Marino TV_JUMP, /* tv_id */
1484*e4b17023SJohn Marino 0, /* properties_required */
1485*e4b17023SJohn Marino 0, /* properties_provided */
1486*e4b17023SJohn Marino 0, /* properties_destroyed */
1487*e4b17023SJohn Marino 0, /* todo_flags_start */
1488*e4b17023SJohn Marino 0 /* todo_flags_finish */
1489*e4b17023SJohn Marino }
1490*e4b17023SJohn Marino };
1491*e4b17023SJohn Marino
1492*e4b17023SJohn Marino /* This section handles removing dead code for flow. */
1493*e4b17023SJohn Marino
1494*e4b17023SJohn Marino void
remove_eh_landing_pad(eh_landing_pad lp)1495*e4b17023SJohn Marino remove_eh_landing_pad (eh_landing_pad lp)
1496*e4b17023SJohn Marino {
1497*e4b17023SJohn Marino eh_landing_pad *pp;
1498*e4b17023SJohn Marino
1499*e4b17023SJohn Marino for (pp = &lp->region->landing_pads; *pp != lp; pp = &(*pp)->next_lp)
1500*e4b17023SJohn Marino continue;
1501*e4b17023SJohn Marino *pp = lp->next_lp;
1502*e4b17023SJohn Marino
1503*e4b17023SJohn Marino if (lp->post_landing_pad)
1504*e4b17023SJohn Marino EH_LANDING_PAD_NR (lp->post_landing_pad) = 0;
1505*e4b17023SJohn Marino VEC_replace (eh_landing_pad, cfun->eh->lp_array, lp->index, NULL);
1506*e4b17023SJohn Marino }
1507*e4b17023SJohn Marino
1508*e4b17023SJohn Marino /* Splice REGION from the region tree. */
1509*e4b17023SJohn Marino
1510*e4b17023SJohn Marino void
remove_eh_handler(eh_region region)1511*e4b17023SJohn Marino remove_eh_handler (eh_region region)
1512*e4b17023SJohn Marino {
1513*e4b17023SJohn Marino eh_region *pp, *pp_start, p, outer;
1514*e4b17023SJohn Marino eh_landing_pad lp;
1515*e4b17023SJohn Marino
1516*e4b17023SJohn Marino for (lp = region->landing_pads; lp ; lp = lp->next_lp)
1517*e4b17023SJohn Marino {
1518*e4b17023SJohn Marino if (lp->post_landing_pad)
1519*e4b17023SJohn Marino EH_LANDING_PAD_NR (lp->post_landing_pad) = 0;
1520*e4b17023SJohn Marino VEC_replace (eh_landing_pad, cfun->eh->lp_array, lp->index, NULL);
1521*e4b17023SJohn Marino }
1522*e4b17023SJohn Marino
1523*e4b17023SJohn Marino outer = region->outer;
1524*e4b17023SJohn Marino if (outer)
1525*e4b17023SJohn Marino pp_start = &outer->inner;
1526*e4b17023SJohn Marino else
1527*e4b17023SJohn Marino pp_start = &cfun->eh->region_tree;
1528*e4b17023SJohn Marino for (pp = pp_start, p = *pp; p != region; pp = &p->next_peer, p = *pp)
1529*e4b17023SJohn Marino continue;
1530*e4b17023SJohn Marino if (region->inner)
1531*e4b17023SJohn Marino {
1532*e4b17023SJohn Marino *pp = p = region->inner;
1533*e4b17023SJohn Marino do
1534*e4b17023SJohn Marino {
1535*e4b17023SJohn Marino p->outer = outer;
1536*e4b17023SJohn Marino pp = &p->next_peer;
1537*e4b17023SJohn Marino p = *pp;
1538*e4b17023SJohn Marino }
1539*e4b17023SJohn Marino while (p);
1540*e4b17023SJohn Marino }
1541*e4b17023SJohn Marino *pp = region->next_peer;
1542*e4b17023SJohn Marino
1543*e4b17023SJohn Marino VEC_replace (eh_region, cfun->eh->region_array, region->index, NULL);
1544*e4b17023SJohn Marino }
1545*e4b17023SJohn Marino
1546*e4b17023SJohn Marino /* Invokes CALLBACK for every exception handler landing pad label.
1547*e4b17023SJohn Marino Only used by reload hackery; should not be used by new code. */
1548*e4b17023SJohn Marino
1549*e4b17023SJohn Marino void
for_each_eh_label(void (* callback)(rtx))1550*e4b17023SJohn Marino for_each_eh_label (void (*callback) (rtx))
1551*e4b17023SJohn Marino {
1552*e4b17023SJohn Marino eh_landing_pad lp;
1553*e4b17023SJohn Marino int i;
1554*e4b17023SJohn Marino
1555*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_landing_pad, cfun->eh->lp_array, i, lp); ++i)
1556*e4b17023SJohn Marino {
1557*e4b17023SJohn Marino if (lp)
1558*e4b17023SJohn Marino {
1559*e4b17023SJohn Marino rtx lab = lp->landing_pad;
1560*e4b17023SJohn Marino if (lab && LABEL_P (lab))
1561*e4b17023SJohn Marino (*callback) (lab);
1562*e4b17023SJohn Marino }
1563*e4b17023SJohn Marino }
1564*e4b17023SJohn Marino }
1565*e4b17023SJohn Marino
1566*e4b17023SJohn Marino /* Create the REG_EH_REGION note for INSN, given its ECF_FLAGS for a
1567*e4b17023SJohn Marino call insn.
1568*e4b17023SJohn Marino
1569*e4b17023SJohn Marino At the gimple level, we use LP_NR
1570*e4b17023SJohn Marino > 0 : The statement transfers to landing pad LP_NR
1571*e4b17023SJohn Marino = 0 : The statement is outside any EH region
1572*e4b17023SJohn Marino < 0 : The statement is within MUST_NOT_THROW region -LP_NR.
1573*e4b17023SJohn Marino
1574*e4b17023SJohn Marino At the rtl level, we use LP_NR
1575*e4b17023SJohn Marino > 0 : The insn transfers to landing pad LP_NR
1576*e4b17023SJohn Marino = 0 : The insn cannot throw
1577*e4b17023SJohn Marino < 0 : The insn is within MUST_NOT_THROW region -LP_NR
1578*e4b17023SJohn Marino = INT_MIN : The insn cannot throw or execute a nonlocal-goto.
1579*e4b17023SJohn Marino missing note: The insn is outside any EH region.
1580*e4b17023SJohn Marino
1581*e4b17023SJohn Marino ??? This difference probably ought to be avoided. We could stand
1582*e4b17023SJohn Marino to record nothrow for arbitrary gimple statements, and so avoid
1583*e4b17023SJohn Marino some moderately complex lookups in stmt_could_throw_p. Perhaps
1584*e4b17023SJohn Marino NOTHROW should be mapped on both sides to INT_MIN. Perhaps the
1585*e4b17023SJohn Marino no-nonlocal-goto property should be recorded elsewhere as a bit
1586*e4b17023SJohn Marino on the call_insn directly. Perhaps we should make more use of
1587*e4b17023SJohn Marino attaching the trees to call_insns (reachable via symbol_ref in
1588*e4b17023SJohn Marino direct call cases) and just pull the data out of the trees. */
1589*e4b17023SJohn Marino
1590*e4b17023SJohn Marino void
make_reg_eh_region_note(rtx insn,int ecf_flags,int lp_nr)1591*e4b17023SJohn Marino make_reg_eh_region_note (rtx insn, int ecf_flags, int lp_nr)
1592*e4b17023SJohn Marino {
1593*e4b17023SJohn Marino rtx value;
1594*e4b17023SJohn Marino if (ecf_flags & ECF_NOTHROW)
1595*e4b17023SJohn Marino value = const0_rtx;
1596*e4b17023SJohn Marino else if (lp_nr != 0)
1597*e4b17023SJohn Marino value = GEN_INT (lp_nr);
1598*e4b17023SJohn Marino else
1599*e4b17023SJohn Marino return;
1600*e4b17023SJohn Marino add_reg_note (insn, REG_EH_REGION, value);
1601*e4b17023SJohn Marino }
1602*e4b17023SJohn Marino
1603*e4b17023SJohn Marino /* Create a REG_EH_REGION note for a CALL_INSN that cannot throw
1604*e4b17023SJohn Marino nor perform a non-local goto. Replace the region note if it
1605*e4b17023SJohn Marino already exists. */
1606*e4b17023SJohn Marino
1607*e4b17023SJohn Marino void
make_reg_eh_region_note_nothrow_nononlocal(rtx insn)1608*e4b17023SJohn Marino make_reg_eh_region_note_nothrow_nononlocal (rtx insn)
1609*e4b17023SJohn Marino {
1610*e4b17023SJohn Marino rtx note = find_reg_note (insn, REG_EH_REGION, NULL_RTX);
1611*e4b17023SJohn Marino rtx intmin = GEN_INT (INT_MIN);
1612*e4b17023SJohn Marino
1613*e4b17023SJohn Marino if (note != 0)
1614*e4b17023SJohn Marino XEXP (note, 0) = intmin;
1615*e4b17023SJohn Marino else
1616*e4b17023SJohn Marino add_reg_note (insn, REG_EH_REGION, intmin);
1617*e4b17023SJohn Marino }
1618*e4b17023SJohn Marino
1619*e4b17023SJohn Marino /* Return true if INSN could throw, assuming no REG_EH_REGION note
1620*e4b17023SJohn Marino to the contrary. */
1621*e4b17023SJohn Marino
1622*e4b17023SJohn Marino bool
insn_could_throw_p(const_rtx insn)1623*e4b17023SJohn Marino insn_could_throw_p (const_rtx insn)
1624*e4b17023SJohn Marino {
1625*e4b17023SJohn Marino if (!flag_exceptions)
1626*e4b17023SJohn Marino return false;
1627*e4b17023SJohn Marino if (CALL_P (insn))
1628*e4b17023SJohn Marino return true;
1629*e4b17023SJohn Marino if (INSN_P (insn) && cfun->can_throw_non_call_exceptions)
1630*e4b17023SJohn Marino return may_trap_p (PATTERN (insn));
1631*e4b17023SJohn Marino return false;
1632*e4b17023SJohn Marino }
1633*e4b17023SJohn Marino
1634*e4b17023SJohn Marino /* Copy an REG_EH_REGION note to each insn that might throw beginning
1635*e4b17023SJohn Marino at FIRST and ending at LAST. NOTE_OR_INSN is either the source insn
1636*e4b17023SJohn Marino to look for a note, or the note itself. */
1637*e4b17023SJohn Marino
1638*e4b17023SJohn Marino void
copy_reg_eh_region_note_forward(rtx note_or_insn,rtx first,rtx last)1639*e4b17023SJohn Marino copy_reg_eh_region_note_forward (rtx note_or_insn, rtx first, rtx last)
1640*e4b17023SJohn Marino {
1641*e4b17023SJohn Marino rtx insn, note = note_or_insn;
1642*e4b17023SJohn Marino
1643*e4b17023SJohn Marino if (INSN_P (note_or_insn))
1644*e4b17023SJohn Marino {
1645*e4b17023SJohn Marino note = find_reg_note (note_or_insn, REG_EH_REGION, NULL_RTX);
1646*e4b17023SJohn Marino if (note == NULL)
1647*e4b17023SJohn Marino return;
1648*e4b17023SJohn Marino }
1649*e4b17023SJohn Marino note = XEXP (note, 0);
1650*e4b17023SJohn Marino
1651*e4b17023SJohn Marino for (insn = first; insn != last ; insn = NEXT_INSN (insn))
1652*e4b17023SJohn Marino if (!find_reg_note (insn, REG_EH_REGION, NULL_RTX)
1653*e4b17023SJohn Marino && insn_could_throw_p (insn))
1654*e4b17023SJohn Marino add_reg_note (insn, REG_EH_REGION, note);
1655*e4b17023SJohn Marino }
1656*e4b17023SJohn Marino
1657*e4b17023SJohn Marino /* Likewise, but iterate backward. */
1658*e4b17023SJohn Marino
1659*e4b17023SJohn Marino void
copy_reg_eh_region_note_backward(rtx note_or_insn,rtx last,rtx first)1660*e4b17023SJohn Marino copy_reg_eh_region_note_backward (rtx note_or_insn, rtx last, rtx first)
1661*e4b17023SJohn Marino {
1662*e4b17023SJohn Marino rtx insn, note = note_or_insn;
1663*e4b17023SJohn Marino
1664*e4b17023SJohn Marino if (INSN_P (note_or_insn))
1665*e4b17023SJohn Marino {
1666*e4b17023SJohn Marino note = find_reg_note (note_or_insn, REG_EH_REGION, NULL_RTX);
1667*e4b17023SJohn Marino if (note == NULL)
1668*e4b17023SJohn Marino return;
1669*e4b17023SJohn Marino }
1670*e4b17023SJohn Marino note = XEXP (note, 0);
1671*e4b17023SJohn Marino
1672*e4b17023SJohn Marino for (insn = last; insn != first; insn = PREV_INSN (insn))
1673*e4b17023SJohn Marino if (insn_could_throw_p (insn))
1674*e4b17023SJohn Marino add_reg_note (insn, REG_EH_REGION, note);
1675*e4b17023SJohn Marino }
1676*e4b17023SJohn Marino
1677*e4b17023SJohn Marino
1678*e4b17023SJohn Marino /* Extract all EH information from INSN. Return true if the insn
1679*e4b17023SJohn Marino was marked NOTHROW. */
1680*e4b17023SJohn Marino
1681*e4b17023SJohn Marino static bool
get_eh_region_and_lp_from_rtx(const_rtx insn,eh_region * pr,eh_landing_pad * plp)1682*e4b17023SJohn Marino get_eh_region_and_lp_from_rtx (const_rtx insn, eh_region *pr,
1683*e4b17023SJohn Marino eh_landing_pad *plp)
1684*e4b17023SJohn Marino {
1685*e4b17023SJohn Marino eh_landing_pad lp = NULL;
1686*e4b17023SJohn Marino eh_region r = NULL;
1687*e4b17023SJohn Marino bool ret = false;
1688*e4b17023SJohn Marino rtx note;
1689*e4b17023SJohn Marino int lp_nr;
1690*e4b17023SJohn Marino
1691*e4b17023SJohn Marino if (! INSN_P (insn))
1692*e4b17023SJohn Marino goto egress;
1693*e4b17023SJohn Marino
1694*e4b17023SJohn Marino if (NONJUMP_INSN_P (insn)
1695*e4b17023SJohn Marino && GET_CODE (PATTERN (insn)) == SEQUENCE)
1696*e4b17023SJohn Marino insn = XVECEXP (PATTERN (insn), 0, 0);
1697*e4b17023SJohn Marino
1698*e4b17023SJohn Marino note = find_reg_note (insn, REG_EH_REGION, NULL_RTX);
1699*e4b17023SJohn Marino if (!note)
1700*e4b17023SJohn Marino {
1701*e4b17023SJohn Marino ret = !insn_could_throw_p (insn);
1702*e4b17023SJohn Marino goto egress;
1703*e4b17023SJohn Marino }
1704*e4b17023SJohn Marino
1705*e4b17023SJohn Marino lp_nr = INTVAL (XEXP (note, 0));
1706*e4b17023SJohn Marino if (lp_nr == 0 || lp_nr == INT_MIN)
1707*e4b17023SJohn Marino {
1708*e4b17023SJohn Marino ret = true;
1709*e4b17023SJohn Marino goto egress;
1710*e4b17023SJohn Marino }
1711*e4b17023SJohn Marino
1712*e4b17023SJohn Marino if (lp_nr < 0)
1713*e4b17023SJohn Marino r = VEC_index (eh_region, cfun->eh->region_array, -lp_nr);
1714*e4b17023SJohn Marino else
1715*e4b17023SJohn Marino {
1716*e4b17023SJohn Marino lp = VEC_index (eh_landing_pad, cfun->eh->lp_array, lp_nr);
1717*e4b17023SJohn Marino r = lp->region;
1718*e4b17023SJohn Marino }
1719*e4b17023SJohn Marino
1720*e4b17023SJohn Marino egress:
1721*e4b17023SJohn Marino *plp = lp;
1722*e4b17023SJohn Marino *pr = r;
1723*e4b17023SJohn Marino return ret;
1724*e4b17023SJohn Marino }
1725*e4b17023SJohn Marino
1726*e4b17023SJohn Marino /* Return the landing pad to which INSN may go, or NULL if it does not
1727*e4b17023SJohn Marino have a reachable landing pad within this function. */
1728*e4b17023SJohn Marino
1729*e4b17023SJohn Marino eh_landing_pad
get_eh_landing_pad_from_rtx(const_rtx insn)1730*e4b17023SJohn Marino get_eh_landing_pad_from_rtx (const_rtx insn)
1731*e4b17023SJohn Marino {
1732*e4b17023SJohn Marino eh_landing_pad lp;
1733*e4b17023SJohn Marino eh_region r;
1734*e4b17023SJohn Marino
1735*e4b17023SJohn Marino get_eh_region_and_lp_from_rtx (insn, &r, &lp);
1736*e4b17023SJohn Marino return lp;
1737*e4b17023SJohn Marino }
1738*e4b17023SJohn Marino
1739*e4b17023SJohn Marino /* Return the region to which INSN may go, or NULL if it does not
1740*e4b17023SJohn Marino have a reachable region within this function. */
1741*e4b17023SJohn Marino
1742*e4b17023SJohn Marino eh_region
get_eh_region_from_rtx(const_rtx insn)1743*e4b17023SJohn Marino get_eh_region_from_rtx (const_rtx insn)
1744*e4b17023SJohn Marino {
1745*e4b17023SJohn Marino eh_landing_pad lp;
1746*e4b17023SJohn Marino eh_region r;
1747*e4b17023SJohn Marino
1748*e4b17023SJohn Marino get_eh_region_and_lp_from_rtx (insn, &r, &lp);
1749*e4b17023SJohn Marino return r;
1750*e4b17023SJohn Marino }
1751*e4b17023SJohn Marino
1752*e4b17023SJohn Marino /* Return true if INSN throws and is caught by something in this function. */
1753*e4b17023SJohn Marino
1754*e4b17023SJohn Marino bool
can_throw_internal(const_rtx insn)1755*e4b17023SJohn Marino can_throw_internal (const_rtx insn)
1756*e4b17023SJohn Marino {
1757*e4b17023SJohn Marino return get_eh_landing_pad_from_rtx (insn) != NULL;
1758*e4b17023SJohn Marino }
1759*e4b17023SJohn Marino
1760*e4b17023SJohn Marino /* Return true if INSN throws and escapes from the current function. */
1761*e4b17023SJohn Marino
1762*e4b17023SJohn Marino bool
can_throw_external(const_rtx insn)1763*e4b17023SJohn Marino can_throw_external (const_rtx insn)
1764*e4b17023SJohn Marino {
1765*e4b17023SJohn Marino eh_landing_pad lp;
1766*e4b17023SJohn Marino eh_region r;
1767*e4b17023SJohn Marino bool nothrow;
1768*e4b17023SJohn Marino
1769*e4b17023SJohn Marino if (! INSN_P (insn))
1770*e4b17023SJohn Marino return false;
1771*e4b17023SJohn Marino
1772*e4b17023SJohn Marino if (NONJUMP_INSN_P (insn)
1773*e4b17023SJohn Marino && GET_CODE (PATTERN (insn)) == SEQUENCE)
1774*e4b17023SJohn Marino {
1775*e4b17023SJohn Marino rtx seq = PATTERN (insn);
1776*e4b17023SJohn Marino int i, n = XVECLEN (seq, 0);
1777*e4b17023SJohn Marino
1778*e4b17023SJohn Marino for (i = 0; i < n; i++)
1779*e4b17023SJohn Marino if (can_throw_external (XVECEXP (seq, 0, i)))
1780*e4b17023SJohn Marino return true;
1781*e4b17023SJohn Marino
1782*e4b17023SJohn Marino return false;
1783*e4b17023SJohn Marino }
1784*e4b17023SJohn Marino
1785*e4b17023SJohn Marino nothrow = get_eh_region_and_lp_from_rtx (insn, &r, &lp);
1786*e4b17023SJohn Marino
1787*e4b17023SJohn Marino /* If we can't throw, we obviously can't throw external. */
1788*e4b17023SJohn Marino if (nothrow)
1789*e4b17023SJohn Marino return false;
1790*e4b17023SJohn Marino
1791*e4b17023SJohn Marino /* If we have an internal landing pad, then we're not external. */
1792*e4b17023SJohn Marino if (lp != NULL)
1793*e4b17023SJohn Marino return false;
1794*e4b17023SJohn Marino
1795*e4b17023SJohn Marino /* If we're not within an EH region, then we are external. */
1796*e4b17023SJohn Marino if (r == NULL)
1797*e4b17023SJohn Marino return true;
1798*e4b17023SJohn Marino
1799*e4b17023SJohn Marino /* The only thing that ought to be left is MUST_NOT_THROW regions,
1800*e4b17023SJohn Marino which don't always have landing pads. */
1801*e4b17023SJohn Marino gcc_assert (r->type == ERT_MUST_NOT_THROW);
1802*e4b17023SJohn Marino return false;
1803*e4b17023SJohn Marino }
1804*e4b17023SJohn Marino
1805*e4b17023SJohn Marino /* Return true if INSN cannot throw at all. */
1806*e4b17023SJohn Marino
1807*e4b17023SJohn Marino bool
insn_nothrow_p(const_rtx insn)1808*e4b17023SJohn Marino insn_nothrow_p (const_rtx insn)
1809*e4b17023SJohn Marino {
1810*e4b17023SJohn Marino eh_landing_pad lp;
1811*e4b17023SJohn Marino eh_region r;
1812*e4b17023SJohn Marino
1813*e4b17023SJohn Marino if (! INSN_P (insn))
1814*e4b17023SJohn Marino return true;
1815*e4b17023SJohn Marino
1816*e4b17023SJohn Marino if (NONJUMP_INSN_P (insn)
1817*e4b17023SJohn Marino && GET_CODE (PATTERN (insn)) == SEQUENCE)
1818*e4b17023SJohn Marino {
1819*e4b17023SJohn Marino rtx seq = PATTERN (insn);
1820*e4b17023SJohn Marino int i, n = XVECLEN (seq, 0);
1821*e4b17023SJohn Marino
1822*e4b17023SJohn Marino for (i = 0; i < n; i++)
1823*e4b17023SJohn Marino if (!insn_nothrow_p (XVECEXP (seq, 0, i)))
1824*e4b17023SJohn Marino return false;
1825*e4b17023SJohn Marino
1826*e4b17023SJohn Marino return true;
1827*e4b17023SJohn Marino }
1828*e4b17023SJohn Marino
1829*e4b17023SJohn Marino return get_eh_region_and_lp_from_rtx (insn, &r, &lp);
1830*e4b17023SJohn Marino }
1831*e4b17023SJohn Marino
1832*e4b17023SJohn Marino /* Return true if INSN can perform a non-local goto. */
1833*e4b17023SJohn Marino /* ??? This test is here in this file because it (ab)uses REG_EH_REGION. */
1834*e4b17023SJohn Marino
1835*e4b17023SJohn Marino bool
can_nonlocal_goto(const_rtx insn)1836*e4b17023SJohn Marino can_nonlocal_goto (const_rtx insn)
1837*e4b17023SJohn Marino {
1838*e4b17023SJohn Marino if (nonlocal_goto_handler_labels && CALL_P (insn))
1839*e4b17023SJohn Marino {
1840*e4b17023SJohn Marino rtx note = find_reg_note (insn, REG_EH_REGION, NULL_RTX);
1841*e4b17023SJohn Marino if (!note || INTVAL (XEXP (note, 0)) != INT_MIN)
1842*e4b17023SJohn Marino return true;
1843*e4b17023SJohn Marino }
1844*e4b17023SJohn Marino return false;
1845*e4b17023SJohn Marino }
1846*e4b17023SJohn Marino
1847*e4b17023SJohn Marino /* Set TREE_NOTHROW and crtl->all_throwers_are_sibcalls. */
1848*e4b17023SJohn Marino
1849*e4b17023SJohn Marino static unsigned int
set_nothrow_function_flags(void)1850*e4b17023SJohn Marino set_nothrow_function_flags (void)
1851*e4b17023SJohn Marino {
1852*e4b17023SJohn Marino rtx insn;
1853*e4b17023SJohn Marino
1854*e4b17023SJohn Marino crtl->nothrow = 1;
1855*e4b17023SJohn Marino
1856*e4b17023SJohn Marino /* Assume crtl->all_throwers_are_sibcalls until we encounter
1857*e4b17023SJohn Marino something that can throw an exception. We specifically exempt
1858*e4b17023SJohn Marino CALL_INSNs that are SIBLING_CALL_P, as these are really jumps,
1859*e4b17023SJohn Marino and can't throw. Most CALL_INSNs are not SIBLING_CALL_P, so this
1860*e4b17023SJohn Marino is optimistic. */
1861*e4b17023SJohn Marino
1862*e4b17023SJohn Marino crtl->all_throwers_are_sibcalls = 1;
1863*e4b17023SJohn Marino
1864*e4b17023SJohn Marino /* If we don't know that this implementation of the function will
1865*e4b17023SJohn Marino actually be used, then we must not set TREE_NOTHROW, since
1866*e4b17023SJohn Marino callers must not assume that this function does not throw. */
1867*e4b17023SJohn Marino if (TREE_NOTHROW (current_function_decl))
1868*e4b17023SJohn Marino return 0;
1869*e4b17023SJohn Marino
1870*e4b17023SJohn Marino if (! flag_exceptions)
1871*e4b17023SJohn Marino return 0;
1872*e4b17023SJohn Marino
1873*e4b17023SJohn Marino for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
1874*e4b17023SJohn Marino if (can_throw_external (insn))
1875*e4b17023SJohn Marino {
1876*e4b17023SJohn Marino crtl->nothrow = 0;
1877*e4b17023SJohn Marino
1878*e4b17023SJohn Marino if (!CALL_P (insn) || !SIBLING_CALL_P (insn))
1879*e4b17023SJohn Marino {
1880*e4b17023SJohn Marino crtl->all_throwers_are_sibcalls = 0;
1881*e4b17023SJohn Marino return 0;
1882*e4b17023SJohn Marino }
1883*e4b17023SJohn Marino }
1884*e4b17023SJohn Marino
1885*e4b17023SJohn Marino for (insn = crtl->epilogue_delay_list; insn;
1886*e4b17023SJohn Marino insn = XEXP (insn, 1))
1887*e4b17023SJohn Marino if (can_throw_external (insn))
1888*e4b17023SJohn Marino {
1889*e4b17023SJohn Marino crtl->nothrow = 0;
1890*e4b17023SJohn Marino
1891*e4b17023SJohn Marino if (!CALL_P (insn) || !SIBLING_CALL_P (insn))
1892*e4b17023SJohn Marino {
1893*e4b17023SJohn Marino crtl->all_throwers_are_sibcalls = 0;
1894*e4b17023SJohn Marino return 0;
1895*e4b17023SJohn Marino }
1896*e4b17023SJohn Marino }
1897*e4b17023SJohn Marino if (crtl->nothrow
1898*e4b17023SJohn Marino && (cgraph_function_body_availability (cgraph_get_node
1899*e4b17023SJohn Marino (current_function_decl))
1900*e4b17023SJohn Marino >= AVAIL_AVAILABLE))
1901*e4b17023SJohn Marino {
1902*e4b17023SJohn Marino struct cgraph_node *node = cgraph_get_node (current_function_decl);
1903*e4b17023SJohn Marino struct cgraph_edge *e;
1904*e4b17023SJohn Marino for (e = node->callers; e; e = e->next_caller)
1905*e4b17023SJohn Marino e->can_throw_external = false;
1906*e4b17023SJohn Marino cgraph_set_nothrow_flag (node, true);
1907*e4b17023SJohn Marino
1908*e4b17023SJohn Marino if (dump_file)
1909*e4b17023SJohn Marino fprintf (dump_file, "Marking function nothrow: %s\n\n",
1910*e4b17023SJohn Marino current_function_name ());
1911*e4b17023SJohn Marino }
1912*e4b17023SJohn Marino return 0;
1913*e4b17023SJohn Marino }
1914*e4b17023SJohn Marino
1915*e4b17023SJohn Marino struct rtl_opt_pass pass_set_nothrow_function_flags =
1916*e4b17023SJohn Marino {
1917*e4b17023SJohn Marino {
1918*e4b17023SJohn Marino RTL_PASS,
1919*e4b17023SJohn Marino "nothrow", /* name */
1920*e4b17023SJohn Marino NULL, /* gate */
1921*e4b17023SJohn Marino set_nothrow_function_flags, /* execute */
1922*e4b17023SJohn Marino NULL, /* sub */
1923*e4b17023SJohn Marino NULL, /* next */
1924*e4b17023SJohn Marino 0, /* static_pass_number */
1925*e4b17023SJohn Marino TV_NONE, /* tv_id */
1926*e4b17023SJohn Marino 0, /* properties_required */
1927*e4b17023SJohn Marino 0, /* properties_provided */
1928*e4b17023SJohn Marino 0, /* properties_destroyed */
1929*e4b17023SJohn Marino 0, /* todo_flags_start */
1930*e4b17023SJohn Marino 0 /* todo_flags_finish */
1931*e4b17023SJohn Marino }
1932*e4b17023SJohn Marino };
1933*e4b17023SJohn Marino
1934*e4b17023SJohn Marino
1935*e4b17023SJohn Marino /* Various hooks for unwind library. */
1936*e4b17023SJohn Marino
1937*e4b17023SJohn Marino /* Expand the EH support builtin functions:
1938*e4b17023SJohn Marino __builtin_eh_pointer and __builtin_eh_filter. */
1939*e4b17023SJohn Marino
1940*e4b17023SJohn Marino static eh_region
expand_builtin_eh_common(tree region_nr_t)1941*e4b17023SJohn Marino expand_builtin_eh_common (tree region_nr_t)
1942*e4b17023SJohn Marino {
1943*e4b17023SJohn Marino HOST_WIDE_INT region_nr;
1944*e4b17023SJohn Marino eh_region region;
1945*e4b17023SJohn Marino
1946*e4b17023SJohn Marino gcc_assert (host_integerp (region_nr_t, 0));
1947*e4b17023SJohn Marino region_nr = tree_low_cst (region_nr_t, 0);
1948*e4b17023SJohn Marino
1949*e4b17023SJohn Marino region = VEC_index (eh_region, cfun->eh->region_array, region_nr);
1950*e4b17023SJohn Marino
1951*e4b17023SJohn Marino /* ??? We shouldn't have been able to delete a eh region without
1952*e4b17023SJohn Marino deleting all the code that depended on it. */
1953*e4b17023SJohn Marino gcc_assert (region != NULL);
1954*e4b17023SJohn Marino
1955*e4b17023SJohn Marino return region;
1956*e4b17023SJohn Marino }
1957*e4b17023SJohn Marino
1958*e4b17023SJohn Marino /* Expand to the exc_ptr value from the given eh region. */
1959*e4b17023SJohn Marino
1960*e4b17023SJohn Marino rtx
expand_builtin_eh_pointer(tree exp)1961*e4b17023SJohn Marino expand_builtin_eh_pointer (tree exp)
1962*e4b17023SJohn Marino {
1963*e4b17023SJohn Marino eh_region region
1964*e4b17023SJohn Marino = expand_builtin_eh_common (CALL_EXPR_ARG (exp, 0));
1965*e4b17023SJohn Marino if (region->exc_ptr_reg == NULL)
1966*e4b17023SJohn Marino region->exc_ptr_reg = gen_reg_rtx (ptr_mode);
1967*e4b17023SJohn Marino return region->exc_ptr_reg;
1968*e4b17023SJohn Marino }
1969*e4b17023SJohn Marino
1970*e4b17023SJohn Marino /* Expand to the filter value from the given eh region. */
1971*e4b17023SJohn Marino
1972*e4b17023SJohn Marino rtx
expand_builtin_eh_filter(tree exp)1973*e4b17023SJohn Marino expand_builtin_eh_filter (tree exp)
1974*e4b17023SJohn Marino {
1975*e4b17023SJohn Marino eh_region region
1976*e4b17023SJohn Marino = expand_builtin_eh_common (CALL_EXPR_ARG (exp, 0));
1977*e4b17023SJohn Marino if (region->filter_reg == NULL)
1978*e4b17023SJohn Marino region->filter_reg = gen_reg_rtx (targetm.eh_return_filter_mode ());
1979*e4b17023SJohn Marino return region->filter_reg;
1980*e4b17023SJohn Marino }
1981*e4b17023SJohn Marino
1982*e4b17023SJohn Marino /* Copy the exc_ptr and filter values from one landing pad's registers
1983*e4b17023SJohn Marino to another. This is used to inline the resx statement. */
1984*e4b17023SJohn Marino
1985*e4b17023SJohn Marino rtx
expand_builtin_eh_copy_values(tree exp)1986*e4b17023SJohn Marino expand_builtin_eh_copy_values (tree exp)
1987*e4b17023SJohn Marino {
1988*e4b17023SJohn Marino eh_region dst
1989*e4b17023SJohn Marino = expand_builtin_eh_common (CALL_EXPR_ARG (exp, 0));
1990*e4b17023SJohn Marino eh_region src
1991*e4b17023SJohn Marino = expand_builtin_eh_common (CALL_EXPR_ARG (exp, 1));
1992*e4b17023SJohn Marino enum machine_mode fmode = targetm.eh_return_filter_mode ();
1993*e4b17023SJohn Marino
1994*e4b17023SJohn Marino if (dst->exc_ptr_reg == NULL)
1995*e4b17023SJohn Marino dst->exc_ptr_reg = gen_reg_rtx (ptr_mode);
1996*e4b17023SJohn Marino if (src->exc_ptr_reg == NULL)
1997*e4b17023SJohn Marino src->exc_ptr_reg = gen_reg_rtx (ptr_mode);
1998*e4b17023SJohn Marino
1999*e4b17023SJohn Marino if (dst->filter_reg == NULL)
2000*e4b17023SJohn Marino dst->filter_reg = gen_reg_rtx (fmode);
2001*e4b17023SJohn Marino if (src->filter_reg == NULL)
2002*e4b17023SJohn Marino src->filter_reg = gen_reg_rtx (fmode);
2003*e4b17023SJohn Marino
2004*e4b17023SJohn Marino emit_move_insn (dst->exc_ptr_reg, src->exc_ptr_reg);
2005*e4b17023SJohn Marino emit_move_insn (dst->filter_reg, src->filter_reg);
2006*e4b17023SJohn Marino
2007*e4b17023SJohn Marino return const0_rtx;
2008*e4b17023SJohn Marino }
2009*e4b17023SJohn Marino
2010*e4b17023SJohn Marino /* Do any necessary initialization to access arbitrary stack frames.
2011*e4b17023SJohn Marino On the SPARC, this means flushing the register windows. */
2012*e4b17023SJohn Marino
2013*e4b17023SJohn Marino void
expand_builtin_unwind_init(void)2014*e4b17023SJohn Marino expand_builtin_unwind_init (void)
2015*e4b17023SJohn Marino {
2016*e4b17023SJohn Marino /* Set this so all the registers get saved in our frame; we need to be
2017*e4b17023SJohn Marino able to copy the saved values for any registers from frames we unwind. */
2018*e4b17023SJohn Marino crtl->saves_all_registers = 1;
2019*e4b17023SJohn Marino
2020*e4b17023SJohn Marino #ifdef SETUP_FRAME_ADDRESSES
2021*e4b17023SJohn Marino SETUP_FRAME_ADDRESSES ();
2022*e4b17023SJohn Marino #endif
2023*e4b17023SJohn Marino }
2024*e4b17023SJohn Marino
2025*e4b17023SJohn Marino /* Map a non-negative number to an eh return data register number; expands
2026*e4b17023SJohn Marino to -1 if no return data register is associated with the input number.
2027*e4b17023SJohn Marino At least the inputs 0 and 1 must be mapped; the target may provide more. */
2028*e4b17023SJohn Marino
2029*e4b17023SJohn Marino rtx
expand_builtin_eh_return_data_regno(tree exp)2030*e4b17023SJohn Marino expand_builtin_eh_return_data_regno (tree exp)
2031*e4b17023SJohn Marino {
2032*e4b17023SJohn Marino tree which = CALL_EXPR_ARG (exp, 0);
2033*e4b17023SJohn Marino unsigned HOST_WIDE_INT iwhich;
2034*e4b17023SJohn Marino
2035*e4b17023SJohn Marino if (TREE_CODE (which) != INTEGER_CST)
2036*e4b17023SJohn Marino {
2037*e4b17023SJohn Marino error ("argument of %<__builtin_eh_return_regno%> must be constant");
2038*e4b17023SJohn Marino return constm1_rtx;
2039*e4b17023SJohn Marino }
2040*e4b17023SJohn Marino
2041*e4b17023SJohn Marino iwhich = tree_low_cst (which, 1);
2042*e4b17023SJohn Marino iwhich = EH_RETURN_DATA_REGNO (iwhich);
2043*e4b17023SJohn Marino if (iwhich == INVALID_REGNUM)
2044*e4b17023SJohn Marino return constm1_rtx;
2045*e4b17023SJohn Marino
2046*e4b17023SJohn Marino #ifdef DWARF_FRAME_REGNUM
2047*e4b17023SJohn Marino iwhich = DWARF_FRAME_REGNUM (iwhich);
2048*e4b17023SJohn Marino #else
2049*e4b17023SJohn Marino iwhich = DBX_REGISTER_NUMBER (iwhich);
2050*e4b17023SJohn Marino #endif
2051*e4b17023SJohn Marino
2052*e4b17023SJohn Marino return GEN_INT (iwhich);
2053*e4b17023SJohn Marino }
2054*e4b17023SJohn Marino
2055*e4b17023SJohn Marino /* Given a value extracted from the return address register or stack slot,
2056*e4b17023SJohn Marino return the actual address encoded in that value. */
2057*e4b17023SJohn Marino
2058*e4b17023SJohn Marino rtx
expand_builtin_extract_return_addr(tree addr_tree)2059*e4b17023SJohn Marino expand_builtin_extract_return_addr (tree addr_tree)
2060*e4b17023SJohn Marino {
2061*e4b17023SJohn Marino rtx addr = expand_expr (addr_tree, NULL_RTX, Pmode, EXPAND_NORMAL);
2062*e4b17023SJohn Marino
2063*e4b17023SJohn Marino if (GET_MODE (addr) != Pmode
2064*e4b17023SJohn Marino && GET_MODE (addr) != VOIDmode)
2065*e4b17023SJohn Marino {
2066*e4b17023SJohn Marino #ifdef POINTERS_EXTEND_UNSIGNED
2067*e4b17023SJohn Marino addr = convert_memory_address (Pmode, addr);
2068*e4b17023SJohn Marino #else
2069*e4b17023SJohn Marino addr = convert_to_mode (Pmode, addr, 0);
2070*e4b17023SJohn Marino #endif
2071*e4b17023SJohn Marino }
2072*e4b17023SJohn Marino
2073*e4b17023SJohn Marino /* First mask out any unwanted bits. */
2074*e4b17023SJohn Marino #ifdef MASK_RETURN_ADDR
2075*e4b17023SJohn Marino expand_and (Pmode, addr, MASK_RETURN_ADDR, addr);
2076*e4b17023SJohn Marino #endif
2077*e4b17023SJohn Marino
2078*e4b17023SJohn Marino /* Then adjust to find the real return address. */
2079*e4b17023SJohn Marino #if defined (RETURN_ADDR_OFFSET)
2080*e4b17023SJohn Marino addr = plus_constant (addr, RETURN_ADDR_OFFSET);
2081*e4b17023SJohn Marino #endif
2082*e4b17023SJohn Marino
2083*e4b17023SJohn Marino return addr;
2084*e4b17023SJohn Marino }
2085*e4b17023SJohn Marino
2086*e4b17023SJohn Marino /* Given an actual address in addr_tree, do any necessary encoding
2087*e4b17023SJohn Marino and return the value to be stored in the return address register or
2088*e4b17023SJohn Marino stack slot so the epilogue will return to that address. */
2089*e4b17023SJohn Marino
2090*e4b17023SJohn Marino rtx
expand_builtin_frob_return_addr(tree addr_tree)2091*e4b17023SJohn Marino expand_builtin_frob_return_addr (tree addr_tree)
2092*e4b17023SJohn Marino {
2093*e4b17023SJohn Marino rtx addr = expand_expr (addr_tree, NULL_RTX, ptr_mode, EXPAND_NORMAL);
2094*e4b17023SJohn Marino
2095*e4b17023SJohn Marino addr = convert_memory_address (Pmode, addr);
2096*e4b17023SJohn Marino
2097*e4b17023SJohn Marino #ifdef RETURN_ADDR_OFFSET
2098*e4b17023SJohn Marino addr = force_reg (Pmode, addr);
2099*e4b17023SJohn Marino addr = plus_constant (addr, -RETURN_ADDR_OFFSET);
2100*e4b17023SJohn Marino #endif
2101*e4b17023SJohn Marino
2102*e4b17023SJohn Marino return addr;
2103*e4b17023SJohn Marino }
2104*e4b17023SJohn Marino
2105*e4b17023SJohn Marino /* Set up the epilogue with the magic bits we'll need to return to the
2106*e4b17023SJohn Marino exception handler. */
2107*e4b17023SJohn Marino
2108*e4b17023SJohn Marino void
expand_builtin_eh_return(tree stackadj_tree ATTRIBUTE_UNUSED,tree handler_tree)2109*e4b17023SJohn Marino expand_builtin_eh_return (tree stackadj_tree ATTRIBUTE_UNUSED,
2110*e4b17023SJohn Marino tree handler_tree)
2111*e4b17023SJohn Marino {
2112*e4b17023SJohn Marino rtx tmp;
2113*e4b17023SJohn Marino
2114*e4b17023SJohn Marino #ifdef EH_RETURN_STACKADJ_RTX
2115*e4b17023SJohn Marino tmp = expand_expr (stackadj_tree, crtl->eh.ehr_stackadj,
2116*e4b17023SJohn Marino VOIDmode, EXPAND_NORMAL);
2117*e4b17023SJohn Marino tmp = convert_memory_address (Pmode, tmp);
2118*e4b17023SJohn Marino if (!crtl->eh.ehr_stackadj)
2119*e4b17023SJohn Marino crtl->eh.ehr_stackadj = copy_to_reg (tmp);
2120*e4b17023SJohn Marino else if (tmp != crtl->eh.ehr_stackadj)
2121*e4b17023SJohn Marino emit_move_insn (crtl->eh.ehr_stackadj, tmp);
2122*e4b17023SJohn Marino #endif
2123*e4b17023SJohn Marino
2124*e4b17023SJohn Marino tmp = expand_expr (handler_tree, crtl->eh.ehr_handler,
2125*e4b17023SJohn Marino VOIDmode, EXPAND_NORMAL);
2126*e4b17023SJohn Marino tmp = convert_memory_address (Pmode, tmp);
2127*e4b17023SJohn Marino if (!crtl->eh.ehr_handler)
2128*e4b17023SJohn Marino crtl->eh.ehr_handler = copy_to_reg (tmp);
2129*e4b17023SJohn Marino else if (tmp != crtl->eh.ehr_handler)
2130*e4b17023SJohn Marino emit_move_insn (crtl->eh.ehr_handler, tmp);
2131*e4b17023SJohn Marino
2132*e4b17023SJohn Marino if (!crtl->eh.ehr_label)
2133*e4b17023SJohn Marino crtl->eh.ehr_label = gen_label_rtx ();
2134*e4b17023SJohn Marino emit_jump (crtl->eh.ehr_label);
2135*e4b17023SJohn Marino }
2136*e4b17023SJohn Marino
2137*e4b17023SJohn Marino /* Expand __builtin_eh_return. This exit path from the function loads up
2138*e4b17023SJohn Marino the eh return data registers, adjusts the stack, and branches to a
2139*e4b17023SJohn Marino given PC other than the normal return address. */
2140*e4b17023SJohn Marino
2141*e4b17023SJohn Marino void
expand_eh_return(void)2142*e4b17023SJohn Marino expand_eh_return (void)
2143*e4b17023SJohn Marino {
2144*e4b17023SJohn Marino rtx around_label;
2145*e4b17023SJohn Marino
2146*e4b17023SJohn Marino if (! crtl->eh.ehr_label)
2147*e4b17023SJohn Marino return;
2148*e4b17023SJohn Marino
2149*e4b17023SJohn Marino crtl->calls_eh_return = 1;
2150*e4b17023SJohn Marino
2151*e4b17023SJohn Marino #ifdef EH_RETURN_STACKADJ_RTX
2152*e4b17023SJohn Marino emit_move_insn (EH_RETURN_STACKADJ_RTX, const0_rtx);
2153*e4b17023SJohn Marino #endif
2154*e4b17023SJohn Marino
2155*e4b17023SJohn Marino around_label = gen_label_rtx ();
2156*e4b17023SJohn Marino emit_jump (around_label);
2157*e4b17023SJohn Marino
2158*e4b17023SJohn Marino emit_label (crtl->eh.ehr_label);
2159*e4b17023SJohn Marino clobber_return_register ();
2160*e4b17023SJohn Marino
2161*e4b17023SJohn Marino #ifdef EH_RETURN_STACKADJ_RTX
2162*e4b17023SJohn Marino emit_move_insn (EH_RETURN_STACKADJ_RTX, crtl->eh.ehr_stackadj);
2163*e4b17023SJohn Marino #endif
2164*e4b17023SJohn Marino
2165*e4b17023SJohn Marino #ifdef HAVE_eh_return
2166*e4b17023SJohn Marino if (HAVE_eh_return)
2167*e4b17023SJohn Marino emit_insn (gen_eh_return (crtl->eh.ehr_handler));
2168*e4b17023SJohn Marino else
2169*e4b17023SJohn Marino #endif
2170*e4b17023SJohn Marino {
2171*e4b17023SJohn Marino #ifdef EH_RETURN_HANDLER_RTX
2172*e4b17023SJohn Marino emit_move_insn (EH_RETURN_HANDLER_RTX, crtl->eh.ehr_handler);
2173*e4b17023SJohn Marino #else
2174*e4b17023SJohn Marino error ("__builtin_eh_return not supported on this target");
2175*e4b17023SJohn Marino #endif
2176*e4b17023SJohn Marino }
2177*e4b17023SJohn Marino
2178*e4b17023SJohn Marino emit_label (around_label);
2179*e4b17023SJohn Marino }
2180*e4b17023SJohn Marino
2181*e4b17023SJohn Marino /* Convert a ptr_mode address ADDR_TREE to a Pmode address controlled by
2182*e4b17023SJohn Marino POINTERS_EXTEND_UNSIGNED and return it. */
2183*e4b17023SJohn Marino
2184*e4b17023SJohn Marino rtx
expand_builtin_extend_pointer(tree addr_tree)2185*e4b17023SJohn Marino expand_builtin_extend_pointer (tree addr_tree)
2186*e4b17023SJohn Marino {
2187*e4b17023SJohn Marino rtx addr = expand_expr (addr_tree, NULL_RTX, ptr_mode, EXPAND_NORMAL);
2188*e4b17023SJohn Marino int extend;
2189*e4b17023SJohn Marino
2190*e4b17023SJohn Marino #ifdef POINTERS_EXTEND_UNSIGNED
2191*e4b17023SJohn Marino extend = POINTERS_EXTEND_UNSIGNED;
2192*e4b17023SJohn Marino #else
2193*e4b17023SJohn Marino /* The previous EH code did an unsigned extend by default, so we do this also
2194*e4b17023SJohn Marino for consistency. */
2195*e4b17023SJohn Marino extend = 1;
2196*e4b17023SJohn Marino #endif
2197*e4b17023SJohn Marino
2198*e4b17023SJohn Marino return convert_modes (targetm.unwind_word_mode (), ptr_mode, addr, extend);
2199*e4b17023SJohn Marino }
2200*e4b17023SJohn Marino
2201*e4b17023SJohn Marino /* In the following functions, we represent entries in the action table
2202*e4b17023SJohn Marino as 1-based indices. Special cases are:
2203*e4b17023SJohn Marino
2204*e4b17023SJohn Marino 0: null action record, non-null landing pad; implies cleanups
2205*e4b17023SJohn Marino -1: null action record, null landing pad; implies no action
2206*e4b17023SJohn Marino -2: no call-site entry; implies must_not_throw
2207*e4b17023SJohn Marino -3: we have yet to process outer regions
2208*e4b17023SJohn Marino
2209*e4b17023SJohn Marino Further, no special cases apply to the "next" field of the record.
2210*e4b17023SJohn Marino For next, 0 means end of list. */
2211*e4b17023SJohn Marino
2212*e4b17023SJohn Marino struct action_record
2213*e4b17023SJohn Marino {
2214*e4b17023SJohn Marino int offset;
2215*e4b17023SJohn Marino int filter;
2216*e4b17023SJohn Marino int next;
2217*e4b17023SJohn Marino };
2218*e4b17023SJohn Marino
2219*e4b17023SJohn Marino static int
action_record_eq(const void * pentry,const void * pdata)2220*e4b17023SJohn Marino action_record_eq (const void *pentry, const void *pdata)
2221*e4b17023SJohn Marino {
2222*e4b17023SJohn Marino const struct action_record *entry = (const struct action_record *) pentry;
2223*e4b17023SJohn Marino const struct action_record *data = (const struct action_record *) pdata;
2224*e4b17023SJohn Marino return entry->filter == data->filter && entry->next == data->next;
2225*e4b17023SJohn Marino }
2226*e4b17023SJohn Marino
2227*e4b17023SJohn Marino static hashval_t
action_record_hash(const void * pentry)2228*e4b17023SJohn Marino action_record_hash (const void *pentry)
2229*e4b17023SJohn Marino {
2230*e4b17023SJohn Marino const struct action_record *entry = (const struct action_record *) pentry;
2231*e4b17023SJohn Marino return entry->next * 1009 + entry->filter;
2232*e4b17023SJohn Marino }
2233*e4b17023SJohn Marino
2234*e4b17023SJohn Marino static int
add_action_record(htab_t ar_hash,int filter,int next)2235*e4b17023SJohn Marino add_action_record (htab_t ar_hash, int filter, int next)
2236*e4b17023SJohn Marino {
2237*e4b17023SJohn Marino struct action_record **slot, *new_ar, tmp;
2238*e4b17023SJohn Marino
2239*e4b17023SJohn Marino tmp.filter = filter;
2240*e4b17023SJohn Marino tmp.next = next;
2241*e4b17023SJohn Marino slot = (struct action_record **) htab_find_slot (ar_hash, &tmp, INSERT);
2242*e4b17023SJohn Marino
2243*e4b17023SJohn Marino if ((new_ar = *slot) == NULL)
2244*e4b17023SJohn Marino {
2245*e4b17023SJohn Marino new_ar = XNEW (struct action_record);
2246*e4b17023SJohn Marino new_ar->offset = VEC_length (uchar, crtl->eh.action_record_data) + 1;
2247*e4b17023SJohn Marino new_ar->filter = filter;
2248*e4b17023SJohn Marino new_ar->next = next;
2249*e4b17023SJohn Marino *slot = new_ar;
2250*e4b17023SJohn Marino
2251*e4b17023SJohn Marino /* The filter value goes in untouched. The link to the next
2252*e4b17023SJohn Marino record is a "self-relative" byte offset, or zero to indicate
2253*e4b17023SJohn Marino that there is no next record. So convert the absolute 1 based
2254*e4b17023SJohn Marino indices we've been carrying around into a displacement. */
2255*e4b17023SJohn Marino
2256*e4b17023SJohn Marino push_sleb128 (&crtl->eh.action_record_data, filter);
2257*e4b17023SJohn Marino if (next)
2258*e4b17023SJohn Marino next -= VEC_length (uchar, crtl->eh.action_record_data) + 1;
2259*e4b17023SJohn Marino push_sleb128 (&crtl->eh.action_record_data, next);
2260*e4b17023SJohn Marino }
2261*e4b17023SJohn Marino
2262*e4b17023SJohn Marino return new_ar->offset;
2263*e4b17023SJohn Marino }
2264*e4b17023SJohn Marino
2265*e4b17023SJohn Marino static int
collect_one_action_chain(htab_t ar_hash,eh_region region)2266*e4b17023SJohn Marino collect_one_action_chain (htab_t ar_hash, eh_region region)
2267*e4b17023SJohn Marino {
2268*e4b17023SJohn Marino int next;
2269*e4b17023SJohn Marino
2270*e4b17023SJohn Marino /* If we've reached the top of the region chain, then we have
2271*e4b17023SJohn Marino no actions, and require no landing pad. */
2272*e4b17023SJohn Marino if (region == NULL)
2273*e4b17023SJohn Marino return -1;
2274*e4b17023SJohn Marino
2275*e4b17023SJohn Marino switch (region->type)
2276*e4b17023SJohn Marino {
2277*e4b17023SJohn Marino case ERT_CLEANUP:
2278*e4b17023SJohn Marino {
2279*e4b17023SJohn Marino eh_region r;
2280*e4b17023SJohn Marino /* A cleanup adds a zero filter to the beginning of the chain, but
2281*e4b17023SJohn Marino there are special cases to look out for. If there are *only*
2282*e4b17023SJohn Marino cleanups along a path, then it compresses to a zero action.
2283*e4b17023SJohn Marino Further, if there are multiple cleanups along a path, we only
2284*e4b17023SJohn Marino need to represent one of them, as that is enough to trigger
2285*e4b17023SJohn Marino entry to the landing pad at runtime. */
2286*e4b17023SJohn Marino next = collect_one_action_chain (ar_hash, region->outer);
2287*e4b17023SJohn Marino if (next <= 0)
2288*e4b17023SJohn Marino return 0;
2289*e4b17023SJohn Marino for (r = region->outer; r ; r = r->outer)
2290*e4b17023SJohn Marino if (r->type == ERT_CLEANUP)
2291*e4b17023SJohn Marino return next;
2292*e4b17023SJohn Marino return add_action_record (ar_hash, 0, next);
2293*e4b17023SJohn Marino }
2294*e4b17023SJohn Marino
2295*e4b17023SJohn Marino case ERT_TRY:
2296*e4b17023SJohn Marino {
2297*e4b17023SJohn Marino eh_catch c;
2298*e4b17023SJohn Marino
2299*e4b17023SJohn Marino /* Process the associated catch regions in reverse order.
2300*e4b17023SJohn Marino If there's a catch-all handler, then we don't need to
2301*e4b17023SJohn Marino search outer regions. Use a magic -3 value to record
2302*e4b17023SJohn Marino that we haven't done the outer search. */
2303*e4b17023SJohn Marino next = -3;
2304*e4b17023SJohn Marino for (c = region->u.eh_try.last_catch; c ; c = c->prev_catch)
2305*e4b17023SJohn Marino {
2306*e4b17023SJohn Marino if (c->type_list == NULL)
2307*e4b17023SJohn Marino {
2308*e4b17023SJohn Marino /* Retrieve the filter from the head of the filter list
2309*e4b17023SJohn Marino where we have stored it (see assign_filter_values). */
2310*e4b17023SJohn Marino int filter = TREE_INT_CST_LOW (TREE_VALUE (c->filter_list));
2311*e4b17023SJohn Marino next = add_action_record (ar_hash, filter, 0);
2312*e4b17023SJohn Marino }
2313*e4b17023SJohn Marino else
2314*e4b17023SJohn Marino {
2315*e4b17023SJohn Marino /* Once the outer search is done, trigger an action record for
2316*e4b17023SJohn Marino each filter we have. */
2317*e4b17023SJohn Marino tree flt_node;
2318*e4b17023SJohn Marino
2319*e4b17023SJohn Marino if (next == -3)
2320*e4b17023SJohn Marino {
2321*e4b17023SJohn Marino next = collect_one_action_chain (ar_hash, region->outer);
2322*e4b17023SJohn Marino
2323*e4b17023SJohn Marino /* If there is no next action, terminate the chain. */
2324*e4b17023SJohn Marino if (next == -1)
2325*e4b17023SJohn Marino next = 0;
2326*e4b17023SJohn Marino /* If all outer actions are cleanups or must_not_throw,
2327*e4b17023SJohn Marino we'll have no action record for it, since we had wanted
2328*e4b17023SJohn Marino to encode these states in the call-site record directly.
2329*e4b17023SJohn Marino Add a cleanup action to the chain to catch these. */
2330*e4b17023SJohn Marino else if (next <= 0)
2331*e4b17023SJohn Marino next = add_action_record (ar_hash, 0, 0);
2332*e4b17023SJohn Marino }
2333*e4b17023SJohn Marino
2334*e4b17023SJohn Marino flt_node = c->filter_list;
2335*e4b17023SJohn Marino for (; flt_node; flt_node = TREE_CHAIN (flt_node))
2336*e4b17023SJohn Marino {
2337*e4b17023SJohn Marino int filter = TREE_INT_CST_LOW (TREE_VALUE (flt_node));
2338*e4b17023SJohn Marino next = add_action_record (ar_hash, filter, next);
2339*e4b17023SJohn Marino }
2340*e4b17023SJohn Marino }
2341*e4b17023SJohn Marino }
2342*e4b17023SJohn Marino return next;
2343*e4b17023SJohn Marino }
2344*e4b17023SJohn Marino
2345*e4b17023SJohn Marino case ERT_ALLOWED_EXCEPTIONS:
2346*e4b17023SJohn Marino /* An exception specification adds its filter to the
2347*e4b17023SJohn Marino beginning of the chain. */
2348*e4b17023SJohn Marino next = collect_one_action_chain (ar_hash, region->outer);
2349*e4b17023SJohn Marino
2350*e4b17023SJohn Marino /* If there is no next action, terminate the chain. */
2351*e4b17023SJohn Marino if (next == -1)
2352*e4b17023SJohn Marino next = 0;
2353*e4b17023SJohn Marino /* If all outer actions are cleanups or must_not_throw,
2354*e4b17023SJohn Marino we'll have no action record for it, since we had wanted
2355*e4b17023SJohn Marino to encode these states in the call-site record directly.
2356*e4b17023SJohn Marino Add a cleanup action to the chain to catch these. */
2357*e4b17023SJohn Marino else if (next <= 0)
2358*e4b17023SJohn Marino next = add_action_record (ar_hash, 0, 0);
2359*e4b17023SJohn Marino
2360*e4b17023SJohn Marino return add_action_record (ar_hash, region->u.allowed.filter, next);
2361*e4b17023SJohn Marino
2362*e4b17023SJohn Marino case ERT_MUST_NOT_THROW:
2363*e4b17023SJohn Marino /* A must-not-throw region with no inner handlers or cleanups
2364*e4b17023SJohn Marino requires no call-site entry. Note that this differs from
2365*e4b17023SJohn Marino the no handler or cleanup case in that we do require an lsda
2366*e4b17023SJohn Marino to be generated. Return a magic -2 value to record this. */
2367*e4b17023SJohn Marino return -2;
2368*e4b17023SJohn Marino }
2369*e4b17023SJohn Marino
2370*e4b17023SJohn Marino gcc_unreachable ();
2371*e4b17023SJohn Marino }
2372*e4b17023SJohn Marino
2373*e4b17023SJohn Marino static int
add_call_site(rtx landing_pad,int action,int section)2374*e4b17023SJohn Marino add_call_site (rtx landing_pad, int action, int section)
2375*e4b17023SJohn Marino {
2376*e4b17023SJohn Marino call_site_record record;
2377*e4b17023SJohn Marino
2378*e4b17023SJohn Marino record = ggc_alloc_call_site_record_d ();
2379*e4b17023SJohn Marino record->landing_pad = landing_pad;
2380*e4b17023SJohn Marino record->action = action;
2381*e4b17023SJohn Marino
2382*e4b17023SJohn Marino VEC_safe_push (call_site_record, gc,
2383*e4b17023SJohn Marino crtl->eh.call_site_record[section], record);
2384*e4b17023SJohn Marino
2385*e4b17023SJohn Marino return call_site_base + VEC_length (call_site_record,
2386*e4b17023SJohn Marino crtl->eh.call_site_record[section]) - 1;
2387*e4b17023SJohn Marino }
2388*e4b17023SJohn Marino
2389*e4b17023SJohn Marino /* Turn REG_EH_REGION notes back into NOTE_INSN_EH_REGION notes.
2390*e4b17023SJohn Marino The new note numbers will not refer to region numbers, but
2391*e4b17023SJohn Marino instead to call site entries. */
2392*e4b17023SJohn Marino
2393*e4b17023SJohn Marino static unsigned int
convert_to_eh_region_ranges(void)2394*e4b17023SJohn Marino convert_to_eh_region_ranges (void)
2395*e4b17023SJohn Marino {
2396*e4b17023SJohn Marino rtx insn, iter, note;
2397*e4b17023SJohn Marino htab_t ar_hash;
2398*e4b17023SJohn Marino int last_action = -3;
2399*e4b17023SJohn Marino rtx last_action_insn = NULL_RTX;
2400*e4b17023SJohn Marino rtx last_landing_pad = NULL_RTX;
2401*e4b17023SJohn Marino rtx first_no_action_insn = NULL_RTX;
2402*e4b17023SJohn Marino int call_site = 0;
2403*e4b17023SJohn Marino int cur_sec = 0;
2404*e4b17023SJohn Marino rtx section_switch_note = NULL_RTX;
2405*e4b17023SJohn Marino rtx first_no_action_insn_before_switch = NULL_RTX;
2406*e4b17023SJohn Marino rtx last_no_action_insn_before_switch = NULL_RTX;
2407*e4b17023SJohn Marino int saved_call_site_base = call_site_base;
2408*e4b17023SJohn Marino
2409*e4b17023SJohn Marino crtl->eh.action_record_data = VEC_alloc (uchar, gc, 64);
2410*e4b17023SJohn Marino
2411*e4b17023SJohn Marino ar_hash = htab_create (31, action_record_hash, action_record_eq, free);
2412*e4b17023SJohn Marino
2413*e4b17023SJohn Marino for (iter = get_insns (); iter ; iter = NEXT_INSN (iter))
2414*e4b17023SJohn Marino if (INSN_P (iter))
2415*e4b17023SJohn Marino {
2416*e4b17023SJohn Marino eh_landing_pad lp;
2417*e4b17023SJohn Marino eh_region region;
2418*e4b17023SJohn Marino bool nothrow;
2419*e4b17023SJohn Marino int this_action;
2420*e4b17023SJohn Marino rtx this_landing_pad;
2421*e4b17023SJohn Marino
2422*e4b17023SJohn Marino insn = iter;
2423*e4b17023SJohn Marino if (NONJUMP_INSN_P (insn)
2424*e4b17023SJohn Marino && GET_CODE (PATTERN (insn)) == SEQUENCE)
2425*e4b17023SJohn Marino insn = XVECEXP (PATTERN (insn), 0, 0);
2426*e4b17023SJohn Marino
2427*e4b17023SJohn Marino nothrow = get_eh_region_and_lp_from_rtx (insn, ®ion, &lp);
2428*e4b17023SJohn Marino if (nothrow)
2429*e4b17023SJohn Marino continue;
2430*e4b17023SJohn Marino if (region)
2431*e4b17023SJohn Marino this_action = collect_one_action_chain (ar_hash, region);
2432*e4b17023SJohn Marino else
2433*e4b17023SJohn Marino this_action = -1;
2434*e4b17023SJohn Marino
2435*e4b17023SJohn Marino /* Existence of catch handlers, or must-not-throw regions
2436*e4b17023SJohn Marino implies that an lsda is needed (even if empty). */
2437*e4b17023SJohn Marino if (this_action != -1)
2438*e4b17023SJohn Marino crtl->uses_eh_lsda = 1;
2439*e4b17023SJohn Marino
2440*e4b17023SJohn Marino /* Delay creation of region notes for no-action regions
2441*e4b17023SJohn Marino until we're sure that an lsda will be required. */
2442*e4b17023SJohn Marino else if (last_action == -3)
2443*e4b17023SJohn Marino {
2444*e4b17023SJohn Marino first_no_action_insn = iter;
2445*e4b17023SJohn Marino last_action = -1;
2446*e4b17023SJohn Marino }
2447*e4b17023SJohn Marino
2448*e4b17023SJohn Marino if (this_action >= 0)
2449*e4b17023SJohn Marino this_landing_pad = lp->landing_pad;
2450*e4b17023SJohn Marino else
2451*e4b17023SJohn Marino this_landing_pad = NULL_RTX;
2452*e4b17023SJohn Marino
2453*e4b17023SJohn Marino /* Differing actions or landing pads implies a change in call-site
2454*e4b17023SJohn Marino info, which implies some EH_REGION note should be emitted. */
2455*e4b17023SJohn Marino if (last_action != this_action
2456*e4b17023SJohn Marino || last_landing_pad != this_landing_pad)
2457*e4b17023SJohn Marino {
2458*e4b17023SJohn Marino /* If there is a queued no-action region in the other section
2459*e4b17023SJohn Marino with hot/cold partitioning, emit it now. */
2460*e4b17023SJohn Marino if (first_no_action_insn_before_switch)
2461*e4b17023SJohn Marino {
2462*e4b17023SJohn Marino gcc_assert (this_action != -1
2463*e4b17023SJohn Marino && last_action == (first_no_action_insn
2464*e4b17023SJohn Marino ? -1 : -3));
2465*e4b17023SJohn Marino call_site = add_call_site (NULL_RTX, 0, 0);
2466*e4b17023SJohn Marino note = emit_note_before (NOTE_INSN_EH_REGION_BEG,
2467*e4b17023SJohn Marino first_no_action_insn_before_switch);
2468*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2469*e4b17023SJohn Marino note = emit_note_after (NOTE_INSN_EH_REGION_END,
2470*e4b17023SJohn Marino last_no_action_insn_before_switch);
2471*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2472*e4b17023SJohn Marino gcc_assert (last_action != -3
2473*e4b17023SJohn Marino || (last_action_insn
2474*e4b17023SJohn Marino == last_no_action_insn_before_switch));
2475*e4b17023SJohn Marino first_no_action_insn_before_switch = NULL_RTX;
2476*e4b17023SJohn Marino last_no_action_insn_before_switch = NULL_RTX;
2477*e4b17023SJohn Marino call_site_base++;
2478*e4b17023SJohn Marino }
2479*e4b17023SJohn Marino /* If we'd not seen a previous action (-3) or the previous
2480*e4b17023SJohn Marino action was must-not-throw (-2), then we do not need an
2481*e4b17023SJohn Marino end note. */
2482*e4b17023SJohn Marino if (last_action >= -1)
2483*e4b17023SJohn Marino {
2484*e4b17023SJohn Marino /* If we delayed the creation of the begin, do it now. */
2485*e4b17023SJohn Marino if (first_no_action_insn)
2486*e4b17023SJohn Marino {
2487*e4b17023SJohn Marino call_site = add_call_site (NULL_RTX, 0, cur_sec);
2488*e4b17023SJohn Marino note = emit_note_before (NOTE_INSN_EH_REGION_BEG,
2489*e4b17023SJohn Marino first_no_action_insn);
2490*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2491*e4b17023SJohn Marino first_no_action_insn = NULL_RTX;
2492*e4b17023SJohn Marino }
2493*e4b17023SJohn Marino
2494*e4b17023SJohn Marino note = emit_note_after (NOTE_INSN_EH_REGION_END,
2495*e4b17023SJohn Marino last_action_insn);
2496*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2497*e4b17023SJohn Marino }
2498*e4b17023SJohn Marino
2499*e4b17023SJohn Marino /* If the new action is must-not-throw, then no region notes
2500*e4b17023SJohn Marino are created. */
2501*e4b17023SJohn Marino if (this_action >= -1)
2502*e4b17023SJohn Marino {
2503*e4b17023SJohn Marino call_site = add_call_site (this_landing_pad,
2504*e4b17023SJohn Marino this_action < 0 ? 0 : this_action,
2505*e4b17023SJohn Marino cur_sec);
2506*e4b17023SJohn Marino note = emit_note_before (NOTE_INSN_EH_REGION_BEG, iter);
2507*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2508*e4b17023SJohn Marino }
2509*e4b17023SJohn Marino
2510*e4b17023SJohn Marino last_action = this_action;
2511*e4b17023SJohn Marino last_landing_pad = this_landing_pad;
2512*e4b17023SJohn Marino }
2513*e4b17023SJohn Marino last_action_insn = iter;
2514*e4b17023SJohn Marino }
2515*e4b17023SJohn Marino else if (NOTE_P (iter)
2516*e4b17023SJohn Marino && NOTE_KIND (iter) == NOTE_INSN_SWITCH_TEXT_SECTIONS)
2517*e4b17023SJohn Marino {
2518*e4b17023SJohn Marino gcc_assert (section_switch_note == NULL_RTX);
2519*e4b17023SJohn Marino gcc_assert (flag_reorder_blocks_and_partition);
2520*e4b17023SJohn Marino section_switch_note = iter;
2521*e4b17023SJohn Marino if (first_no_action_insn)
2522*e4b17023SJohn Marino {
2523*e4b17023SJohn Marino first_no_action_insn_before_switch = first_no_action_insn;
2524*e4b17023SJohn Marino last_no_action_insn_before_switch = last_action_insn;
2525*e4b17023SJohn Marino first_no_action_insn = NULL_RTX;
2526*e4b17023SJohn Marino gcc_assert (last_action == -1);
2527*e4b17023SJohn Marino last_action = -3;
2528*e4b17023SJohn Marino }
2529*e4b17023SJohn Marino /* Force closing of current EH region before section switch and
2530*e4b17023SJohn Marino opening a new one afterwards. */
2531*e4b17023SJohn Marino else if (last_action != -3)
2532*e4b17023SJohn Marino last_landing_pad = pc_rtx;
2533*e4b17023SJohn Marino call_site_base += VEC_length (call_site_record,
2534*e4b17023SJohn Marino crtl->eh.call_site_record[cur_sec]);
2535*e4b17023SJohn Marino cur_sec++;
2536*e4b17023SJohn Marino gcc_assert (crtl->eh.call_site_record[cur_sec] == NULL);
2537*e4b17023SJohn Marino crtl->eh.call_site_record[cur_sec]
2538*e4b17023SJohn Marino = VEC_alloc (call_site_record, gc, 10);
2539*e4b17023SJohn Marino }
2540*e4b17023SJohn Marino
2541*e4b17023SJohn Marino if (last_action >= -1 && ! first_no_action_insn)
2542*e4b17023SJohn Marino {
2543*e4b17023SJohn Marino note = emit_note_after (NOTE_INSN_EH_REGION_END, last_action_insn);
2544*e4b17023SJohn Marino NOTE_EH_HANDLER (note) = call_site;
2545*e4b17023SJohn Marino }
2546*e4b17023SJohn Marino
2547*e4b17023SJohn Marino call_site_base = saved_call_site_base;
2548*e4b17023SJohn Marino
2549*e4b17023SJohn Marino htab_delete (ar_hash);
2550*e4b17023SJohn Marino return 0;
2551*e4b17023SJohn Marino }
2552*e4b17023SJohn Marino
2553*e4b17023SJohn Marino static bool
gate_convert_to_eh_region_ranges(void)2554*e4b17023SJohn Marino gate_convert_to_eh_region_ranges (void)
2555*e4b17023SJohn Marino {
2556*e4b17023SJohn Marino /* Nothing to do for SJLJ exceptions or if no regions created. */
2557*e4b17023SJohn Marino if (cfun->eh->region_tree == NULL)
2558*e4b17023SJohn Marino return false;
2559*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
2560*e4b17023SJohn Marino return false;
2561*e4b17023SJohn Marino return true;
2562*e4b17023SJohn Marino }
2563*e4b17023SJohn Marino
2564*e4b17023SJohn Marino struct rtl_opt_pass pass_convert_to_eh_region_ranges =
2565*e4b17023SJohn Marino {
2566*e4b17023SJohn Marino {
2567*e4b17023SJohn Marino RTL_PASS,
2568*e4b17023SJohn Marino "eh_ranges", /* name */
2569*e4b17023SJohn Marino gate_convert_to_eh_region_ranges, /* gate */
2570*e4b17023SJohn Marino convert_to_eh_region_ranges, /* execute */
2571*e4b17023SJohn Marino NULL, /* sub */
2572*e4b17023SJohn Marino NULL, /* next */
2573*e4b17023SJohn Marino 0, /* static_pass_number */
2574*e4b17023SJohn Marino TV_NONE, /* tv_id */
2575*e4b17023SJohn Marino 0, /* properties_required */
2576*e4b17023SJohn Marino 0, /* properties_provided */
2577*e4b17023SJohn Marino 0, /* properties_destroyed */
2578*e4b17023SJohn Marino 0, /* todo_flags_start */
2579*e4b17023SJohn Marino 0 /* todo_flags_finish */
2580*e4b17023SJohn Marino }
2581*e4b17023SJohn Marino };
2582*e4b17023SJohn Marino
2583*e4b17023SJohn Marino static void
push_uleb128(VEC (uchar,gc)** data_area,unsigned int value)2584*e4b17023SJohn Marino push_uleb128 (VEC (uchar, gc) **data_area, unsigned int value)
2585*e4b17023SJohn Marino {
2586*e4b17023SJohn Marino do
2587*e4b17023SJohn Marino {
2588*e4b17023SJohn Marino unsigned char byte = value & 0x7f;
2589*e4b17023SJohn Marino value >>= 7;
2590*e4b17023SJohn Marino if (value)
2591*e4b17023SJohn Marino byte |= 0x80;
2592*e4b17023SJohn Marino VEC_safe_push (uchar, gc, *data_area, byte);
2593*e4b17023SJohn Marino }
2594*e4b17023SJohn Marino while (value);
2595*e4b17023SJohn Marino }
2596*e4b17023SJohn Marino
2597*e4b17023SJohn Marino static void
push_sleb128(VEC (uchar,gc)** data_area,int value)2598*e4b17023SJohn Marino push_sleb128 (VEC (uchar, gc) **data_area, int value)
2599*e4b17023SJohn Marino {
2600*e4b17023SJohn Marino unsigned char byte;
2601*e4b17023SJohn Marino int more;
2602*e4b17023SJohn Marino
2603*e4b17023SJohn Marino do
2604*e4b17023SJohn Marino {
2605*e4b17023SJohn Marino byte = value & 0x7f;
2606*e4b17023SJohn Marino value >>= 7;
2607*e4b17023SJohn Marino more = ! ((value == 0 && (byte & 0x40) == 0)
2608*e4b17023SJohn Marino || (value == -1 && (byte & 0x40) != 0));
2609*e4b17023SJohn Marino if (more)
2610*e4b17023SJohn Marino byte |= 0x80;
2611*e4b17023SJohn Marino VEC_safe_push (uchar, gc, *data_area, byte);
2612*e4b17023SJohn Marino }
2613*e4b17023SJohn Marino while (more);
2614*e4b17023SJohn Marino }
2615*e4b17023SJohn Marino
2616*e4b17023SJohn Marino
2617*e4b17023SJohn Marino #ifndef HAVE_AS_LEB128
2618*e4b17023SJohn Marino static int
dw2_size_of_call_site_table(int section)2619*e4b17023SJohn Marino dw2_size_of_call_site_table (int section)
2620*e4b17023SJohn Marino {
2621*e4b17023SJohn Marino int n = VEC_length (call_site_record, crtl->eh.call_site_record[section]);
2622*e4b17023SJohn Marino int size = n * (4 + 4 + 4);
2623*e4b17023SJohn Marino int i;
2624*e4b17023SJohn Marino
2625*e4b17023SJohn Marino for (i = 0; i < n; ++i)
2626*e4b17023SJohn Marino {
2627*e4b17023SJohn Marino struct call_site_record_d *cs =
2628*e4b17023SJohn Marino VEC_index (call_site_record, crtl->eh.call_site_record[section], i);
2629*e4b17023SJohn Marino size += size_of_uleb128 (cs->action);
2630*e4b17023SJohn Marino }
2631*e4b17023SJohn Marino
2632*e4b17023SJohn Marino return size;
2633*e4b17023SJohn Marino }
2634*e4b17023SJohn Marino
2635*e4b17023SJohn Marino static int
sjlj_size_of_call_site_table(void)2636*e4b17023SJohn Marino sjlj_size_of_call_site_table (void)
2637*e4b17023SJohn Marino {
2638*e4b17023SJohn Marino int n = VEC_length (call_site_record, crtl->eh.call_site_record[0]);
2639*e4b17023SJohn Marino int size = 0;
2640*e4b17023SJohn Marino int i;
2641*e4b17023SJohn Marino
2642*e4b17023SJohn Marino for (i = 0; i < n; ++i)
2643*e4b17023SJohn Marino {
2644*e4b17023SJohn Marino struct call_site_record_d *cs =
2645*e4b17023SJohn Marino VEC_index (call_site_record, crtl->eh.call_site_record[0], i);
2646*e4b17023SJohn Marino size += size_of_uleb128 (INTVAL (cs->landing_pad));
2647*e4b17023SJohn Marino size += size_of_uleb128 (cs->action);
2648*e4b17023SJohn Marino }
2649*e4b17023SJohn Marino
2650*e4b17023SJohn Marino return size;
2651*e4b17023SJohn Marino }
2652*e4b17023SJohn Marino #endif
2653*e4b17023SJohn Marino
2654*e4b17023SJohn Marino static void
dw2_output_call_site_table(int cs_format,int section)2655*e4b17023SJohn Marino dw2_output_call_site_table (int cs_format, int section)
2656*e4b17023SJohn Marino {
2657*e4b17023SJohn Marino int n = VEC_length (call_site_record, crtl->eh.call_site_record[section]);
2658*e4b17023SJohn Marino int i;
2659*e4b17023SJohn Marino const char *begin;
2660*e4b17023SJohn Marino
2661*e4b17023SJohn Marino if (section == 0)
2662*e4b17023SJohn Marino begin = current_function_func_begin_label;
2663*e4b17023SJohn Marino else if (first_function_block_is_cold)
2664*e4b17023SJohn Marino begin = crtl->subsections.hot_section_label;
2665*e4b17023SJohn Marino else
2666*e4b17023SJohn Marino begin = crtl->subsections.cold_section_label;
2667*e4b17023SJohn Marino
2668*e4b17023SJohn Marino for (i = 0; i < n; ++i)
2669*e4b17023SJohn Marino {
2670*e4b17023SJohn Marino struct call_site_record_d *cs =
2671*e4b17023SJohn Marino VEC_index (call_site_record, crtl->eh.call_site_record[section], i);
2672*e4b17023SJohn Marino char reg_start_lab[32];
2673*e4b17023SJohn Marino char reg_end_lab[32];
2674*e4b17023SJohn Marino char landing_pad_lab[32];
2675*e4b17023SJohn Marino
2676*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (reg_start_lab, "LEHB", call_site_base + i);
2677*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (reg_end_lab, "LEHE", call_site_base + i);
2678*e4b17023SJohn Marino
2679*e4b17023SJohn Marino if (cs->landing_pad)
2680*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (landing_pad_lab, "L",
2681*e4b17023SJohn Marino CODE_LABEL_NUMBER (cs->landing_pad));
2682*e4b17023SJohn Marino
2683*e4b17023SJohn Marino /* ??? Perhaps use insn length scaling if the assembler supports
2684*e4b17023SJohn Marino generic arithmetic. */
2685*e4b17023SJohn Marino /* ??? Perhaps use attr_length to choose data1 or data2 instead of
2686*e4b17023SJohn Marino data4 if the function is small enough. */
2687*e4b17023SJohn Marino if (cs_format == DW_EH_PE_uleb128)
2688*e4b17023SJohn Marino {
2689*e4b17023SJohn Marino dw2_asm_output_delta_uleb128 (reg_start_lab, begin,
2690*e4b17023SJohn Marino "region %d start", i);
2691*e4b17023SJohn Marino dw2_asm_output_delta_uleb128 (reg_end_lab, reg_start_lab,
2692*e4b17023SJohn Marino "length");
2693*e4b17023SJohn Marino if (cs->landing_pad)
2694*e4b17023SJohn Marino dw2_asm_output_delta_uleb128 (landing_pad_lab, begin,
2695*e4b17023SJohn Marino "landing pad");
2696*e4b17023SJohn Marino else
2697*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (0, "landing pad");
2698*e4b17023SJohn Marino }
2699*e4b17023SJohn Marino else
2700*e4b17023SJohn Marino {
2701*e4b17023SJohn Marino dw2_asm_output_delta (4, reg_start_lab, begin,
2702*e4b17023SJohn Marino "region %d start", i);
2703*e4b17023SJohn Marino dw2_asm_output_delta (4, reg_end_lab, reg_start_lab, "length");
2704*e4b17023SJohn Marino if (cs->landing_pad)
2705*e4b17023SJohn Marino dw2_asm_output_delta (4, landing_pad_lab, begin,
2706*e4b17023SJohn Marino "landing pad");
2707*e4b17023SJohn Marino else
2708*e4b17023SJohn Marino dw2_asm_output_data (4, 0, "landing pad");
2709*e4b17023SJohn Marino }
2710*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (cs->action, "action");
2711*e4b17023SJohn Marino }
2712*e4b17023SJohn Marino
2713*e4b17023SJohn Marino call_site_base += n;
2714*e4b17023SJohn Marino }
2715*e4b17023SJohn Marino
2716*e4b17023SJohn Marino static void
sjlj_output_call_site_table(void)2717*e4b17023SJohn Marino sjlj_output_call_site_table (void)
2718*e4b17023SJohn Marino {
2719*e4b17023SJohn Marino int n = VEC_length (call_site_record, crtl->eh.call_site_record[0]);
2720*e4b17023SJohn Marino int i;
2721*e4b17023SJohn Marino
2722*e4b17023SJohn Marino for (i = 0; i < n; ++i)
2723*e4b17023SJohn Marino {
2724*e4b17023SJohn Marino struct call_site_record_d *cs =
2725*e4b17023SJohn Marino VEC_index (call_site_record, crtl->eh.call_site_record[0], i);
2726*e4b17023SJohn Marino
2727*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (INTVAL (cs->landing_pad),
2728*e4b17023SJohn Marino "region %d landing pad", i);
2729*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (cs->action, "action");
2730*e4b17023SJohn Marino }
2731*e4b17023SJohn Marino
2732*e4b17023SJohn Marino call_site_base += n;
2733*e4b17023SJohn Marino }
2734*e4b17023SJohn Marino
2735*e4b17023SJohn Marino /* Switch to the section that should be used for exception tables. */
2736*e4b17023SJohn Marino
2737*e4b17023SJohn Marino static void
switch_to_exception_section(const char * ARG_UNUSED (fnname))2738*e4b17023SJohn Marino switch_to_exception_section (const char * ARG_UNUSED (fnname))
2739*e4b17023SJohn Marino {
2740*e4b17023SJohn Marino section *s;
2741*e4b17023SJohn Marino
2742*e4b17023SJohn Marino if (exception_section)
2743*e4b17023SJohn Marino s = exception_section;
2744*e4b17023SJohn Marino else
2745*e4b17023SJohn Marino {
2746*e4b17023SJohn Marino /* Compute the section and cache it into exception_section,
2747*e4b17023SJohn Marino unless it depends on the function name. */
2748*e4b17023SJohn Marino if (targetm_common.have_named_sections)
2749*e4b17023SJohn Marino {
2750*e4b17023SJohn Marino int flags;
2751*e4b17023SJohn Marino
2752*e4b17023SJohn Marino if (EH_TABLES_CAN_BE_READ_ONLY)
2753*e4b17023SJohn Marino {
2754*e4b17023SJohn Marino int tt_format =
2755*e4b17023SJohn Marino ASM_PREFERRED_EH_DATA_FORMAT (/*code=*/0, /*global=*/1);
2756*e4b17023SJohn Marino flags = ((! flag_pic
2757*e4b17023SJohn Marino || ((tt_format & 0x70) != DW_EH_PE_absptr
2758*e4b17023SJohn Marino && (tt_format & 0x70) != DW_EH_PE_aligned))
2759*e4b17023SJohn Marino ? 0 : SECTION_WRITE);
2760*e4b17023SJohn Marino }
2761*e4b17023SJohn Marino else
2762*e4b17023SJohn Marino flags = SECTION_WRITE;
2763*e4b17023SJohn Marino
2764*e4b17023SJohn Marino #ifdef HAVE_LD_EH_GC_SECTIONS
2765*e4b17023SJohn Marino if (flag_function_sections)
2766*e4b17023SJohn Marino {
2767*e4b17023SJohn Marino char *section_name = XNEWVEC (char, strlen (fnname) + 32);
2768*e4b17023SJohn Marino sprintf (section_name, ".gcc_except_table.%s", fnname);
2769*e4b17023SJohn Marino s = get_section (section_name, flags, NULL);
2770*e4b17023SJohn Marino free (section_name);
2771*e4b17023SJohn Marino }
2772*e4b17023SJohn Marino else
2773*e4b17023SJohn Marino #endif
2774*e4b17023SJohn Marino exception_section
2775*e4b17023SJohn Marino = s = get_section (".gcc_except_table", flags, NULL);
2776*e4b17023SJohn Marino }
2777*e4b17023SJohn Marino else
2778*e4b17023SJohn Marino exception_section
2779*e4b17023SJohn Marino = s = flag_pic ? data_section : readonly_data_section;
2780*e4b17023SJohn Marino }
2781*e4b17023SJohn Marino
2782*e4b17023SJohn Marino switch_to_section (s);
2783*e4b17023SJohn Marino }
2784*e4b17023SJohn Marino
2785*e4b17023SJohn Marino
2786*e4b17023SJohn Marino /* Output a reference from an exception table to the type_info object TYPE.
2787*e4b17023SJohn Marino TT_FORMAT and TT_FORMAT_SIZE describe the DWARF encoding method used for
2788*e4b17023SJohn Marino the value. */
2789*e4b17023SJohn Marino
2790*e4b17023SJohn Marino static void
output_ttype(tree type,int tt_format,int tt_format_size)2791*e4b17023SJohn Marino output_ttype (tree type, int tt_format, int tt_format_size)
2792*e4b17023SJohn Marino {
2793*e4b17023SJohn Marino rtx value;
2794*e4b17023SJohn Marino bool is_public = true;
2795*e4b17023SJohn Marino
2796*e4b17023SJohn Marino if (type == NULL_TREE)
2797*e4b17023SJohn Marino value = const0_rtx;
2798*e4b17023SJohn Marino else
2799*e4b17023SJohn Marino {
2800*e4b17023SJohn Marino struct varpool_node *node;
2801*e4b17023SJohn Marino
2802*e4b17023SJohn Marino /* FIXME lto. pass_ipa_free_lang_data changes all types to
2803*e4b17023SJohn Marino runtime types so TYPE should already be a runtime type
2804*e4b17023SJohn Marino reference. When pass_ipa_free_lang data is made a default
2805*e4b17023SJohn Marino pass, we can then remove the call to lookup_type_for_runtime
2806*e4b17023SJohn Marino below. */
2807*e4b17023SJohn Marino if (TYPE_P (type))
2808*e4b17023SJohn Marino type = lookup_type_for_runtime (type);
2809*e4b17023SJohn Marino
2810*e4b17023SJohn Marino value = expand_expr (type, NULL_RTX, VOIDmode, EXPAND_INITIALIZER);
2811*e4b17023SJohn Marino
2812*e4b17023SJohn Marino /* Let cgraph know that the rtti decl is used. Not all of the
2813*e4b17023SJohn Marino paths below go through assemble_integer, which would take
2814*e4b17023SJohn Marino care of this for us. */
2815*e4b17023SJohn Marino STRIP_NOPS (type);
2816*e4b17023SJohn Marino if (TREE_CODE (type) == ADDR_EXPR)
2817*e4b17023SJohn Marino {
2818*e4b17023SJohn Marino type = TREE_OPERAND (type, 0);
2819*e4b17023SJohn Marino if (TREE_CODE (type) == VAR_DECL)
2820*e4b17023SJohn Marino {
2821*e4b17023SJohn Marino node = varpool_node (type);
2822*e4b17023SJohn Marino if (node)
2823*e4b17023SJohn Marino varpool_mark_needed_node (node);
2824*e4b17023SJohn Marino is_public = TREE_PUBLIC (type);
2825*e4b17023SJohn Marino }
2826*e4b17023SJohn Marino }
2827*e4b17023SJohn Marino else
2828*e4b17023SJohn Marino gcc_assert (TREE_CODE (type) == INTEGER_CST);
2829*e4b17023SJohn Marino }
2830*e4b17023SJohn Marino
2831*e4b17023SJohn Marino /* Allow the target to override the type table entry format. */
2832*e4b17023SJohn Marino if (targetm.asm_out.ttype (value))
2833*e4b17023SJohn Marino return;
2834*e4b17023SJohn Marino
2835*e4b17023SJohn Marino if (tt_format == DW_EH_PE_absptr || tt_format == DW_EH_PE_aligned)
2836*e4b17023SJohn Marino assemble_integer (value, tt_format_size,
2837*e4b17023SJohn Marino tt_format_size * BITS_PER_UNIT, 1);
2838*e4b17023SJohn Marino else
2839*e4b17023SJohn Marino dw2_asm_output_encoded_addr_rtx (tt_format, value, is_public, NULL);
2840*e4b17023SJohn Marino }
2841*e4b17023SJohn Marino
2842*e4b17023SJohn Marino static void
output_one_function_exception_table(int section)2843*e4b17023SJohn Marino output_one_function_exception_table (int section)
2844*e4b17023SJohn Marino {
2845*e4b17023SJohn Marino int tt_format, cs_format, lp_format, i;
2846*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2847*e4b17023SJohn Marino char ttype_label[32];
2848*e4b17023SJohn Marino char cs_after_size_label[32];
2849*e4b17023SJohn Marino char cs_end_label[32];
2850*e4b17023SJohn Marino #else
2851*e4b17023SJohn Marino int call_site_len;
2852*e4b17023SJohn Marino #endif
2853*e4b17023SJohn Marino int have_tt_data;
2854*e4b17023SJohn Marino int tt_format_size = 0;
2855*e4b17023SJohn Marino
2856*e4b17023SJohn Marino have_tt_data = (VEC_length (tree, cfun->eh->ttype_data)
2857*e4b17023SJohn Marino || (targetm.arm_eabi_unwinder
2858*e4b17023SJohn Marino ? VEC_length (tree, cfun->eh->ehspec_data.arm_eabi)
2859*e4b17023SJohn Marino : VEC_length (uchar, cfun->eh->ehspec_data.other)));
2860*e4b17023SJohn Marino
2861*e4b17023SJohn Marino /* Indicate the format of the @TType entries. */
2862*e4b17023SJohn Marino if (! have_tt_data)
2863*e4b17023SJohn Marino tt_format = DW_EH_PE_omit;
2864*e4b17023SJohn Marino else
2865*e4b17023SJohn Marino {
2866*e4b17023SJohn Marino tt_format = ASM_PREFERRED_EH_DATA_FORMAT (/*code=*/0, /*global=*/1);
2867*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2868*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (ttype_label,
2869*e4b17023SJohn Marino section ? "LLSDATTC" : "LLSDATT",
2870*e4b17023SJohn Marino current_function_funcdef_no);
2871*e4b17023SJohn Marino #endif
2872*e4b17023SJohn Marino tt_format_size = size_of_encoded_value (tt_format);
2873*e4b17023SJohn Marino
2874*e4b17023SJohn Marino assemble_align (tt_format_size * BITS_PER_UNIT);
2875*e4b17023SJohn Marino }
2876*e4b17023SJohn Marino
2877*e4b17023SJohn Marino targetm.asm_out.internal_label (asm_out_file, section ? "LLSDAC" : "LLSDA",
2878*e4b17023SJohn Marino current_function_funcdef_no);
2879*e4b17023SJohn Marino
2880*e4b17023SJohn Marino /* The LSDA header. */
2881*e4b17023SJohn Marino
2882*e4b17023SJohn Marino /* Indicate the format of the landing pad start pointer. An omitted
2883*e4b17023SJohn Marino field implies @LPStart == @Start. */
2884*e4b17023SJohn Marino /* Currently we always put @LPStart == @Start. This field would
2885*e4b17023SJohn Marino be most useful in moving the landing pads completely out of
2886*e4b17023SJohn Marino line to another section, but it could also be used to minimize
2887*e4b17023SJohn Marino the size of uleb128 landing pad offsets. */
2888*e4b17023SJohn Marino lp_format = DW_EH_PE_omit;
2889*e4b17023SJohn Marino dw2_asm_output_data (1, lp_format, "@LPStart format (%s)",
2890*e4b17023SJohn Marino eh_data_format_name (lp_format));
2891*e4b17023SJohn Marino
2892*e4b17023SJohn Marino /* @LPStart pointer would go here. */
2893*e4b17023SJohn Marino
2894*e4b17023SJohn Marino dw2_asm_output_data (1, tt_format, "@TType format (%s)",
2895*e4b17023SJohn Marino eh_data_format_name (tt_format));
2896*e4b17023SJohn Marino
2897*e4b17023SJohn Marino #ifndef HAVE_AS_LEB128
2898*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
2899*e4b17023SJohn Marino call_site_len = sjlj_size_of_call_site_table ();
2900*e4b17023SJohn Marino else
2901*e4b17023SJohn Marino call_site_len = dw2_size_of_call_site_table (section);
2902*e4b17023SJohn Marino #endif
2903*e4b17023SJohn Marino
2904*e4b17023SJohn Marino /* A pc-relative 4-byte displacement to the @TType data. */
2905*e4b17023SJohn Marino if (have_tt_data)
2906*e4b17023SJohn Marino {
2907*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2908*e4b17023SJohn Marino char ttype_after_disp_label[32];
2909*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (ttype_after_disp_label,
2910*e4b17023SJohn Marino section ? "LLSDATTDC" : "LLSDATTD",
2911*e4b17023SJohn Marino current_function_funcdef_no);
2912*e4b17023SJohn Marino dw2_asm_output_delta_uleb128 (ttype_label, ttype_after_disp_label,
2913*e4b17023SJohn Marino "@TType base offset");
2914*e4b17023SJohn Marino ASM_OUTPUT_LABEL (asm_out_file, ttype_after_disp_label);
2915*e4b17023SJohn Marino #else
2916*e4b17023SJohn Marino /* Ug. Alignment queers things. */
2917*e4b17023SJohn Marino unsigned int before_disp, after_disp, last_disp, disp;
2918*e4b17023SJohn Marino
2919*e4b17023SJohn Marino before_disp = 1 + 1;
2920*e4b17023SJohn Marino after_disp = (1 + size_of_uleb128 (call_site_len)
2921*e4b17023SJohn Marino + call_site_len
2922*e4b17023SJohn Marino + VEC_length (uchar, crtl->eh.action_record_data)
2923*e4b17023SJohn Marino + (VEC_length (tree, cfun->eh->ttype_data)
2924*e4b17023SJohn Marino * tt_format_size));
2925*e4b17023SJohn Marino
2926*e4b17023SJohn Marino disp = after_disp;
2927*e4b17023SJohn Marino do
2928*e4b17023SJohn Marino {
2929*e4b17023SJohn Marino unsigned int disp_size, pad;
2930*e4b17023SJohn Marino
2931*e4b17023SJohn Marino last_disp = disp;
2932*e4b17023SJohn Marino disp_size = size_of_uleb128 (disp);
2933*e4b17023SJohn Marino pad = before_disp + disp_size + after_disp;
2934*e4b17023SJohn Marino if (pad % tt_format_size)
2935*e4b17023SJohn Marino pad = tt_format_size - (pad % tt_format_size);
2936*e4b17023SJohn Marino else
2937*e4b17023SJohn Marino pad = 0;
2938*e4b17023SJohn Marino disp = after_disp + pad;
2939*e4b17023SJohn Marino }
2940*e4b17023SJohn Marino while (disp != last_disp);
2941*e4b17023SJohn Marino
2942*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (disp, "@TType base offset");
2943*e4b17023SJohn Marino #endif
2944*e4b17023SJohn Marino }
2945*e4b17023SJohn Marino
2946*e4b17023SJohn Marino /* Indicate the format of the call-site offsets. */
2947*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2948*e4b17023SJohn Marino cs_format = DW_EH_PE_uleb128;
2949*e4b17023SJohn Marino #else
2950*e4b17023SJohn Marino cs_format = DW_EH_PE_udata4;
2951*e4b17023SJohn Marino #endif
2952*e4b17023SJohn Marino dw2_asm_output_data (1, cs_format, "call-site format (%s)",
2953*e4b17023SJohn Marino eh_data_format_name (cs_format));
2954*e4b17023SJohn Marino
2955*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2956*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (cs_after_size_label,
2957*e4b17023SJohn Marino section ? "LLSDACSBC" : "LLSDACSB",
2958*e4b17023SJohn Marino current_function_funcdef_no);
2959*e4b17023SJohn Marino ASM_GENERATE_INTERNAL_LABEL (cs_end_label,
2960*e4b17023SJohn Marino section ? "LLSDACSEC" : "LLSDACSE",
2961*e4b17023SJohn Marino current_function_funcdef_no);
2962*e4b17023SJohn Marino dw2_asm_output_delta_uleb128 (cs_end_label, cs_after_size_label,
2963*e4b17023SJohn Marino "Call-site table length");
2964*e4b17023SJohn Marino ASM_OUTPUT_LABEL (asm_out_file, cs_after_size_label);
2965*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
2966*e4b17023SJohn Marino sjlj_output_call_site_table ();
2967*e4b17023SJohn Marino else
2968*e4b17023SJohn Marino dw2_output_call_site_table (cs_format, section);
2969*e4b17023SJohn Marino ASM_OUTPUT_LABEL (asm_out_file, cs_end_label);
2970*e4b17023SJohn Marino #else
2971*e4b17023SJohn Marino dw2_asm_output_data_uleb128 (call_site_len, "Call-site table length");
2972*e4b17023SJohn Marino if (targetm_common.except_unwind_info (&global_options) == UI_SJLJ)
2973*e4b17023SJohn Marino sjlj_output_call_site_table ();
2974*e4b17023SJohn Marino else
2975*e4b17023SJohn Marino dw2_output_call_site_table (cs_format, section);
2976*e4b17023SJohn Marino #endif
2977*e4b17023SJohn Marino
2978*e4b17023SJohn Marino /* ??? Decode and interpret the data for flag_debug_asm. */
2979*e4b17023SJohn Marino {
2980*e4b17023SJohn Marino uchar uc;
2981*e4b17023SJohn Marino FOR_EACH_VEC_ELT (uchar, crtl->eh.action_record_data, i, uc)
2982*e4b17023SJohn Marino dw2_asm_output_data (1, uc, i ? NULL : "Action record table");
2983*e4b17023SJohn Marino }
2984*e4b17023SJohn Marino
2985*e4b17023SJohn Marino if (have_tt_data)
2986*e4b17023SJohn Marino assemble_align (tt_format_size * BITS_PER_UNIT);
2987*e4b17023SJohn Marino
2988*e4b17023SJohn Marino i = VEC_length (tree, cfun->eh->ttype_data);
2989*e4b17023SJohn Marino while (i-- > 0)
2990*e4b17023SJohn Marino {
2991*e4b17023SJohn Marino tree type = VEC_index (tree, cfun->eh->ttype_data, i);
2992*e4b17023SJohn Marino output_ttype (type, tt_format, tt_format_size);
2993*e4b17023SJohn Marino }
2994*e4b17023SJohn Marino
2995*e4b17023SJohn Marino #ifdef HAVE_AS_LEB128
2996*e4b17023SJohn Marino if (have_tt_data)
2997*e4b17023SJohn Marino ASM_OUTPUT_LABEL (asm_out_file, ttype_label);
2998*e4b17023SJohn Marino #endif
2999*e4b17023SJohn Marino
3000*e4b17023SJohn Marino /* ??? Decode and interpret the data for flag_debug_asm. */
3001*e4b17023SJohn Marino if (targetm.arm_eabi_unwinder)
3002*e4b17023SJohn Marino {
3003*e4b17023SJohn Marino tree type;
3004*e4b17023SJohn Marino for (i = 0;
3005*e4b17023SJohn Marino VEC_iterate (tree, cfun->eh->ehspec_data.arm_eabi, i, type); ++i)
3006*e4b17023SJohn Marino output_ttype (type, tt_format, tt_format_size);
3007*e4b17023SJohn Marino }
3008*e4b17023SJohn Marino else
3009*e4b17023SJohn Marino {
3010*e4b17023SJohn Marino uchar uc;
3011*e4b17023SJohn Marino for (i = 0;
3012*e4b17023SJohn Marino VEC_iterate (uchar, cfun->eh->ehspec_data.other, i, uc); ++i)
3013*e4b17023SJohn Marino dw2_asm_output_data (1, uc,
3014*e4b17023SJohn Marino i ? NULL : "Exception specification table");
3015*e4b17023SJohn Marino }
3016*e4b17023SJohn Marino }
3017*e4b17023SJohn Marino
3018*e4b17023SJohn Marino void
output_function_exception_table(const char * fnname)3019*e4b17023SJohn Marino output_function_exception_table (const char *fnname)
3020*e4b17023SJohn Marino {
3021*e4b17023SJohn Marino rtx personality = get_personality_function (current_function_decl);
3022*e4b17023SJohn Marino
3023*e4b17023SJohn Marino /* Not all functions need anything. */
3024*e4b17023SJohn Marino if (! crtl->uses_eh_lsda)
3025*e4b17023SJohn Marino return;
3026*e4b17023SJohn Marino
3027*e4b17023SJohn Marino if (personality)
3028*e4b17023SJohn Marino {
3029*e4b17023SJohn Marino assemble_external_libcall (personality);
3030*e4b17023SJohn Marino
3031*e4b17023SJohn Marino if (targetm.asm_out.emit_except_personality)
3032*e4b17023SJohn Marino targetm.asm_out.emit_except_personality (personality);
3033*e4b17023SJohn Marino }
3034*e4b17023SJohn Marino
3035*e4b17023SJohn Marino switch_to_exception_section (fnname);
3036*e4b17023SJohn Marino
3037*e4b17023SJohn Marino /* If the target wants a label to begin the table, emit it here. */
3038*e4b17023SJohn Marino targetm.asm_out.emit_except_table_label (asm_out_file);
3039*e4b17023SJohn Marino
3040*e4b17023SJohn Marino output_one_function_exception_table (0);
3041*e4b17023SJohn Marino if (crtl->eh.call_site_record[1] != NULL)
3042*e4b17023SJohn Marino output_one_function_exception_table (1);
3043*e4b17023SJohn Marino
3044*e4b17023SJohn Marino switch_to_section (current_function_section ());
3045*e4b17023SJohn Marino }
3046*e4b17023SJohn Marino
3047*e4b17023SJohn Marino void
set_eh_throw_stmt_table(struct function * fun,struct htab * table)3048*e4b17023SJohn Marino set_eh_throw_stmt_table (struct function *fun, struct htab *table)
3049*e4b17023SJohn Marino {
3050*e4b17023SJohn Marino fun->eh->throw_stmt_table = table;
3051*e4b17023SJohn Marino }
3052*e4b17023SJohn Marino
3053*e4b17023SJohn Marino htab_t
get_eh_throw_stmt_table(struct function * fun)3054*e4b17023SJohn Marino get_eh_throw_stmt_table (struct function *fun)
3055*e4b17023SJohn Marino {
3056*e4b17023SJohn Marino return fun->eh->throw_stmt_table;
3057*e4b17023SJohn Marino }
3058*e4b17023SJohn Marino
3059*e4b17023SJohn Marino /* Determine if the function needs an EH personality function. */
3060*e4b17023SJohn Marino
3061*e4b17023SJohn Marino enum eh_personality_kind
function_needs_eh_personality(struct function * fn)3062*e4b17023SJohn Marino function_needs_eh_personality (struct function *fn)
3063*e4b17023SJohn Marino {
3064*e4b17023SJohn Marino enum eh_personality_kind kind = eh_personality_none;
3065*e4b17023SJohn Marino eh_region i;
3066*e4b17023SJohn Marino
3067*e4b17023SJohn Marino FOR_ALL_EH_REGION_FN (i, fn)
3068*e4b17023SJohn Marino {
3069*e4b17023SJohn Marino switch (i->type)
3070*e4b17023SJohn Marino {
3071*e4b17023SJohn Marino case ERT_CLEANUP:
3072*e4b17023SJohn Marino /* Can do with any personality including the generic C one. */
3073*e4b17023SJohn Marino kind = eh_personality_any;
3074*e4b17023SJohn Marino break;
3075*e4b17023SJohn Marino
3076*e4b17023SJohn Marino case ERT_TRY:
3077*e4b17023SJohn Marino case ERT_ALLOWED_EXCEPTIONS:
3078*e4b17023SJohn Marino /* Always needs a EH personality function. The generic C
3079*e4b17023SJohn Marino personality doesn't handle these even for empty type lists. */
3080*e4b17023SJohn Marino return eh_personality_lang;
3081*e4b17023SJohn Marino
3082*e4b17023SJohn Marino case ERT_MUST_NOT_THROW:
3083*e4b17023SJohn Marino /* Always needs a EH personality function. The language may specify
3084*e4b17023SJohn Marino what abort routine that must be used, e.g. std::terminate. */
3085*e4b17023SJohn Marino return eh_personality_lang;
3086*e4b17023SJohn Marino }
3087*e4b17023SJohn Marino }
3088*e4b17023SJohn Marino
3089*e4b17023SJohn Marino return kind;
3090*e4b17023SJohn Marino }
3091*e4b17023SJohn Marino
3092*e4b17023SJohn Marino /* Dump EH information to OUT. */
3093*e4b17023SJohn Marino
3094*e4b17023SJohn Marino void
dump_eh_tree(FILE * out,struct function * fun)3095*e4b17023SJohn Marino dump_eh_tree (FILE * out, struct function *fun)
3096*e4b17023SJohn Marino {
3097*e4b17023SJohn Marino eh_region i;
3098*e4b17023SJohn Marino int depth = 0;
3099*e4b17023SJohn Marino static const char *const type_name[] = {
3100*e4b17023SJohn Marino "cleanup", "try", "allowed_exceptions", "must_not_throw"
3101*e4b17023SJohn Marino };
3102*e4b17023SJohn Marino
3103*e4b17023SJohn Marino i = fun->eh->region_tree;
3104*e4b17023SJohn Marino if (!i)
3105*e4b17023SJohn Marino return;
3106*e4b17023SJohn Marino
3107*e4b17023SJohn Marino fprintf (out, "Eh tree:\n");
3108*e4b17023SJohn Marino while (1)
3109*e4b17023SJohn Marino {
3110*e4b17023SJohn Marino fprintf (out, " %*s %i %s", depth * 2, "",
3111*e4b17023SJohn Marino i->index, type_name[(int) i->type]);
3112*e4b17023SJohn Marino
3113*e4b17023SJohn Marino if (i->landing_pads)
3114*e4b17023SJohn Marino {
3115*e4b17023SJohn Marino eh_landing_pad lp;
3116*e4b17023SJohn Marino
3117*e4b17023SJohn Marino fprintf (out, " land:");
3118*e4b17023SJohn Marino if (current_ir_type () == IR_GIMPLE)
3119*e4b17023SJohn Marino {
3120*e4b17023SJohn Marino for (lp = i->landing_pads; lp ; lp = lp->next_lp)
3121*e4b17023SJohn Marino {
3122*e4b17023SJohn Marino fprintf (out, "{%i,", lp->index);
3123*e4b17023SJohn Marino print_generic_expr (out, lp->post_landing_pad, 0);
3124*e4b17023SJohn Marino fputc ('}', out);
3125*e4b17023SJohn Marino if (lp->next_lp)
3126*e4b17023SJohn Marino fputc (',', out);
3127*e4b17023SJohn Marino }
3128*e4b17023SJohn Marino }
3129*e4b17023SJohn Marino else
3130*e4b17023SJohn Marino {
3131*e4b17023SJohn Marino for (lp = i->landing_pads; lp ; lp = lp->next_lp)
3132*e4b17023SJohn Marino {
3133*e4b17023SJohn Marino fprintf (out, "{%i,", lp->index);
3134*e4b17023SJohn Marino if (lp->landing_pad)
3135*e4b17023SJohn Marino fprintf (out, "%i%s,", INSN_UID (lp->landing_pad),
3136*e4b17023SJohn Marino NOTE_P (lp->landing_pad) ? "(del)" : "");
3137*e4b17023SJohn Marino else
3138*e4b17023SJohn Marino fprintf (out, "(nil),");
3139*e4b17023SJohn Marino if (lp->post_landing_pad)
3140*e4b17023SJohn Marino {
3141*e4b17023SJohn Marino rtx lab = label_rtx (lp->post_landing_pad);
3142*e4b17023SJohn Marino fprintf (out, "%i%s}", INSN_UID (lab),
3143*e4b17023SJohn Marino NOTE_P (lab) ? "(del)" : "");
3144*e4b17023SJohn Marino }
3145*e4b17023SJohn Marino else
3146*e4b17023SJohn Marino fprintf (out, "(nil)}");
3147*e4b17023SJohn Marino if (lp->next_lp)
3148*e4b17023SJohn Marino fputc (',', out);
3149*e4b17023SJohn Marino }
3150*e4b17023SJohn Marino }
3151*e4b17023SJohn Marino }
3152*e4b17023SJohn Marino
3153*e4b17023SJohn Marino switch (i->type)
3154*e4b17023SJohn Marino {
3155*e4b17023SJohn Marino case ERT_CLEANUP:
3156*e4b17023SJohn Marino case ERT_MUST_NOT_THROW:
3157*e4b17023SJohn Marino break;
3158*e4b17023SJohn Marino
3159*e4b17023SJohn Marino case ERT_TRY:
3160*e4b17023SJohn Marino {
3161*e4b17023SJohn Marino eh_catch c;
3162*e4b17023SJohn Marino fprintf (out, " catch:");
3163*e4b17023SJohn Marino for (c = i->u.eh_try.first_catch; c; c = c->next_catch)
3164*e4b17023SJohn Marino {
3165*e4b17023SJohn Marino fputc ('{', out);
3166*e4b17023SJohn Marino if (c->label)
3167*e4b17023SJohn Marino {
3168*e4b17023SJohn Marino fprintf (out, "lab:");
3169*e4b17023SJohn Marino print_generic_expr (out, c->label, 0);
3170*e4b17023SJohn Marino fputc (';', out);
3171*e4b17023SJohn Marino }
3172*e4b17023SJohn Marino print_generic_expr (out, c->type_list, 0);
3173*e4b17023SJohn Marino fputc ('}', out);
3174*e4b17023SJohn Marino if (c->next_catch)
3175*e4b17023SJohn Marino fputc (',', out);
3176*e4b17023SJohn Marino }
3177*e4b17023SJohn Marino }
3178*e4b17023SJohn Marino break;
3179*e4b17023SJohn Marino
3180*e4b17023SJohn Marino case ERT_ALLOWED_EXCEPTIONS:
3181*e4b17023SJohn Marino fprintf (out, " filter :%i types:", i->u.allowed.filter);
3182*e4b17023SJohn Marino print_generic_expr (out, i->u.allowed.type_list, 0);
3183*e4b17023SJohn Marino break;
3184*e4b17023SJohn Marino }
3185*e4b17023SJohn Marino fputc ('\n', out);
3186*e4b17023SJohn Marino
3187*e4b17023SJohn Marino /* If there are sub-regions, process them. */
3188*e4b17023SJohn Marino if (i->inner)
3189*e4b17023SJohn Marino i = i->inner, depth++;
3190*e4b17023SJohn Marino /* If there are peers, process them. */
3191*e4b17023SJohn Marino else if (i->next_peer)
3192*e4b17023SJohn Marino i = i->next_peer;
3193*e4b17023SJohn Marino /* Otherwise, step back up the tree to the next peer. */
3194*e4b17023SJohn Marino else
3195*e4b17023SJohn Marino {
3196*e4b17023SJohn Marino do
3197*e4b17023SJohn Marino {
3198*e4b17023SJohn Marino i = i->outer;
3199*e4b17023SJohn Marino depth--;
3200*e4b17023SJohn Marino if (i == NULL)
3201*e4b17023SJohn Marino return;
3202*e4b17023SJohn Marino }
3203*e4b17023SJohn Marino while (i->next_peer == NULL);
3204*e4b17023SJohn Marino i = i->next_peer;
3205*e4b17023SJohn Marino }
3206*e4b17023SJohn Marino }
3207*e4b17023SJohn Marino }
3208*e4b17023SJohn Marino
3209*e4b17023SJohn Marino /* Dump the EH tree for FN on stderr. */
3210*e4b17023SJohn Marino
3211*e4b17023SJohn Marino DEBUG_FUNCTION void
debug_eh_tree(struct function * fn)3212*e4b17023SJohn Marino debug_eh_tree (struct function *fn)
3213*e4b17023SJohn Marino {
3214*e4b17023SJohn Marino dump_eh_tree (stderr, fn);
3215*e4b17023SJohn Marino }
3216*e4b17023SJohn Marino
3217*e4b17023SJohn Marino /* Verify invariants on EH datastructures. */
3218*e4b17023SJohn Marino
3219*e4b17023SJohn Marino DEBUG_FUNCTION void
verify_eh_tree(struct function * fun)3220*e4b17023SJohn Marino verify_eh_tree (struct function *fun)
3221*e4b17023SJohn Marino {
3222*e4b17023SJohn Marino eh_region r, outer;
3223*e4b17023SJohn Marino int nvisited_lp, nvisited_r;
3224*e4b17023SJohn Marino int count_lp, count_r, depth, i;
3225*e4b17023SJohn Marino eh_landing_pad lp;
3226*e4b17023SJohn Marino bool err = false;
3227*e4b17023SJohn Marino
3228*e4b17023SJohn Marino if (!fun->eh->region_tree)
3229*e4b17023SJohn Marino return;
3230*e4b17023SJohn Marino
3231*e4b17023SJohn Marino count_r = 0;
3232*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_region, fun->eh->region_array, i, r); ++i)
3233*e4b17023SJohn Marino if (r)
3234*e4b17023SJohn Marino {
3235*e4b17023SJohn Marino if (r->index == i)
3236*e4b17023SJohn Marino count_r++;
3237*e4b17023SJohn Marino else
3238*e4b17023SJohn Marino {
3239*e4b17023SJohn Marino error ("region_array is corrupted for region %i", r->index);
3240*e4b17023SJohn Marino err = true;
3241*e4b17023SJohn Marino }
3242*e4b17023SJohn Marino }
3243*e4b17023SJohn Marino
3244*e4b17023SJohn Marino count_lp = 0;
3245*e4b17023SJohn Marino for (i = 1; VEC_iterate (eh_landing_pad, fun->eh->lp_array, i, lp); ++i)
3246*e4b17023SJohn Marino if (lp)
3247*e4b17023SJohn Marino {
3248*e4b17023SJohn Marino if (lp->index == i)
3249*e4b17023SJohn Marino count_lp++;
3250*e4b17023SJohn Marino else
3251*e4b17023SJohn Marino {
3252*e4b17023SJohn Marino error ("lp_array is corrupted for lp %i", lp->index);
3253*e4b17023SJohn Marino err = true;
3254*e4b17023SJohn Marino }
3255*e4b17023SJohn Marino }
3256*e4b17023SJohn Marino
3257*e4b17023SJohn Marino depth = nvisited_lp = nvisited_r = 0;
3258*e4b17023SJohn Marino outer = NULL;
3259*e4b17023SJohn Marino r = fun->eh->region_tree;
3260*e4b17023SJohn Marino while (1)
3261*e4b17023SJohn Marino {
3262*e4b17023SJohn Marino if (VEC_index (eh_region, fun->eh->region_array, r->index) != r)
3263*e4b17023SJohn Marino {
3264*e4b17023SJohn Marino error ("region_array is corrupted for region %i", r->index);
3265*e4b17023SJohn Marino err = true;
3266*e4b17023SJohn Marino }
3267*e4b17023SJohn Marino if (r->outer != outer)
3268*e4b17023SJohn Marino {
3269*e4b17023SJohn Marino error ("outer block of region %i is wrong", r->index);
3270*e4b17023SJohn Marino err = true;
3271*e4b17023SJohn Marino }
3272*e4b17023SJohn Marino if (depth < 0)
3273*e4b17023SJohn Marino {
3274*e4b17023SJohn Marino error ("negative nesting depth of region %i", r->index);
3275*e4b17023SJohn Marino err = true;
3276*e4b17023SJohn Marino }
3277*e4b17023SJohn Marino nvisited_r++;
3278*e4b17023SJohn Marino
3279*e4b17023SJohn Marino for (lp = r->landing_pads; lp ; lp = lp->next_lp)
3280*e4b17023SJohn Marino {
3281*e4b17023SJohn Marino if (VEC_index (eh_landing_pad, fun->eh->lp_array, lp->index) != lp)
3282*e4b17023SJohn Marino {
3283*e4b17023SJohn Marino error ("lp_array is corrupted for lp %i", lp->index);
3284*e4b17023SJohn Marino err = true;
3285*e4b17023SJohn Marino }
3286*e4b17023SJohn Marino if (lp->region != r)
3287*e4b17023SJohn Marino {
3288*e4b17023SJohn Marino error ("region of lp %i is wrong", lp->index);
3289*e4b17023SJohn Marino err = true;
3290*e4b17023SJohn Marino }
3291*e4b17023SJohn Marino nvisited_lp++;
3292*e4b17023SJohn Marino }
3293*e4b17023SJohn Marino
3294*e4b17023SJohn Marino if (r->inner)
3295*e4b17023SJohn Marino outer = r, r = r->inner, depth++;
3296*e4b17023SJohn Marino else if (r->next_peer)
3297*e4b17023SJohn Marino r = r->next_peer;
3298*e4b17023SJohn Marino else
3299*e4b17023SJohn Marino {
3300*e4b17023SJohn Marino do
3301*e4b17023SJohn Marino {
3302*e4b17023SJohn Marino r = r->outer;
3303*e4b17023SJohn Marino if (r == NULL)
3304*e4b17023SJohn Marino goto region_done;
3305*e4b17023SJohn Marino depth--;
3306*e4b17023SJohn Marino outer = r->outer;
3307*e4b17023SJohn Marino }
3308*e4b17023SJohn Marino while (r->next_peer == NULL);
3309*e4b17023SJohn Marino r = r->next_peer;
3310*e4b17023SJohn Marino }
3311*e4b17023SJohn Marino }
3312*e4b17023SJohn Marino region_done:
3313*e4b17023SJohn Marino if (depth != 0)
3314*e4b17023SJohn Marino {
3315*e4b17023SJohn Marino error ("tree list ends on depth %i", depth);
3316*e4b17023SJohn Marino err = true;
3317*e4b17023SJohn Marino }
3318*e4b17023SJohn Marino if (count_r != nvisited_r)
3319*e4b17023SJohn Marino {
3320*e4b17023SJohn Marino error ("region_array does not match region_tree");
3321*e4b17023SJohn Marino err = true;
3322*e4b17023SJohn Marino }
3323*e4b17023SJohn Marino if (count_lp != nvisited_lp)
3324*e4b17023SJohn Marino {
3325*e4b17023SJohn Marino error ("lp_array does not match region_tree");
3326*e4b17023SJohn Marino err = true;
3327*e4b17023SJohn Marino }
3328*e4b17023SJohn Marino
3329*e4b17023SJohn Marino if (err)
3330*e4b17023SJohn Marino {
3331*e4b17023SJohn Marino dump_eh_tree (stderr, fun);
3332*e4b17023SJohn Marino internal_error ("verify_eh_tree failed");
3333*e4b17023SJohn Marino }
3334*e4b17023SJohn Marino }
3335*e4b17023SJohn Marino
3336*e4b17023SJohn Marino #include "gt-except.h"
3337