OSDN Git Service

Warning fixes:
[pf3gnuchains/gcc-fork.git] / gcc / cp / except.c
1 /* Handle exceptional things in C++.
2    Copyright (C) 1989, 92-97, 1998 Free Software Foundation, Inc.
3    Contributed by Michael Tiemann <tiemann@cygnus.com>
4    Rewritten by Mike Stump <mrs@cygnus.com>, based upon an
5    initial re-implementation courtesy Tad Hunt.
6
7 This file is part of GNU CC.
8
9 GNU CC is free software; you can redistribute it and/or modify
10 it under the terms of the GNU General Public License as published by
11 the Free Software Foundation; either version 2, or (at your option)
12 any later version.
13
14 GNU CC is distributed in the hope that it will be useful,
15 but WITHOUT ANY WARRANTY; without even the implied warranty of
16 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17 GNU General Public License for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GNU CC; see the file COPYING.  If not, write to
21 the Free Software Foundation, 59 Temple Place - Suite 330,
22 Boston, MA 02111-1307, USA.  */
23
24
25 #include "config.h"
26 #include "system.h"
27 #include "tree.h"
28 #include "rtl.h"
29 #include "cp-tree.h"
30 #include "flags.h"
31 #include "obstack.h"
32 #include "expr.h"
33 #include "output.h"
34 #include "except.h"
35 #include "function.h"
36 #include "defaults.h"
37 #include "toplev.h"
38 #include "eh-common.h"
39
40 rtx expand_builtin_return_addr  PROTO((enum built_in_function, int, rtx));
41
42 /* Holds the fndecl for __builtin_return_address.  */
43 tree builtin_return_address_fndecl;
44
45 /* A couple of backend routines from m88k.c */
46
47 static void push_eh_cleanup PROTO((void));
48 static tree build_eh_type_type PROTO((tree));
49 static tree build_eh_type PROTO((tree));
50 static void expand_end_eh_spec PROTO((tree));
51 static tree call_eh_info PROTO((void));
52 static void push_eh_info PROTO((void));
53 static tree get_eh_info PROTO((void));
54 static tree get_eh_value PROTO((void));
55 static tree get_eh_type PROTO((void));
56 static tree get_eh_caught PROTO((void));
57 static tree get_eh_handlers PROTO((void));
58 static tree do_pop_exception PROTO((void));
59 static void process_start_catch_block PROTO((tree, tree));
60 static void process_start_catch_block_old PROTO((tree, tree));
61 static tree build_eh_type_type_ref PROTO((tree));
62
63 #if 0
64 /* This is the startup, and finish stuff per exception table.  */
65
66 /* XXX - Tad: exception handling section */
67 #ifndef EXCEPT_SECTION_ASM_OP
68 #define EXCEPT_SECTION_ASM_OP   "section\t.gcc_except_table,\"a\",@progbits"
69 #endif
70
71 #ifdef EXCEPT_SECTION_ASM_OP
72
73  /* on machines which support it, the exception table lives in another section,
74         but it needs a label so we can reference it...  This sets up that
75     label! */
76 asm (EXCEPT_SECTION_ASM_OP);
77 exception_table __EXCEPTION_TABLE__[1] = { (void*)0, (void*)0, (void*)0 };
78 asm (TEXT_SECTION_ASM_OP);
79
80 #endif /* EXCEPT_SECTION_ASM_OP */
81
82 #ifdef EXCEPT_SECTION_ASM_OP
83
84  /* we need to know where the end of the exception table is... so this
85     is how we do it! */
86
87 asm (EXCEPT_SECTION_ASM_OP);
88 exception_table __EXCEPTION_END__[1] = { (void*)-1, (void*)-1, (void*)-1 };
89 asm (TEXT_SECTION_ASM_OP);
90
91 #endif /* EXCEPT_SECTION_ASM_OP */
92
93 #endif
94
95 #include "decl.h"
96 #include "insn-flags.h"
97 #include "obstack.h"
98
99 /* ======================================================================
100    Briefly the algorithm works like this:
101
102      When a constructor or start of a try block is encountered,
103      push_eh_entry (&eh_stack) is called.  Push_eh_entry () creates a
104      new entry in the unwind protection stack and returns a label to
105      output to start the protection for that block.
106
107      When a destructor or end try block is encountered, pop_eh_entry
108      (&eh_stack) is called.  Pop_eh_entry () returns the eh_entry it
109      created when push_eh_entry () was called.  The eh_entry structure
110      contains three things at this point.  The start protect label,
111      the end protect label, and the exception handler label.  The end
112      protect label should be output before the call to the destructor
113      (if any). If it was a destructor, then its parse tree is stored
114      in the finalization variable in the eh_entry structure.  Otherwise
115      the finalization variable is set to NULL to reflect the fact that
116      it is the end of a try block.  Next, this modified eh_entry node
117      is enqueued in the finalizations queue by calling
118      enqueue_eh_entry (&queue,entry).
119
120         +---------------------------------------------------------------+
121         |XXX: Will need modification to deal with partially             |
122         |                       constructed arrays of objects           |
123         |                                                               |
124         |       Basically, this consists of keeping track of how many   |
125         |       of the objects have been constructed already (this      |
126         |       should be in a register though, so that shouldn't be a  |
127         |       problem.                                                |
128         +---------------------------------------------------------------+
129
130      When a catch block is encountered, there is a lot of work to be
131      done.
132
133      Since we don't want to generate the catch block inline with the
134      regular flow of the function, we need to have some way of doing
135      so.  Luckily, we can use sequences to defer the catch sections.
136      When the start of a catch block is encountered, we start the
137      sequence.  After the catch block is generated, we end the
138      sequence.
139
140      Next we must insure that when the catch block is executed, all
141      finalizations for the matching try block have been completed.  If
142      any of those finalizations throw an exception, we must call
143      terminate according to the ARM (section r.15.6.1).  What this
144      means is that we need to dequeue and emit finalizations for each
145      entry in the eh_queue until we get to an entry with a NULL
146      finalization field.  For any of the finalization entries, if it
147      is not a call to terminate (), we must protect it by giving it
148      another start label, end label, and exception handler label,
149      setting its finalization tree to be a call to terminate (), and
150      enqueue'ing this new eh_entry to be output at an outer level.
151      Finally, after all that is done, we can get around to outputting
152      the catch block which basically wraps all the "catch (...) {...}"
153      statements in a big if/then/else construct that matches the
154      correct block to call.
155      
156      ===================================================================== */
157
158 /* local globals for function calls
159    ====================================================================== */
160
161 /* Used to cache "terminate" and "__throw_type_match*".  */
162 static tree Terminate, CatchMatch;
163
164 /* Used to cache __find_first_exception_table_match for throw.  */
165 static tree FirstExceptionMatch;
166
167 /* Used to cache a call to __unwind_function.  */
168 static tree Unwind;
169
170 /* ====================================================================== */
171
172
173 /* ========================================================================= */
174
175
176
177 /* local globals - these local globals are for storing data necessary for
178    generating the exception table and code in the correct order.
179
180    ========================================================================= */
181
182 extern rtx catch_clauses;
183 extern tree const_ptr_type_node;
184
185 /* ========================================================================= */
186
187 /* sets up all the global eh stuff that needs to be initialized at the
188    start of compilation.
189
190    This includes:
191                 - Setting up all the function call trees.  */
192
193 void
194 init_exception_processing ()
195 {
196   /* void vtype () */
197   tree vtype = build_function_type (void_type_node, void_list_node);
198   
199   if (flag_honor_std)
200     push_namespace (get_identifier ("std"));
201   Terminate = auto_function (get_identifier ("terminate"),
202                              vtype, NOT_BUILT_IN);
203   TREE_THIS_VOLATILE (Terminate) = 1;
204   if (flag_honor_std)
205     pop_namespace ();
206
207   push_lang_context (lang_name_c);
208
209   set_exception_lang_code (EH_LANG_C_plus_plus);
210   set_exception_version_code (1);
211
212   CatchMatch
213     = builtin_function (flag_rtti
214                         ? "__throw_type_match_rtti"
215                         : "__throw_type_match",
216                         build_function_type (ptr_type_node,
217                                              tree_cons (NULL_TREE, const_ptr_type_node,
218                                                         tree_cons (NULL_TREE, const_ptr_type_node,
219                                                                    tree_cons (NULL_TREE, ptr_type_node,
220                                                                               void_list_node)))),
221                         NOT_BUILT_IN, NULL_PTR);
222   FirstExceptionMatch
223     = builtin_function ("__find_first_exception_table_match",
224                         build_function_type (ptr_type_node,
225                                              tree_cons (NULL_TREE, ptr_type_node,
226                                                         void_list_node)),
227                         NOT_BUILT_IN, NULL_PTR);
228   Unwind
229     = builtin_function ("__unwind_function",
230                         build_function_type (void_type_node,
231                                              tree_cons (NULL_TREE, ptr_type_node,
232                                                         void_list_node)),
233                         NOT_BUILT_IN, NULL_PTR);
234
235   pop_lang_context ();
236
237   /* If we use setjmp/longjmp EH, arrange for all cleanup actions to
238      be protected with __terminate.  */
239   protect_cleanup_actions_with_terminate = 1;
240 }
241
242 /* Retrieve a pointer to the cp_eh_info node for the current exception.  */
243
244 static tree
245 call_eh_info ()
246 {
247   tree fn;
248
249   fn = get_identifier ("__cp_eh_info");
250   if (IDENTIFIER_GLOBAL_VALUE (fn))
251     fn = IDENTIFIER_GLOBAL_VALUE (fn);
252   else
253     {
254       tree t1, t, fields[7];
255
256       /* Declare cp_eh_info * __cp_eh_info (void),
257          as defined in exception.cc. */
258       push_obstacks_nochange ();
259       end_temporary_allocation ();
260
261       /* struct cp_eh_info.  This must match exception.cc.  Note that this
262          type is not pushed anywhere.  */
263       t1= make_lang_type (RECORD_TYPE);
264       fields[0] = build_lang_field_decl (FIELD_DECL, 
265                     get_identifier ("handler_label"), ptr_type_node);
266       fields[1] = build_lang_field_decl (FIELD_DECL, 
267                     get_identifier ("dynamic_handler_chain"), ptr_type_node);
268       fields[2] = build_lang_field_decl (FIELD_DECL, 
269                     get_identifier ("info"), ptr_type_node);
270       /* N.B.: The fourth field LEN is expected to be
271          the number of fields - 1, not the total number of fields.  */
272       finish_builtin_type (t1, "eh_context", fields, 2, ptr_type_node);
273       t1 = build_pointer_type (t1);
274
275       t1= make_lang_type (RECORD_TYPE);
276       fields[0] = build_lang_field_decl (FIELD_DECL, 
277                     get_identifier ("match_function"), ptr_type_node);
278       fields[1] = build_lang_field_decl (FIELD_DECL, 
279                     get_identifier ("language"), short_integer_type_node);
280       fields[2] = build_lang_field_decl (FIELD_DECL, 
281                     get_identifier ("version"), short_integer_type_node);
282       /* N.B.: The fourth field LEN is expected to be
283          the number of fields - 1, not the total number of fields.  */
284       finish_builtin_type (t1, "__eh_info", fields, 2, ptr_type_node);
285       t = make_lang_type (RECORD_TYPE);
286       fields[0] = build_lang_field_decl (FIELD_DECL, 
287                                               get_identifier ("eh_info"), t1);
288       fields[1] = build_lang_field_decl (FIELD_DECL, get_identifier ("value"),
289                                          ptr_type_node);
290       fields[2] = build_lang_field_decl (FIELD_DECL, get_identifier ("type"),
291                                          ptr_type_node);
292       fields[3] = build_lang_field_decl
293         (FIELD_DECL, get_identifier ("cleanup"),
294          build_pointer_type (build_function_type
295                              (ptr_type_node, tree_cons
296                               (NULL_TREE, ptr_type_node, void_list_node))));
297       fields[4] = build_lang_field_decl (FIELD_DECL, get_identifier ("caught"),
298                                          boolean_type_node);
299       fields[5] = build_lang_field_decl (FIELD_DECL, get_identifier ("next"),
300                                          build_pointer_type (t));
301       fields[6] = build_lang_field_decl
302         (FIELD_DECL, get_identifier ("handlers"), long_integer_type_node);
303       /* N.B.: The fourth field LEN is expected to be
304          the number of fields - 1, not the total number of fields.  */
305       finish_builtin_type (t, "cp_eh_info", fields, 6, ptr_type_node);
306       t = build_pointer_type (t);
307
308       /* And now the function.  */
309       fn = build_lang_decl (FUNCTION_DECL, fn,
310                             build_function_type (t, void_list_node));
311       DECL_EXTERNAL (fn) = 1;
312       TREE_PUBLIC (fn) = 1;
313       DECL_ARTIFICIAL (fn) = 1;
314       pushdecl_top_level (fn);
315       make_function_rtl (fn);
316       assemble_external (fn);
317       pop_obstacks ();
318     }
319   return build_function_call (fn, NULL_TREE);
320 }
321
322 /* Retrieve a pointer to the cp_eh_info node for the current exception
323    and save it in the current binding level.  */
324
325 static void
326 push_eh_info ()
327 {
328   tree decl, fn = call_eh_info ();
329
330   /* Remember the pointer to the current exception info; it won't change
331      during this catch block.  */
332   decl = build_decl (VAR_DECL, get_identifier ("__exception_info"),
333                      TREE_TYPE (fn));
334   DECL_ARTIFICIAL (decl) = 1;
335   DECL_INITIAL (decl) = fn;
336   decl = pushdecl (decl);
337   cp_finish_decl (decl, fn, NULL_TREE, 0, 0);
338 }
339
340 /* Returns a reference to the cp_eh_info node for the current exception.  */
341
342 static tree
343 get_eh_info ()
344 {
345   /* Look for the pointer pushed in push_eh_info.  */
346   tree t = lookup_name (get_identifier ("__exception_info"), 0);
347   return build_indirect_ref (t, NULL_PTR);
348 }
349
350 /* Returns a reference to the current exception object.  */
351
352 static tree
353 get_eh_value ()
354 {
355   return build_component_ref (get_eh_info (), get_identifier ("value"),
356                               NULL_TREE, 0);
357 }
358
359 /* Returns a reference to the current exception type.  */
360
361 static tree
362 get_eh_type ()
363 {
364   return build_component_ref (get_eh_info (), get_identifier ("type"),
365                               NULL_TREE, 0);
366 }
367
368 /* Returns a reference to whether or not the current exception
369    has been caught.  */
370
371 static tree
372 get_eh_caught ()
373 {
374   return build_component_ref (get_eh_info (), get_identifier ("caught"),
375                               NULL_TREE, 0);
376 }
377
378 /* Returns a reference to whether or not the current exception
379    has been caught.  */
380
381 static tree
382 get_eh_handlers ()
383 {
384   return build_component_ref (get_eh_info (), get_identifier ("handlers"),
385                               NULL_TREE, 0);
386 }
387
388 /* Build a type value for use at runtime for a type that is matched
389    against by the exception handling system.  */
390
391 static tree
392 build_eh_type_type (type)
393      tree type;
394 {
395   char *typestring;
396   tree exp;
397
398   if (type == error_mark_node)
399     return error_mark_node;
400
401   /* peel back references, so they match.  */
402   if (TREE_CODE (type) == REFERENCE_TYPE)
403     type = TREE_TYPE (type);
404
405   /* Peel off cv qualifiers.  */
406   type = TYPE_MAIN_VARIANT (type);
407
408   if (flag_rtti)
409     {
410       return build1 (ADDR_EXPR, ptr_type_node, get_typeid (type));
411     }
412
413   typestring = build_overload_name (type, 1, 1);
414   exp = combine_strings (build_string (strlen (typestring)+1, typestring));
415   return build1 (ADDR_EXPR, ptr_type_node, exp);
416 }
417
418 /* Build the address of a runtime type for use in the runtime matching
419    field of the new exception model */
420
421 static tree
422 build_eh_type_type_ref (type)
423      tree type;
424 {
425   char *typestring;
426   tree exp;
427
428   if (type == error_mark_node)
429     return error_mark_node;
430
431   /* peel back references, so they match.  */
432   if (TREE_CODE (type) == REFERENCE_TYPE)
433     type = TREE_TYPE (type);
434
435   /* Peel off cv qualifiers.  */
436   type = TYPE_MAIN_VARIANT (type);
437
438   push_obstacks_nochange ();
439   end_temporary_allocation ();
440
441   if (flag_rtti)
442     {
443       exp = get_tinfo_fn (type);
444       TREE_USED (exp) = 1;
445       mark_inline_for_output (exp);
446       exp = build1 (ADDR_EXPR, ptr_type_node, exp);
447     }
448   else
449     {
450       typestring = build_overload_name (type, 1, 1);
451       exp = combine_strings (build_string (strlen (typestring)+1, typestring));
452       exp = build1 (ADDR_EXPR, ptr_type_node, exp);
453     }
454   pop_obstacks ();
455   return (exp);
456 }
457
458
459 /* Build a type value for use at runtime for a exp that is thrown or
460    matched against by the exception handling system.  */
461
462 static tree
463 build_eh_type (exp)
464      tree exp;
465 {
466   if (flag_rtti)
467     {
468       exp = build_typeid (exp);
469       return build1 (ADDR_EXPR, ptr_type_node, exp);
470     }
471   return build_eh_type_type (TREE_TYPE (exp));
472 }
473
474 /* This routine is called to mark all the symbols representing runtime
475    type functions in the exception table as haveing been referenced.
476    This will make sure code is emitted for them. Called from finish_file. */
477 void 
478 mark_all_runtime_matches () 
479 {
480   int x,num;
481   void **ptr;
482   tree exp;
483   
484   num = find_all_handler_type_matches (&ptr);
485   if (num == 0 || ptr == NULL)
486     return;
487   
488   for (x=0; x <num; x++)
489     {
490       exp = (tree) ptr[x];
491       if (TREE_CODE (exp) == ADDR_EXPR)
492         {
493           exp = TREE_OPERAND (exp, 0);
494           if (TREE_CODE (exp) == FUNCTION_DECL)
495             TREE_SYMBOL_REFERENCED (DECL_ASSEMBLER_NAME (exp)) = 1;
496         }
497     }
498   
499   free (ptr);
500 }
501
502 /* Build up a call to __cp_pop_exception, to destroy the exception object
503    for the current catch block.  HANDLER is either true or false, telling
504    the library whether or not it is being called from an exception handler;
505    if it is, it avoids destroying the object on rethrow.  */
506
507 static tree
508 do_pop_exception ()
509 {
510   tree fn, cleanup;
511   fn = get_identifier ("__cp_pop_exception");
512   if (IDENTIFIER_GLOBAL_VALUE (fn))
513     fn = IDENTIFIER_GLOBAL_VALUE (fn);
514   else
515     {
516       /* Declare void __cp_pop_exception (void *),
517          as defined in exception.cc. */
518       push_obstacks_nochange ();
519       end_temporary_allocation ();
520       fn = build_lang_decl
521         (FUNCTION_DECL, fn,
522          build_function_type (void_type_node, tree_cons
523                               (NULL_TREE, ptr_type_node, void_list_node)));
524       DECL_EXTERNAL (fn) = 1;
525       TREE_PUBLIC (fn) = 1;
526       DECL_ARTIFICIAL (fn) = 1;
527       pushdecl_top_level (fn);
528       make_function_rtl (fn);
529       assemble_external (fn);
530       pop_obstacks ();
531     }
532
533   /* Arrange to do a dynamically scoped cleanup upon exit from this region.  */
534   cleanup = lookup_name (get_identifier ("__exception_info"), 0);
535   cleanup = build_function_call (fn, expr_tree_cons
536                                  (NULL_TREE, cleanup, NULL_TREE));
537   return cleanup;
538 }
539
540 /* This routine creates the cleanup for the current exception.  */
541
542 static void
543 push_eh_cleanup ()
544 {
545   int yes;
546
547   expand_expr (build_unary_op (PREINCREMENT_EXPR, get_eh_handlers (), 1),
548                const0_rtx, VOIDmode, EXPAND_NORMAL);
549
550   yes = suspend_momentary ();
551   /* All cleanups must last longer than normal.  */
552   expand_decl_cleanup (NULL_TREE, do_pop_exception ());
553   resume_momentary (yes);
554 }
555
556 /* Build up a call to terminate on the function obstack, for use as an
557    exception handler.  */
558
559 tree
560 build_terminate_handler ()
561 {
562   int yes = suspend_momentary ();
563   tree term = build_function_call (Terminate, NULL_TREE);
564   resume_momentary (yes);
565   return term;
566 }
567
568 /* Call this to start a catch block. Typename is the typename, and identifier
569    is the variable to place the object in or NULL if the variable doesn't
570    matter.  If typename is NULL, that means its a "catch (...)" or catch
571    everything.  In that case we don't need to do any type checking.
572    (ie: it ends up as the "else" clause rather than an "else if" clause) */
573
574 void
575 expand_start_catch_block (declspecs, declarator)
576      tree declspecs, declarator;
577 {
578   tree decl;
579
580   if (processing_template_decl)
581     {
582       if (declspecs)
583         {
584           decl = grokdeclarator (declarator, declspecs, CATCHPARM,
585                                  1, NULL_TREE);
586           pushdecl (decl);
587           decl = build_min_nt (DECL_STMT, copy_to_permanent (declarator),
588                                copy_to_permanent (declspecs),
589                                NULL_TREE);
590           add_tree (decl);
591         }
592       return;
593     }
594
595   if (! doing_eh (1))
596     return;
597
598   if (flag_new_exceptions)
599     process_start_catch_block (declspecs, declarator);
600   else
601     process_start_catch_block_old (declspecs, declarator);
602 }
603
604
605 /* This function performs the expand_start_catch_block functionality for 
606    exceptions implemented in the old style, where catch blocks were all
607    called, and had to check the runtime information themselves. */
608
609 static void 
610 process_start_catch_block_old (declspecs, declarator)
611      tree declspecs, declarator;
612 {
613   rtx false_label_rtx;
614   tree decl = NULL_TREE;
615   tree init;
616
617   /* Create a binding level for the eh_info and the exception object
618      cleanup.  */
619   pushlevel (0);
620   expand_start_bindings (0);
621
622   false_label_rtx = gen_label_rtx ();
623   push_label_entry (&false_label_stack, false_label_rtx, NULL_TREE);
624
625   emit_line_note (input_filename, lineno);
626
627   push_eh_info ();
628
629   if (declspecs)
630     {
631       decl = grokdeclarator (declarator, declspecs, CATCHPARM, 1, NULL_TREE);
632
633       if (decl == NULL_TREE)
634         error ("invalid catch parameter");
635     }
636
637   if (decl)
638     {
639       tree exp;
640       rtx call_rtx, return_value_rtx;
641       tree init_type;
642
643       /* Make sure we mark the catch param as used, otherwise we'll get
644          a warning about an unused ((anonymous)).  */
645       TREE_USED (decl) = 1;
646
647       /* Figure out the type that the initializer is.  */
648       init_type = TREE_TYPE (decl);
649       if (TREE_CODE (init_type) != REFERENCE_TYPE
650           && TREE_CODE (init_type) != POINTER_TYPE)
651         init_type = build_reference_type (init_type);
652
653       exp = get_eh_value ();
654
655       /* Since pointers are passed by value, initialize a reference to
656          pointer catch parm with the address of the value slot.  */
657       if (TREE_CODE (init_type) == REFERENCE_TYPE
658           && TREE_CODE (TREE_TYPE (init_type)) == POINTER_TYPE)
659         exp = build_unary_op (ADDR_EXPR, exp, 1);
660
661       exp = expr_tree_cons (NULL_TREE,
662                        build_eh_type_type (TREE_TYPE (decl)),
663                        expr_tree_cons (NULL_TREE,
664                                   get_eh_type (),
665                                   expr_tree_cons (NULL_TREE, exp, NULL_TREE)));
666       exp = build_function_call (CatchMatch, exp);
667       call_rtx = expand_call (exp, NULL_RTX, 0);
668
669       return_value_rtx = hard_function_value (ptr_type_node, exp);
670
671       /* did the throw type match function return TRUE? */
672       emit_cmp_insn (return_value_rtx, const0_rtx, EQ, NULL_RTX,
673                     GET_MODE (return_value_rtx), 0, 0);
674
675       /* if it returned FALSE, jump over the catch block, else fall into it */
676       emit_jump_insn (gen_beq (false_label_rtx));
677
678       push_eh_cleanup ();
679
680       /* Create a binding level for the parm.  */
681       pushlevel (0);
682       expand_start_bindings (0);
683
684       init = convert_from_reference (make_tree (init_type, call_rtx));
685
686       /* If the constructor for the catch parm exits via an exception, we
687          must call terminate.  See eh23.C.  */
688       if (TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
689         {
690           /* Generate the copy constructor call directly so we can wrap it.
691              See also expand_default_init.  */
692           init = ocp_convert (TREE_TYPE (decl), init,
693                               CONV_IMPLICIT|CONV_FORCE_TEMP, 0);
694           init = build (TRY_CATCH_EXPR, TREE_TYPE (init), init,
695                         build_terminate_handler ());
696         }
697
698       /* Let `cp_finish_decl' know that this initializer is ok.  */
699       DECL_INITIAL (decl) = init;
700       decl = pushdecl (decl);
701
702       cp_finish_decl (decl, init, NULL_TREE, 0, LOOKUP_ONLYCONVERTING);
703     }
704   else
705     {
706       push_eh_cleanup ();
707
708       /* Create a binding level for the parm.  */
709       pushlevel (0);
710       expand_start_bindings (0);
711
712       /* Fall into the catch all section.  */
713     }
714
715   init = build_modify_expr (get_eh_caught (), NOP_EXPR, integer_one_node);
716   expand_expr (init, const0_rtx, VOIDmode, EXPAND_NORMAL);
717
718   emit_line_note (input_filename, lineno);
719 }
720
721 /* This function performs the expand_start_catch_block functionality for 
722    exceptions implemented in the new style. __throw determines whether
723    a handler needs to be called or not, so the handler itself has to do
724    nothing additionaal. */
725
726 static void 
727 process_start_catch_block (declspecs, declarator)
728      tree declspecs, declarator;
729 {
730   tree decl = NULL_TREE;
731   tree init;
732
733   /* Create a binding level for the eh_info and the exception object
734      cleanup.  */
735   pushlevel (0);
736   expand_start_bindings (0);
737
738
739   if (declspecs)
740     {
741       decl = grokdeclarator (declarator, declspecs, CATCHPARM, 1, NULL_TREE);
742
743       if (decl == NULL_TREE)
744         error ("invalid catch parameter");
745     }
746
747   if (decl)
748     start_catch_handler (build_eh_type_type_ref (TREE_TYPE (decl)));
749   else
750     start_catch_handler (CATCH_ALL_TYPE);
751
752   emit_line_note (input_filename, lineno);
753
754   push_eh_info ();
755
756   if (decl)
757     {
758       tree exp;
759       tree init_type;
760
761       /* Make sure we mark the catch param as used, otherwise we'll get
762          a warning about an unused ((anonymous)).  */
763       TREE_USED (decl) = 1;
764
765       /* Figure out the type that the initializer is.  */
766       init_type = TREE_TYPE (decl);
767       if (TREE_CODE (init_type) != REFERENCE_TYPE
768           && TREE_CODE (init_type) != POINTER_TYPE)
769         init_type = build_reference_type (init_type);
770
771       exp = get_eh_value ();
772
773       /* Since pointers are passed by value, initialize a reference to
774          pointer catch parm with the address of the value slot.  */
775       if (TREE_CODE (init_type) == REFERENCE_TYPE
776           && TREE_CODE (TREE_TYPE (init_type)) == POINTER_TYPE)
777         exp = build_unary_op (ADDR_EXPR, exp, 1);
778
779       exp = ocp_convert (init_type , exp, CONV_IMPLICIT|CONV_FORCE_TEMP, 0);
780
781       push_eh_cleanup ();
782
783       /* Create a binding level for the parm.  */
784       pushlevel (0);
785       expand_start_bindings (0);
786
787       init = convert_from_reference (exp);
788
789       /* If the constructor for the catch parm exits via an exception, we
790          must call terminate.  See eh23.C.  */
791       if (TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl)))
792         {
793           /* Generate the copy constructor call directly so we can wrap it.
794              See also expand_default_init.  */
795           init = ocp_convert (TREE_TYPE (decl), init,
796                               CONV_IMPLICIT|CONV_FORCE_TEMP, 0);
797           init = build (TRY_CATCH_EXPR, TREE_TYPE (init), init,
798                         build_terminate_handler ());
799         }
800
801       /* Let `cp_finish_decl' know that this initializer is ok.  */
802       DECL_INITIAL (decl) = init;
803       decl = pushdecl (decl);
804
805       cp_finish_decl (decl, init, NULL_TREE, 0, LOOKUP_ONLYCONVERTING);
806     }
807   else
808     {
809       push_eh_cleanup ();
810
811       /* Create a binding level for the parm.  */
812       pushlevel (0);
813       expand_start_bindings (0);
814
815       /* Fall into the catch all section.  */
816     }
817
818   init = build_modify_expr (get_eh_caught (), NOP_EXPR, integer_one_node);
819   expand_expr (init, const0_rtx, VOIDmode, EXPAND_NORMAL);
820
821   emit_line_note (input_filename, lineno);
822 }
823
824
825
826 /* Call this to end a catch block.  Its responsible for emitting the
827    code to handle jumping back to the correct place, and for emitting
828    the label to jump to if this catch block didn't match.  */
829
830 void
831 expand_end_catch_block ()
832 {
833   if (! doing_eh (1))
834     return;
835
836   /* Cleanup the EH parameter.  */
837   expand_end_bindings (getdecls (), kept_level_p (), 0);
838   poplevel (kept_level_p (), 1, 0);
839       
840   /* Cleanup the EH object.  */
841   expand_end_bindings (getdecls (), kept_level_p (), 0);
842   poplevel (kept_level_p (), 1, 0);
843
844   /* Fall to outside the try statement when done executing handler and
845      we fall off end of handler.  This is jump Lresume in the
846      documentation.  */
847   expand_goto (top_label_entry (&caught_return_label_stack));
848
849   /* label we emit to jump to if this catch block didn't match.  */
850   /* This the closing } in the `if (eq) {' of the documentation.  */
851   if (! flag_new_exceptions)
852     emit_label (pop_label_entry (&false_label_stack));
853 }
854
855 /* An exception spec is implemented more or less like:
856
857    try {
858      function body;
859    } catch (...) {
860      void *p[] = { typeid(raises) };
861      __check_eh_spec (p, count);
862    }
863
864    __check_eh_spec in exception.cc handles all the details.  */
865
866 void
867 expand_start_eh_spec ()
868 {
869   expand_start_try_stmts ();
870 }
871
872 static void
873 expand_end_eh_spec (raises)
874      tree raises;
875 {
876   tree tmp, fn, decl, types = NULL_TREE;
877   int count = 0;
878
879   expand_start_all_catch ();
880   expand_start_catch_block (NULL_TREE, NULL_TREE);
881
882   /* Build up an array of type_infos.  */
883   for (; raises && TREE_VALUE (raises); raises = TREE_CHAIN (raises))
884     {
885       types = expr_tree_cons
886         (NULL_TREE, build_eh_type_type (TREE_VALUE (raises)), types);
887       ++count;
888     }
889
890   types = build_nt (CONSTRUCTOR, NULL_TREE, types);
891   TREE_HAS_CONSTRUCTOR (types) = 1;
892
893   /* We can't pass the CONSTRUCTOR directly, so stick it in a variable.  */
894   tmp = build_array_type (const_ptr_type_node, NULL_TREE);
895   decl = build_decl (VAR_DECL, NULL_TREE, tmp);
896   DECL_ARTIFICIAL (decl) = 1;
897   DECL_INITIAL (decl) = types;
898   cp_finish_decl (decl, types, NULL_TREE, 0, 0);
899
900   decl = decay_conversion (decl);
901
902   fn = get_identifier ("__check_eh_spec");
903   if (IDENTIFIER_GLOBAL_VALUE (fn))
904     fn = IDENTIFIER_GLOBAL_VALUE (fn);
905   else
906     {
907       push_obstacks_nochange ();
908       end_temporary_allocation ();
909
910       tmp = tree_cons
911         (NULL_TREE, integer_type_node, tree_cons
912          (NULL_TREE, TREE_TYPE (decl), void_list_node));
913       tmp = build_function_type (void_type_node, tmp);
914   
915       fn = build_lang_decl (FUNCTION_DECL, fn, tmp);
916       DECL_EXTERNAL (fn) = 1;
917       TREE_PUBLIC (fn) = 1;
918       DECL_ARTIFICIAL (fn) = 1;
919       TREE_THIS_VOLATILE (fn) = 1;
920       pushdecl_top_level (fn);
921       make_function_rtl (fn);
922       assemble_external (fn);
923       pop_obstacks ();
924     }
925
926   tmp = expr_tree_cons (NULL_TREE, build_int_2 (count, 0), expr_tree_cons
927                         (NULL_TREE, decl, NULL_TREE));
928   tmp = build_call (fn, TREE_TYPE (TREE_TYPE (fn)), tmp);
929   expand_expr (tmp, const0_rtx, VOIDmode, EXPAND_NORMAL);
930
931   expand_end_catch_block ();
932   expand_end_all_catch ();
933 }
934
935 /* This is called to expand all the toplevel exception handling
936    finalization for a function.  It should only be called once per
937    function.  */
938
939 void
940 expand_exception_blocks ()
941 {
942   do_pending_stack_adjust ();
943   push_to_sequence (catch_clauses);
944   expand_leftover_cleanups ();
945   do_pending_stack_adjust ();
946   catch_clauses = get_insns ();
947   end_sequence ();
948
949   /* Do this after we expand leftover cleanups, so that the
950      expand_eh_region_end that expand_end_eh_spec does will match the
951      right expand_eh_region_start, and make sure it comes out before
952      the terminate protected region.  */
953   if (TYPE_RAISES_EXCEPTIONS (TREE_TYPE (current_function_decl)))
954     {
955      expand_end_eh_spec (TYPE_RAISES_EXCEPTIONS (TREE_TYPE (current_function_decl)));
956      do_pending_stack_adjust ();
957      push_to_sequence (catch_clauses);
958      expand_leftover_cleanups ();
959      do_pending_stack_adjust ();
960      catch_clauses = get_insns ();
961      end_sequence ();
962     }
963
964   if (catch_clauses)
965     {
966       rtx funcend = gen_label_rtx ();
967       emit_jump (funcend);
968
969       /* We cannot protect n regions this way if we must flow into the
970          EH region through the top of the region, as we have to with
971          the setjmp/longjmp approach.  */
972       if (exceptions_via_longjmp == 0)
973         expand_eh_region_start ();
974
975       emit_insns (catch_clauses);
976       catch_clauses = NULL_RTX;
977
978       if (exceptions_via_longjmp == 0)
979         expand_eh_region_end (build_terminate_handler ());
980
981       expand_leftover_cleanups ();
982
983       emit_label (funcend);
984     }
985 }
986
987 tree
988 start_anon_func ()
989 {
990   static int counter = 0;
991   int old_interface_unknown = interface_unknown;
992   char name[32];
993   tree params;
994   tree t;
995
996   push_cp_function_context (NULL_TREE);
997   push_to_top_level ();
998
999   /* No need to mangle this.  */
1000   push_lang_context (lang_name_c);
1001
1002   interface_unknown = 1;
1003
1004   params = void_list_node;
1005   /* tcf stands for throw clean function.  */
1006   sprintf (name, "__tcf_%d", counter++);
1007   t = make_call_declarator (get_identifier (name), params, NULL_TREE,
1008                             NULL_TREE);
1009   start_function (decl_tree_cons (NULL_TREE, get_identifier ("static"),
1010                                   void_list_node),
1011                   t, NULL_TREE, 0);
1012   store_parm_decls ();
1013   pushlevel (0);
1014   clear_last_expr ();
1015   push_momentary ();
1016   expand_start_bindings (0);
1017   emit_line_note (input_filename, lineno);
1018
1019   interface_unknown = old_interface_unknown;
1020
1021   pop_lang_context ();
1022
1023   return current_function_decl;
1024 }
1025
1026 void
1027 end_anon_func ()
1028 {
1029   expand_end_bindings (getdecls (), 1, 0);
1030   poplevel (1, 0, 0);
1031   pop_momentary ();
1032
1033   finish_function (lineno, 0, 0);
1034
1035   pop_from_top_level ();
1036   pop_cp_function_context (NULL_TREE);
1037 }
1038
1039 /* Return a pointer to a buffer for an exception object of type TYPE.  */
1040
1041 tree
1042 alloc_eh_object (type)
1043      tree type;
1044 {
1045   tree fn, exp;
1046
1047   fn = get_identifier ("__eh_alloc");
1048   if (IDENTIFIER_GLOBAL_VALUE (fn))
1049     fn = IDENTIFIER_GLOBAL_VALUE (fn);
1050   else
1051     {
1052       /* Declare __eh_alloc (size_t), as defined in exception.cc.  */
1053       tree tmp;
1054       push_obstacks_nochange ();
1055       end_temporary_allocation ();
1056       tmp = tree_cons (NULL_TREE, sizetype, void_list_node);
1057       fn = build_lang_decl (FUNCTION_DECL, fn,
1058                             build_function_type (ptr_type_node, tmp));
1059       DECL_EXTERNAL (fn) = 1;
1060       TREE_PUBLIC (fn) = 1;
1061       DECL_ARTIFICIAL (fn) = 1;
1062       pushdecl_top_level (fn);
1063       make_function_rtl (fn);
1064       assemble_external (fn);
1065       pop_obstacks ();
1066     }
1067
1068   exp = build_function_call (fn, expr_tree_cons
1069                              (NULL_TREE, size_in_bytes (type), NULL_TREE));
1070   exp = build1 (NOP_EXPR, build_pointer_type (type), exp);
1071   return exp;
1072 }
1073
1074 /* Expand a throw statement.  This follows the following
1075    algorithm:
1076
1077         1. Allocate space to save the current PC onto the stack.
1078         2. Generate and emit a label and save its address into the
1079                 newly allocated stack space since we can't save the pc directly.
1080         3. If this is the first call to throw in this function:
1081                 generate a label for the throw block
1082         4. jump to the throw block label.  */
1083
1084 void
1085 expand_throw (exp)
1086      tree exp;
1087 {
1088   tree fn;
1089   static tree cleanup_type;
1090
1091   if (! doing_eh (1))
1092     return;
1093
1094   if (exp)
1095     {
1096       tree throw_type;
1097       tree cleanup = NULL_TREE, e;
1098
1099       /* throw expression */
1100       /* First, decay it.  */
1101       exp = decay_conversion (exp);
1102
1103       /* cleanup_type is void (*)(void *, int),
1104          the internal type of a destructor. */
1105       if (cleanup_type == NULL_TREE)
1106         {
1107           push_obstacks_nochange ();
1108           end_temporary_allocation ();
1109           cleanup_type = build_pointer_type
1110             (build_function_type
1111              (void_type_node, tree_cons
1112               (NULL_TREE, ptr_type_node, tree_cons
1113                (NULL_TREE, integer_type_node, void_list_node))));
1114           pop_obstacks ();
1115         }
1116
1117       if (TREE_CODE (TREE_TYPE (exp)) == POINTER_TYPE)
1118         {
1119           throw_type = build_eh_type (exp);
1120           exp = build_reinterpret_cast (ptr_type_node, exp);
1121         }
1122       else
1123         {
1124           tree object, ptr;
1125
1126           /* OK, this is kind of wacky.  The WP says that we call
1127              terminate
1128
1129              when the exception handling mechanism, after completing
1130              evaluation of the expression to be thrown but before the
1131              exception is caught (_except.throw_), calls a user function
1132              that exits via an uncaught exception.
1133
1134              So we have to protect the actual initialization of the
1135              exception object with terminate(), but evaluate the expression
1136              first.  We also expand the call to __eh_alloc
1137              first.  Since there could be temps in the expression, we need
1138              to handle that, too.  */
1139
1140           expand_start_target_temps ();
1141
1142 #if 0
1143           /* Unfortunately, this doesn't work.  */
1144           preexpand_calls (exp);
1145 #else
1146           /* Store the throw expression into a temp.  This can be less
1147              efficient than storing it into the allocated space directly, but
1148              oh well.  To do this efficiently we would need to insinuate
1149              ourselves into expand_call.  */
1150           if (TREE_SIDE_EFFECTS (exp))
1151             {
1152               tree temp = build (VAR_DECL, TREE_TYPE (exp));
1153               DECL_ARTIFICIAL (temp) = 1;
1154               layout_decl (temp, 0);
1155               DECL_RTL (temp) = assign_temp (TREE_TYPE (exp), 2, 0, 1);
1156               expand_expr (build (INIT_EXPR, TREE_TYPE (exp), temp, exp),
1157                            NULL_RTX, VOIDmode, 0);
1158               expand_decl_cleanup (NULL_TREE, maybe_build_cleanup (temp));
1159               exp = temp;
1160             }
1161 #endif
1162
1163           /* Allocate the space for the exception.  */
1164           ptr = save_expr (alloc_eh_object (TREE_TYPE (exp)));
1165           expand_expr (ptr, const0_rtx, VOIDmode, 0);
1166
1167           expand_eh_region_start ();
1168
1169           object = build_indirect_ref (ptr, NULL_PTR);
1170           exp = build_modify_expr (object, INIT_EXPR, exp);
1171
1172           if (exp == error_mark_node)
1173             error ("  in thrown expression");
1174
1175           expand_expr (exp, const0_rtx, VOIDmode, 0);
1176           expand_eh_region_end (build_terminate_handler ());
1177           expand_end_target_temps ();
1178
1179           throw_type = build_eh_type (object);
1180
1181           if (TYPE_HAS_DESTRUCTOR (TREE_TYPE (object)))
1182             {
1183               cleanup = lookup_fnfields (TYPE_BINFO (TREE_TYPE (object)),
1184                                          dtor_identifier, 0);
1185               cleanup = TREE_VALUE (cleanup);
1186               mark_used (cleanup);
1187               mark_addressable (cleanup);
1188               /* Pretend it's a normal function.  */
1189               cleanup = build1 (ADDR_EXPR, cleanup_type, cleanup);
1190             }
1191
1192           exp = ptr;
1193         }
1194
1195       if (cleanup == NULL_TREE)
1196         {
1197           cleanup = build_int_2 (0, 0);
1198           TREE_TYPE (cleanup) = cleanup_type;
1199         }
1200
1201       fn = get_identifier ("__cp_push_exception");
1202       if (IDENTIFIER_GLOBAL_VALUE (fn))
1203         fn = IDENTIFIER_GLOBAL_VALUE (fn);
1204       else
1205         {
1206           /* Declare __cp_push_exception (void*, void*, void (*)(void*, int)),
1207              as defined in exception.cc.  */
1208           tree tmp;
1209           push_obstacks_nochange ();
1210           end_temporary_allocation ();
1211           tmp = tree_cons
1212             (NULL_TREE, ptr_type_node, tree_cons
1213              (NULL_TREE, ptr_type_node, tree_cons
1214               (NULL_TREE, cleanup_type, void_list_node)));
1215           fn = build_lang_decl (FUNCTION_DECL, fn,
1216                                 build_function_type (void_type_node, tmp));
1217           DECL_EXTERNAL (fn) = 1;
1218           TREE_PUBLIC (fn) = 1;
1219           DECL_ARTIFICIAL (fn) = 1;
1220           pushdecl_top_level (fn);
1221           make_function_rtl (fn);
1222           assemble_external (fn);
1223           pop_obstacks ();
1224         }
1225
1226       e = expr_tree_cons (NULL_TREE, exp, expr_tree_cons
1227                           (NULL_TREE, throw_type, expr_tree_cons
1228                            (NULL_TREE, cleanup, NULL_TREE)));
1229       e = build_function_call (fn, e);
1230       expand_expr (e, const0_rtx, VOIDmode, 0);
1231     }
1232   else
1233     {
1234       /* rethrow current exception; note that it's no longer caught.  */
1235
1236       tree fn = get_identifier ("__uncatch_exception");
1237       if (IDENTIFIER_GLOBAL_VALUE (fn))
1238         fn = IDENTIFIER_GLOBAL_VALUE (fn);
1239       else
1240         {
1241           /* Declare void __uncatch_exception (void)
1242              as defined in exception.cc. */
1243           push_obstacks_nochange ();
1244           end_temporary_allocation ();
1245           fn = build_lang_decl (FUNCTION_DECL, fn,
1246                                 build_function_type (void_type_node,
1247                                                      void_list_node));
1248           DECL_EXTERNAL (fn) = 1;
1249           TREE_PUBLIC (fn) = 1;
1250           DECL_ARTIFICIAL (fn) = 1;
1251           pushdecl_top_level (fn);
1252           make_function_rtl (fn);
1253           assemble_external (fn);
1254           pop_obstacks ();
1255         }
1256
1257       exp = build_function_call (fn, NULL_TREE);
1258       expand_expr (exp, const0_rtx, VOIDmode, EXPAND_NORMAL);
1259     }
1260
1261   expand_internal_throw ();
1262 }
1263
1264 /* Build a throw expression.  */
1265
1266 tree
1267 build_throw (e)
1268      tree e;
1269 {
1270   if (e == error_mark_node)
1271     return e;
1272
1273   if (processing_template_decl)
1274     return build_min (THROW_EXPR, void_type_node, e);
1275
1276   if (! flag_ansi && e == null_node)
1277     {
1278       cp_warning ("throwing NULL");
1279       e = integer_zero_node;
1280     }
1281
1282   e = build1 (THROW_EXPR, void_type_node, e);
1283   TREE_SIDE_EFFECTS (e) = 1;
1284   TREE_USED (e) = 1;
1285
1286   return e;
1287 }