OSDN Git Service

* except.c (expand_throw): Use cp_finish_decl for the throw temp.
[pf3gnuchains/gcc-fork.git] / gcc / cp / cvt.c
1 /* Language-level data type conversion for GNU C++.
2    Copyright (C) 1987, 88, 92-97, 1998 Free Software Foundation, Inc.
3    Hacked by Michael Tiemann (tiemann@cygnus.com)
4
5 This file is part of GNU CC.
6
7 GNU CC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
11
12 GNU CC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with GNU CC; see the file COPYING.  If not, write to
19 the Free Software Foundation, 59 Temple Place - Suite 330,
20 Boston, MA 02111-1307, USA.  */
21
22
23 /* This file contains the functions for converting C expressions
24    to different data types.  The only entry point is `convert'.
25    Every language front end must have a `convert' function
26    but what kind of conversions it does will depend on the language.  */
27
28 #include "config.h"
29 #include "system.h"
30 #include "tree.h"
31 #include "flags.h"
32 #include "cp-tree.h"
33 #include "convert.h"
34
35 extern tree static_aggregates;
36
37 static tree cp_convert_to_pointer PROTO((tree, tree));
38 static tree convert_to_pointer_force PROTO((tree, tree));
39 static tree build_up_reference PROTO((tree, tree, int));
40
41 /* Change of width--truncation and extension of integers or reals--
42    is represented with NOP_EXPR.  Proper functioning of many things
43    assumes that no other conversions can be NOP_EXPRs.
44
45    Conversion between integer and pointer is represented with CONVERT_EXPR.
46    Converting integer to real uses FLOAT_EXPR
47    and real to integer uses FIX_TRUNC_EXPR.
48
49    Here is a list of all the functions that assume that widening and
50    narrowing is always done with a NOP_EXPR:
51      In convert.c, convert_to_integer.
52      In c-typeck.c, build_binary_op_nodefault (boolean ops),
53         and truthvalue_conversion.
54      In expr.c: expand_expr, for operands of a MULT_EXPR.
55      In fold-const.c: fold.
56      In tree.c: get_narrower and get_unwidened.
57
58    C++: in multiple-inheritance, converting between pointers may involve
59    adjusting them by a delta stored within the class definition.  */
60 \f
61 /* Subroutines of `convert'.  */
62
63 /* if converting pointer to pointer
64      if dealing with classes, check for derived->base or vice versa
65      else if dealing with method pointers, delegate
66      else convert blindly
67    else if converting class, pass off to build_type_conversion
68    else try C-style pointer conversion  */
69
70 static tree
71 cp_convert_to_pointer (type, expr)
72      tree type, expr;
73 {
74   register tree intype = TREE_TYPE (expr);
75   register enum tree_code form;
76   tree rval;
77
78   if (IS_AGGR_TYPE (intype))
79     {
80       intype = complete_type (intype);
81       if (TYPE_SIZE (intype) == NULL_TREE)
82         {
83           cp_error ("can't convert from incomplete type `%T' to `%T'",
84                     intype, type);
85           return error_mark_node;
86         }
87
88       rval = build_type_conversion (CONVERT_EXPR, type, expr, 1);
89       if (rval)
90         {
91           if (rval == error_mark_node)
92             cp_error ("conversion of `%E' from `%T' to `%T' is ambiguous",
93                       expr, intype, type);
94           return rval;
95         }
96     }
97
98   if (TYPE_PTRMEMFUNC_P (type))
99     type = TYPE_PTRMEMFUNC_FN_TYPE (type);
100
101   /* Handle anachronistic conversions from (::*)() to cv void* or (*)().  */
102   if (TREE_CODE (type) == POINTER_TYPE
103       && (TREE_CODE (TREE_TYPE (type)) == FUNCTION_TYPE
104           || TYPE_MAIN_VARIANT (TREE_TYPE (type)) == void_type_node))
105     {
106       /* Allow an implicit this pointer for pointer to member
107          functions.  */
108       if (TYPE_PTRMEMFUNC_P (intype))
109         {
110           tree fntype = TREE_TYPE (TYPE_PTRMEMFUNC_FN_TYPE (intype));
111           tree decl = maybe_dummy_object (TYPE_METHOD_BASETYPE (fntype), 0);
112           expr = build (OFFSET_REF, fntype, decl, expr);
113         }
114
115       if (TREE_CODE (expr) == OFFSET_REF
116           && TREE_CODE (TREE_TYPE (expr)) == METHOD_TYPE)
117         expr = resolve_offset_ref (expr);
118       if (TREE_CODE (TREE_TYPE (expr)) == METHOD_TYPE)
119         expr = build_addr_func (expr);
120       if (TREE_CODE (TREE_TYPE (expr)) == POINTER_TYPE)
121         {
122           if (TREE_CODE (TREE_TYPE (TREE_TYPE (expr))) == METHOD_TYPE)
123             if (pedantic || warn_pmf2ptr)
124               cp_pedwarn ("converting from `%T' to `%T'", TREE_TYPE (expr),
125                           type);
126           return build1 (NOP_EXPR, type, expr);
127         }
128       intype = TREE_TYPE (expr);
129     }
130
131   if (TYPE_PTRMEMFUNC_P (intype))
132     intype = TYPE_PTRMEMFUNC_FN_TYPE (intype);
133
134   form = TREE_CODE (intype);
135
136   if (form == POINTER_TYPE || form == REFERENCE_TYPE)
137     {
138       intype = TYPE_MAIN_VARIANT (intype);
139
140       if (TYPE_MAIN_VARIANT (type) != intype
141           && TREE_CODE (TREE_TYPE (type)) == RECORD_TYPE
142           && IS_AGGR_TYPE (TREE_TYPE (type))
143           && IS_AGGR_TYPE (TREE_TYPE (intype))
144           && TREE_CODE (TREE_TYPE (intype)) == RECORD_TYPE
145           /* If EXPR is NULL, then we don't need to do any arithmetic
146              to convert it:
147
148                [conv.ptr]
149
150                The null pointer value is converted to the null pointer
151                value of the destination type.  */
152           && !integer_zerop (expr))
153         {
154           enum tree_code code = PLUS_EXPR;
155           tree binfo = get_binfo (TREE_TYPE (type), TREE_TYPE (intype), 1);
156           if (binfo == error_mark_node)
157             return error_mark_node;
158           if (binfo == NULL_TREE)
159             {
160               binfo = get_binfo (TREE_TYPE (intype), TREE_TYPE (type), 1);
161               if (binfo == error_mark_node)
162                 return error_mark_node;
163               code = MINUS_EXPR;
164             }
165           if (binfo)
166             {
167               if (TYPE_USES_VIRTUAL_BASECLASSES (TREE_TYPE (type))
168                   || TYPE_USES_VIRTUAL_BASECLASSES (TREE_TYPE (intype))
169                   || ! BINFO_OFFSET_ZEROP (binfo))
170                 {
171                   /* Need to get the path we took.  */
172                   tree path;
173
174                   if (code == PLUS_EXPR)
175                     get_base_distance (TREE_TYPE (type), TREE_TYPE (intype),
176                                        0, &path);
177                   else
178                     get_base_distance (TREE_TYPE (intype), TREE_TYPE (type),
179                                        0, &path);
180                   return build_vbase_path (code, type, expr, path, 0);
181                 }
182             }
183         }
184       if (TREE_CODE (TREE_TYPE (intype)) == METHOD_TYPE
185           && TREE_CODE (type) == POINTER_TYPE
186           && TREE_CODE (TREE_TYPE (type)) == METHOD_TYPE)
187         return build_ptrmemfunc (type, expr, 1);
188
189       if (TREE_CODE (TREE_TYPE (type)) == OFFSET_TYPE
190           && TREE_CODE (TREE_TYPE (intype)) == OFFSET_TYPE)
191         {
192           tree b1 = TYPE_OFFSET_BASETYPE (TREE_TYPE (type));
193           tree b2 = TYPE_OFFSET_BASETYPE (TREE_TYPE (intype));
194           tree binfo = get_binfo (b2, b1, 1);
195           enum tree_code code = PLUS_EXPR;
196
197           if (binfo == NULL_TREE)
198             {
199               binfo = get_binfo (b1, b2, 1);
200               code = MINUS_EXPR;
201             }
202
203           if (binfo == error_mark_node)
204             return error_mark_node;
205           if (binfo && ! TREE_VIA_VIRTUAL (binfo))
206             expr = size_binop (code, expr, BINFO_OFFSET (binfo));
207         }
208
209       if (TREE_CODE (TREE_TYPE (intype)) == METHOD_TYPE
210           || (TREE_CODE (type) == POINTER_TYPE
211               && TREE_CODE (TREE_TYPE (type)) == METHOD_TYPE))
212         {
213           cp_error ("cannot convert `%E' from type `%T' to type `%T'",
214                     expr, intype, type);
215           return error_mark_node;
216         }
217
218       rval = build1 (NOP_EXPR, type, expr);
219       TREE_CONSTANT (rval) = TREE_CONSTANT (expr);
220       return rval;
221     }
222
223   my_friendly_assert (form != OFFSET_TYPE, 186);
224
225   if (TYPE_LANG_SPECIFIC (intype)
226       && (IS_SIGNATURE_POINTER (intype) || IS_SIGNATURE_REFERENCE (intype)))
227     return convert_to_pointer (type, build_optr_ref (expr));
228
229   if (integer_zerop (expr))
230     {
231       if (TREE_CODE (TREE_TYPE (type)) == METHOD_TYPE)
232         return build_ptrmemfunc (type, expr, 0);
233       expr = build_int_2 (0, 0);
234       TREE_TYPE (expr) = type;
235       return expr;
236     }
237
238   if (INTEGRAL_CODE_P (form))
239     {
240       if (TYPE_PRECISION (intype) == POINTER_SIZE)
241         return build1 (CONVERT_EXPR, type, expr);
242       expr = cp_convert (type_for_size (POINTER_SIZE, 0), expr);
243       /* Modes may be different but sizes should be the same.  */
244       if (GET_MODE_SIZE (TYPE_MODE (TREE_TYPE (expr)))
245           != GET_MODE_SIZE (TYPE_MODE (type)))
246         /* There is supposed to be some integral type
247            that is the same width as a pointer.  */
248         abort ();
249       return convert_to_pointer (type, expr);
250     }
251
252   if (type_unknown_p (expr))
253     return instantiate_type (type, expr, 1);
254
255   cp_error ("cannot convert `%E' from type `%T' to type `%T'",
256             expr, intype, type);
257   return error_mark_node;
258 }
259
260 /* Like convert, except permit conversions to take place which
261    are not normally allowed due to access restrictions
262    (such as conversion from sub-type to private super-type).  */
263
264 static tree
265 convert_to_pointer_force (type, expr)
266      tree type, expr;
267 {
268   register tree intype = TREE_TYPE (expr);
269   register enum tree_code form = TREE_CODE (intype);
270   
271   if (integer_zerop (expr))
272     {
273       expr = build_int_2 (0, 0);
274       TREE_TYPE (expr) = type;
275       return expr;
276     }
277
278   /* Convert signature pointer/reference to `void *' first.  */
279   if (form == RECORD_TYPE
280       && (IS_SIGNATURE_POINTER (intype) || IS_SIGNATURE_REFERENCE (intype)))
281     {
282       expr = build_optr_ref (expr);
283       intype = TREE_TYPE (expr);
284       form = TREE_CODE (intype);
285     }
286
287   if (form == POINTER_TYPE)
288     {
289       intype = TYPE_MAIN_VARIANT (intype);
290
291       if (TYPE_MAIN_VARIANT (type) != intype
292           && TREE_CODE (TREE_TYPE (type)) == RECORD_TYPE
293           && IS_AGGR_TYPE (TREE_TYPE (type))
294           && IS_AGGR_TYPE (TREE_TYPE (intype))
295           && TREE_CODE (TREE_TYPE (intype)) == RECORD_TYPE)
296         {
297           enum tree_code code = PLUS_EXPR;
298           tree path;
299           int distance = get_base_distance (TREE_TYPE (type),
300                                             TREE_TYPE (intype), 0, &path);
301           if (distance == -2)
302             {
303             ambig:
304               cp_error ("type `%T' is ambiguous baseclass of `%s'",
305                         TREE_TYPE (type),
306                         TYPE_NAME_STRING (TREE_TYPE (intype)));
307               return error_mark_node;
308             }
309           if (distance == -1)
310             {
311               distance = get_base_distance (TREE_TYPE (intype),
312                                             TREE_TYPE (type), 0, &path);
313               if (distance == -2)
314                 goto ambig;
315               if (distance < 0)
316                 /* Doesn't need any special help from us.  */
317                 return build1 (NOP_EXPR, type, expr);
318
319               code = MINUS_EXPR;
320             }
321           return build_vbase_path (code, type, expr, path, 0);
322         }
323     }
324
325   return cp_convert_to_pointer (type, expr);
326 }
327
328 /* We are passing something to a function which requires a reference.
329    The type we are interested in is in TYPE. The initial
330    value we have to begin with is in ARG.
331
332    FLAGS controls how we manage access checking.
333    DIRECT_BIND in FLAGS controls how any temporaries are generated.  */
334
335 static tree
336 build_up_reference (type, arg, flags)
337      tree type, arg;
338      int flags;
339 {
340   tree rval;
341   tree argtype = TREE_TYPE (arg);
342   tree target_type = TREE_TYPE (type);
343
344   my_friendly_assert (TREE_CODE (type) == REFERENCE_TYPE, 187);
345
346   if ((flags & DIRECT_BIND) && ! real_lvalue_p (arg))
347     {
348       tree targ = arg;
349       if (toplevel_bindings_p ())
350         arg = get_temp_name (argtype, 1);
351       else
352         {
353           arg = pushdecl (build_decl (VAR_DECL, NULL_TREE, argtype));
354           DECL_ARTIFICIAL (arg) = 1;
355         }
356       DECL_INITIAL (arg) = targ;
357       cp_finish_decl (arg, targ, NULL_TREE, 0,
358                       LOOKUP_ONLYCONVERTING|DIRECT_BIND);
359     }
360   else if (!(flags & DIRECT_BIND) && ! lvalue_p (arg))
361     {
362       tree slot = build_decl (VAR_DECL, NULL_TREE, argtype);
363       DECL_ARTIFICIAL (slot) = 1;
364       arg = build (TARGET_EXPR, argtype, slot, arg, NULL_TREE, NULL_TREE);
365       TREE_SIDE_EFFECTS (arg) = 1;
366     }
367
368   /* If we had a way to wrap this up, and say, if we ever needed it's
369      address, transform all occurrences of the register, into a memory
370      reference we could win better.  */
371   rval = build_unary_op (ADDR_EXPR, arg, 1);
372   if (rval == error_mark_node)
373     return error_mark_node;
374
375   if ((flags & LOOKUP_PROTECT)
376       && TYPE_MAIN_VARIANT (argtype) != TYPE_MAIN_VARIANT (target_type)
377       && IS_AGGR_TYPE (argtype)
378       && IS_AGGR_TYPE (target_type))
379     {
380       /* We go through get_binfo for the access control.  */
381       tree binfo = get_binfo (target_type, argtype, 1);
382       if (binfo == error_mark_node)
383         return error_mark_node;
384       if (binfo == NULL_TREE)
385         return error_not_base_type (target_type, argtype);
386       rval = convert_pointer_to_real (binfo, rval);
387     }
388   else
389     rval
390       = convert_to_pointer_force (build_pointer_type (target_type), rval);
391   rval = build1 (NOP_EXPR, type, rval);
392   TREE_CONSTANT (rval) = TREE_CONSTANT (TREE_OPERAND (rval, 0));
393   return rval;
394 }
395
396 /* For C++: Only need to do one-level references, but cannot
397    get tripped up on signed/unsigned differences.
398
399    DECL is either NULL_TREE or the _DECL node for a reference that is being
400    initialized.  It can be error_mark_node if we don't know the _DECL but
401    we know it's an initialization.  */
402
403 tree
404 convert_to_reference (reftype, expr, convtype, flags, decl)
405      tree reftype, expr;
406      int convtype, flags;
407      tree decl;
408 {
409   register tree type = TYPE_MAIN_VARIANT (TREE_TYPE (reftype));
410   register tree intype = TREE_TYPE (expr);
411   tree rval = NULL_TREE;
412   tree rval_as_conversion = NULL_TREE;
413   int i;
414
415   if (TREE_CODE (type) == FUNCTION_TYPE && intype == unknown_type_node)
416     {
417       expr = instantiate_type (type, expr, 0);
418       intype = TREE_TYPE (expr);
419     }
420
421   if (TREE_CODE (intype) == REFERENCE_TYPE)
422     my_friendly_abort (364);
423
424   intype = TYPE_MAIN_VARIANT (intype);
425
426   i = comp_target_types (type, intype, 0);
427
428   if (i <= 0 && (convtype & CONV_IMPLICIT) && IS_AGGR_TYPE (intype)
429       && ! (flags & LOOKUP_NO_CONVERSION))
430     {
431       /* Look for a user-defined conversion to lvalue that we can use.  */
432
433       rval_as_conversion
434         = build_type_conversion (CONVERT_EXPR, reftype, expr, 1);
435
436       if (rval_as_conversion && rval_as_conversion != error_mark_node
437           && real_lvalue_p (rval_as_conversion))
438         {
439           expr = rval_as_conversion;
440           rval_as_conversion = NULL_TREE;
441           intype = type;
442           i = 1;
443         }
444     }
445
446   if (((convtype & CONV_STATIC) && i == -1)
447       || ((convtype & CONV_IMPLICIT) && i == 1))
448     {
449       if (flags & LOOKUP_COMPLAIN)
450         {
451           tree ttl = TREE_TYPE (reftype);
452           tree ttr = lvalue_type (expr);
453
454           /* [dcl.init.ref] says that if an rvalue is used to
455              initialize a reference, then the reference must be to a
456              non-volatile const type.  */
457           if (! real_lvalue_p (expr)
458               && !CP_TYPE_CONST_NON_VOLATILE_P (ttl))
459             {
460               char* msg;
461
462               if (CP_TYPE_VOLATILE_P (ttl) && decl)
463                 msg = "initialization of volatile reference type `%#T'";
464               else if (CP_TYPE_VOLATILE_P (ttl))
465                 msg = "conversion to volatile reference type `%#T'";
466               else if (decl)
467                 msg = "initialization of non-const reference type `%#T'";
468               else
469                 msg = "conversion to non-const reference type `%#T'";
470
471               cp_error (msg, reftype);
472               cp_error ("from rvalue of type `%T'", intype);
473             }
474           else if (! (convtype & CONV_CONST)
475                    && !at_least_as_qualified_p (ttl, ttr))
476             cp_error ("conversion from `%T' to `%T' discards qualifiers",
477                       ttr, reftype);
478         }
479
480       return build_up_reference (reftype, expr, flags);
481     }
482   else if ((convtype & CONV_REINTERPRET) && lvalue_p (expr))
483     {
484       /* When casting an lvalue to a reference type, just convert into
485          a pointer to the new type and deference it.  This is allowed
486          by San Diego WP section 5.2.9 paragraph 12, though perhaps it
487          should be done directly (jason).  (int &)ri ---> *(int*)&ri */
488
489       /* B* bp; A& ar = (A&)bp; is valid, but it's probably not what they
490          meant.  */
491       if (TREE_CODE (intype) == POINTER_TYPE
492           && (comptypes (TREE_TYPE (intype), type, 
493                          COMPARE_BASE | COMPARE_RELAXED )))
494         cp_warning ("casting `%T' to `%T' does not dereference pointer",
495                     intype, reftype);
496           
497       rval = build_unary_op (ADDR_EXPR, expr, 0);
498       if (rval != error_mark_node)
499         rval = convert_force (build_pointer_type (TREE_TYPE (reftype)),
500                               rval, 0);
501       if (rval != error_mark_node)
502         rval = build1 (NOP_EXPR, reftype, rval);
503     }
504   else
505     {
506       rval = convert_for_initialization (NULL_TREE, type, expr, flags,
507                                          "converting", 0, 0);
508       if (rval == error_mark_node)
509         return error_mark_node;
510       rval = build_up_reference (reftype, rval, flags);
511
512       if (rval && ! CP_TYPE_CONST_P (TREE_TYPE (reftype)))
513         cp_pedwarn ("initializing non-const `%T' with `%T' will use a temporary",
514                     reftype, intype);
515     }
516
517   if (rval)
518     {
519       /* If we found a way to convert earlier, then use it.  */
520       return rval;
521     }
522
523   my_friendly_assert (TREE_CODE (intype) != OFFSET_TYPE, 189);
524
525   if (flags & LOOKUP_COMPLAIN)
526     cp_error ("cannot convert type `%T' to type `%T'", intype, reftype);
527
528   if (flags & LOOKUP_SPECULATIVELY)
529     return NULL_TREE;
530
531   return error_mark_node;
532 }
533
534 /* We are using a reference VAL for its value. Bash that reference all the
535    way down to its lowest form.  */
536
537 tree
538 convert_from_reference (val)
539      tree val;
540 {
541   tree type = TREE_TYPE (val);
542
543   if (TREE_CODE (type) == OFFSET_TYPE)
544     type = TREE_TYPE (type);
545   if (TREE_CODE (type) == REFERENCE_TYPE)
546     return build_indirect_ref (val, NULL_PTR);
547   return val;
548 }
549 \f
550 /* Call this when we know (for any reason) that expr is not, in fact,
551    zero.  This routine is like convert_pointer_to, but it pays
552    attention to which specific instance of what type we want to
553    convert to.  This routine should eventually become
554    convert_to_pointer after all references to convert_to_pointer
555    are removed.  */
556
557 tree
558 convert_pointer_to_real (binfo, expr)
559      tree binfo, expr;
560 {
561   register tree intype = TREE_TYPE (expr);
562   tree ptr_type;
563   tree type, rval;
564
565   if (intype == error_mark_node)
566     return error_mark_node;
567
568   if (TREE_CODE (binfo) == TREE_VEC)
569     type = BINFO_TYPE (binfo);
570   else if (IS_AGGR_TYPE (binfo))
571     {
572       type = binfo;
573     }
574   else
575     {
576       type = binfo;
577       binfo = NULL_TREE;
578     }
579
580   ptr_type = cp_build_qualified_type (type,
581                                       CP_TYPE_QUALS (TREE_TYPE (intype)));
582   ptr_type = build_pointer_type (ptr_type);
583   if (ptr_type == TYPE_MAIN_VARIANT (intype))
584     return expr;
585
586   my_friendly_assert (!integer_zerop (expr), 191);
587
588   intype = TYPE_MAIN_VARIANT (TREE_TYPE (intype));
589   if (TREE_CODE (type) == RECORD_TYPE
590       && TREE_CODE (intype) == RECORD_TYPE
591       && type != intype)
592     {
593       tree path;
594       int distance
595         = get_base_distance (binfo, intype, 0, &path);
596
597       /* This function shouldn't be called with unqualified arguments
598          but if it is, give them an error message that they can read.  */
599       if (distance < 0)
600         {
601           cp_error ("cannot convert a pointer of type `%T' to a pointer of type `%T'",
602                     intype, type);
603
604           if (distance == -2)
605             cp_error ("because `%T' is an ambiguous base class", type);
606           return error_mark_node;
607         }
608
609       return build_vbase_path (PLUS_EXPR, ptr_type, expr, path, 1);
610     }
611   rval = build1 (NOP_EXPR, ptr_type,
612                  TREE_CODE (expr) == NOP_EXPR ? TREE_OPERAND (expr, 0) : expr);
613   TREE_CONSTANT (rval) = TREE_CONSTANT (expr);
614   return rval;
615 }
616
617 /* Call this when we know (for any reason) that expr is
618    not, in fact, zero.  This routine gets a type out of the first
619    argument and uses it to search for the type to convert to.  If there
620    is more than one instance of that type in the expr, the conversion is
621    ambiguous.  This routine should eventually go away, and all
622    callers should use convert_to_pointer_real.  */
623
624 tree
625 convert_pointer_to (binfo, expr)
626      tree binfo, expr;
627 {
628   tree type;
629
630   if (TREE_CODE (binfo) == TREE_VEC)
631     type = BINFO_TYPE (binfo);
632   else if (IS_AGGR_TYPE (binfo))
633       type = binfo;
634   else
635       type = binfo;
636   return convert_pointer_to_real (type, expr);
637 }
638 \f
639 /* C++ conversions, preference to static cast conversions.  */
640
641 tree
642 cp_convert (type, expr)
643      tree type, expr;
644 {
645   return ocp_convert (type, expr, CONV_OLD_CONVERT, LOOKUP_NORMAL);
646 }
647
648 /* Conversion...
649
650    FLAGS indicates how we should behave.  */
651
652 tree
653 ocp_convert (type, expr, convtype, flags)
654      tree type, expr;
655      int convtype, flags;
656 {
657   register tree e = expr;
658   register enum tree_code code = TREE_CODE (type);
659
660   if (e == error_mark_node
661       || TREE_TYPE (e) == error_mark_node)
662     return error_mark_node;
663
664   if (TREE_READONLY_DECL_P (e))
665     e = decl_constant_value (e);
666
667   if (IS_AGGR_TYPE (type) && (convtype & CONV_FORCE_TEMP)
668       /* Some internal structures (vtable_entry_type, sigtbl_ptr_type)
669          don't go through finish_struct, so they don't have the synthesized
670          constructors.  So don't force a temporary.  */
671       && TYPE_HAS_CONSTRUCTOR (type))
672     /* We need a new temporary; don't take this shortcut.  */;
673   else if (TYPE_MAIN_VARIANT (type) == TYPE_MAIN_VARIANT (TREE_TYPE (e)))
674     {
675       if (same_type_p (type, TREE_TYPE (e)))
676         /* The call to fold will not always remove the NOP_EXPR as
677            might be expected, since if one of the types is a typedef;
678            the comparsion in fold is just equality of pointers, not a
679            call to comptypes.  We don't call fold in this case because
680            that can result in infinite recursion; fold will call
681            convert, which will call ocp_convert, etc.  */
682         return e;
683       else
684         return fold (build1 (NOP_EXPR, type, e));
685     }
686
687   if (code == VOID_TYPE && (convtype & CONV_STATIC))
688     {
689       if (type_unknown_p (e))
690         error ("address of overloaded function with no contextual type information");
691
692       return build1 (CONVERT_EXPR, type, e);
693     }
694
695 #if 0
696   /* This is incorrect.  A truncation can't be stripped this way.
697      Extensions will be stripped by the use of get_unwidened.  */
698   if (TREE_CODE (e) == NOP_EXPR)
699     return cp_convert (type, TREE_OPERAND (e, 0));
700 #endif
701
702   /* Just convert to the type of the member.  */
703   if (code == OFFSET_TYPE)
704     {
705       type = TREE_TYPE (type);
706       code = TREE_CODE (type);
707     }
708
709 #if 0
710   if (code == REFERENCE_TYPE)
711     return fold (convert_to_reference (type, e, convtype, flags, NULL_TREE));
712   else if (TREE_CODE (TREE_TYPE (e)) == REFERENCE_TYPE)
713     e = convert_from_reference (e);
714 #endif
715
716   if (TREE_CODE (e) == OFFSET_REF)
717     e = resolve_offset_ref (e);
718
719   if (INTEGRAL_CODE_P (code))
720     {
721       tree intype = TREE_TYPE (e);
722       /* enum = enum, enum = int, enum = float, (enum)pointer are all
723          errors.  */
724       if (TREE_CODE (type) == ENUMERAL_TYPE
725           && ((ARITHMETIC_TYPE_P (intype) && ! (convtype & CONV_STATIC))
726               || (TREE_CODE (intype) == POINTER_TYPE)))
727         {
728           cp_pedwarn ("conversion from `%#T' to `%#T'", intype, type);
729
730           if (flag_pedantic_errors)
731             return error_mark_node;
732         }
733       if (IS_AGGR_TYPE (intype))
734         {
735           tree rval;
736           rval = build_type_conversion (CONVERT_EXPR, type, e, 1);
737           if (rval)
738             return rval;
739           if (flags & LOOKUP_COMPLAIN)
740             cp_error ("`%#T' used where a `%T' was expected", intype, type);
741           if (flags & LOOKUP_SPECULATIVELY)
742             return NULL_TREE;
743           return error_mark_node;
744         }
745       if (code == BOOLEAN_TYPE)
746         {
747           /* Common Ada/Pascal programmer's mistake.  We always warn
748              about this since it is so bad.  */
749           if (TREE_CODE (expr) == FUNCTION_DECL)
750             cp_warning ("the address of `%D', will always be `true'", expr);
751           return truthvalue_conversion (e);
752         }
753       return fold (convert_to_integer (type, e));
754     }
755   if (code == POINTER_TYPE || code == REFERENCE_TYPE
756       || TYPE_PTRMEMFUNC_P (type))
757     return fold (cp_convert_to_pointer (type, e));
758   if (code == REAL_TYPE || code == COMPLEX_TYPE)
759     {
760       if (IS_AGGR_TYPE (TREE_TYPE (e)))
761         {
762           tree rval;
763           rval = build_type_conversion (CONVERT_EXPR, type, e, 1);
764           if (rval)
765             return rval;
766           else
767             if (flags & LOOKUP_COMPLAIN)
768               cp_error ("`%#T' used where a floating point value was expected",
769                         TREE_TYPE (e));
770         }
771       if (code == REAL_TYPE)
772         return fold (convert_to_real (type, e));
773       else if (code == COMPLEX_TYPE)
774         return fold (convert_to_complex (type, e));
775     }
776
777   /* New C++ semantics:  since assignment is now based on
778      memberwise copying,  if the rhs type is derived from the
779      lhs type, then we may still do a conversion.  */
780   if (IS_AGGR_TYPE_CODE (code))
781     {
782       tree dtype = TREE_TYPE (e);
783       tree ctor = NULL_TREE;
784
785       dtype = TYPE_MAIN_VARIANT (dtype);
786
787       /* Conversion of object pointers or signature pointers/references
788          to signature pointers/references.  */
789
790       if (TYPE_LANG_SPECIFIC (type)
791           && (IS_SIGNATURE_POINTER (type) || IS_SIGNATURE_REFERENCE (type)))
792         {
793           tree constructor = build_signature_pointer_constructor (type, expr);
794           tree sig_ty = SIGNATURE_TYPE (type);
795           tree sig_ptr;
796
797           if (constructor == error_mark_node)
798             return error_mark_node;
799
800           sig_ptr = get_temp_name (type, 1);
801           DECL_INITIAL (sig_ptr) = constructor;
802           CLEAR_SIGNATURE (sig_ty);
803           cp_finish_decl (sig_ptr, constructor, NULL_TREE, 0, 0);
804           SET_SIGNATURE (sig_ty);
805           TREE_READONLY (sig_ptr) = 1;
806
807           return sig_ptr;
808         }
809
810       /* Conversion between aggregate types.  New C++ semantics allow
811          objects of derived type to be cast to objects of base type.
812          Old semantics only allowed this between pointers.
813
814          There may be some ambiguity between using a constructor
815          vs. using a type conversion operator when both apply.  */
816
817       ctor = e;
818
819       if (IS_AGGR_TYPE (type) && CLASSTYPE_ABSTRACT_VIRTUALS (type))
820         {
821           abstract_virtuals_error (NULL_TREE, type);
822           return error_mark_node;
823         }
824
825       if ((flags & LOOKUP_ONLYCONVERTING)
826           && ! (IS_AGGR_TYPE (dtype) && DERIVED_FROM_P (type, dtype)))
827         /* For copy-initialization, first we create a temp of the proper type
828            with a user-defined conversion sequence, then we direct-initialize
829            the target with the temp (see [dcl.init]).  */
830         ctor = build_user_type_conversion (type, ctor, flags);
831       if (ctor)
832         ctor = build_method_call (NULL_TREE, ctor_identifier,
833                                   build_expr_list (NULL_TREE, ctor),
834                                   TYPE_BINFO (type), flags);
835       if (ctor)
836         return build_cplus_new (type, ctor);
837     }
838
839   /* If TYPE or TREE_TYPE (E) is not on the permanent_obstack,
840      then it won't be hashed and hence compare as not equal,
841      even when it is.  */
842   if (code == ARRAY_TYPE
843       && TREE_TYPE (TREE_TYPE (e)) == TREE_TYPE (type)
844       && index_type_equal (TYPE_DOMAIN (TREE_TYPE (e)), TYPE_DOMAIN (type)))
845     return e;
846
847   if (flags & LOOKUP_COMPLAIN)
848     cp_error ("conversion from `%T' to non-scalar type `%T' requested",
849               TREE_TYPE (expr), type);
850   if (flags & LOOKUP_SPECULATIVELY)
851     return NULL_TREE;
852   return error_mark_node;
853 }
854
855 /* Create an expression whose value is that of EXPR,
856    converted to type TYPE.  The TREE_TYPE of the value
857    is always TYPE.  This function implements all reasonable
858    conversions; callers should filter out those that are
859    not permitted by the language being compiled.
860
861    Most of this routine is from build_reinterpret_cast.
862
863    The backend cannot call cp_convert (what was convert) because
864    conversions to/from basetypes may involve memory references
865    (vbases) and adding or subtracting small values (multiple
866    inheritance), but it calls convert from the constant folding code
867    on subtrees of already build trees after it has ripped them apart.
868
869    Also, if we ever support range variables, we'll probably also have to
870    do a little bit more work.  */
871
872 tree
873 convert (type, expr)
874      tree type, expr;
875 {
876   tree intype;
877
878   if (type == error_mark_node || expr == error_mark_node)
879     return error_mark_node;
880
881   intype = TREE_TYPE (expr);
882
883   if (POINTER_TYPE_P (type) && POINTER_TYPE_P (intype))
884     {
885       if (TREE_READONLY_DECL_P (expr))
886         expr = decl_constant_value (expr);
887       return fold (build1 (NOP_EXPR, type, expr));
888     }
889
890   return ocp_convert (type, expr, CONV_OLD_CONVERT,
891                       LOOKUP_NORMAL|LOOKUP_NO_CONVERSION);
892 }
893
894 /* Like cp_convert, except permit conversions to take place which
895    are not normally allowed due to access restrictions
896    (such as conversion from sub-type to private super-type).  */
897
898 tree
899 convert_force (type, expr, convtype)
900      tree type;
901      tree expr;
902      int convtype;
903 {
904   register tree e = expr;
905   register enum tree_code code = TREE_CODE (type);
906
907   if (code == REFERENCE_TYPE)
908     return fold (convert_to_reference (type, e, CONV_C_CAST, LOOKUP_COMPLAIN,
909                                        NULL_TREE));
910   else if (TREE_CODE (TREE_TYPE (e)) == REFERENCE_TYPE)
911     e = convert_from_reference (e);
912
913   if (code == POINTER_TYPE)
914     return fold (convert_to_pointer_force (type, e));
915
916   /* From typeck.c convert_for_assignment */
917   if (((TREE_CODE (TREE_TYPE (e)) == POINTER_TYPE && TREE_CODE (e) == ADDR_EXPR
918         && TREE_CODE (TREE_TYPE (e)) == POINTER_TYPE
919         && TREE_CODE (TREE_TYPE (TREE_TYPE (e))) == METHOD_TYPE)
920        || integer_zerop (e)
921        || TYPE_PTRMEMFUNC_P (TREE_TYPE (e)))
922       && TYPE_PTRMEMFUNC_P (type))
923     {
924       /* compatible pointer to member functions.  */
925       return build_ptrmemfunc (TYPE_PTRMEMFUNC_FN_TYPE (type), e, 1);
926     }
927
928   return ocp_convert (type, e, CONV_C_CAST|convtype, LOOKUP_NORMAL);
929 }
930
931 /* Convert an aggregate EXPR to type XTYPE.  If a conversion
932    exists, return the attempted conversion.  This may
933    return ERROR_MARK_NODE if the conversion is not
934    allowed (references private members, etc).
935    If no conversion exists, NULL_TREE is returned.
936
937    If (FOR_SURE & 1) is non-zero, then we allow this type conversion
938    to take place immediately.  Otherwise, we build a SAVE_EXPR
939    which can be evaluated if the results are ever needed.
940
941    Changes to this functions should be mirrored in user_harshness.
942
943    FIXME: Ambiguity checking is wrong.  Should choose one by the implicit
944    object parameter, or by the second standard conversion sequence if
945    that doesn't do it.  This will probably wait for an overloading rewrite.
946    (jason 8/9/95)  */
947
948 tree
949 build_type_conversion (code, xtype, expr, for_sure)
950      enum tree_code code ATTRIBUTE_UNUSED;
951      tree xtype, expr;
952      int for_sure;
953 {
954   /* C++: check to see if we can convert this aggregate type
955      into the required type.  */
956   return build_user_type_conversion
957     (xtype, expr, for_sure ? LOOKUP_NORMAL : 0);
958 }
959
960 /* Convert the given EXPR to one of a group of types suitable for use in an
961    expression.  DESIRES is a combination of various WANT_* flags (q.v.)
962    which indicates which types are suitable.  If COMPLAIN is 1, complain
963    about ambiguity; otherwise, the caller will deal with it.  */
964
965 tree
966 build_expr_type_conversion (desires, expr, complain)
967      int desires;
968      tree expr;
969      int complain;
970 {
971   tree basetype = TREE_TYPE (expr);
972   tree conv = NULL_TREE;
973   tree winner = NULL_TREE;
974
975   if (expr == null_node 
976       && (desires & WANT_INT) 
977       && !(desires & WANT_NULL))
978     cp_warning ("converting NULL to non-pointer type");
979     
980   if (TREE_CODE (basetype) == OFFSET_TYPE)
981     expr = resolve_offset_ref (expr);
982   expr = convert_from_reference (expr);
983   basetype = TREE_TYPE (expr);
984
985   if (! IS_AGGR_TYPE (basetype))
986     switch (TREE_CODE (basetype))
987       {
988       case INTEGER_TYPE:
989         if ((desires & WANT_NULL) && null_ptr_cst_p (expr))
990           return expr;
991         /* else fall through...  */
992
993       case BOOLEAN_TYPE:
994         return (desires & WANT_INT) ? expr : NULL_TREE;
995       case ENUMERAL_TYPE:
996         return (desires & WANT_ENUM) ? expr : NULL_TREE;
997       case REAL_TYPE:
998         return (desires & WANT_FLOAT) ? expr : NULL_TREE;
999       case POINTER_TYPE:
1000         return (desires & WANT_POINTER) ? expr : NULL_TREE;
1001         
1002       case FUNCTION_TYPE:
1003       case ARRAY_TYPE:
1004         return (desires & WANT_POINTER) ? default_conversion (expr)
1005                                         : NULL_TREE;
1006       default:
1007         return NULL_TREE;
1008       }
1009
1010   /* The code for conversions from class type is currently only used for
1011      delete expressions.  Other expressions are handled by build_new_op.  */
1012
1013   if (! TYPE_HAS_CONVERSION (basetype))
1014     return NULL_TREE;
1015
1016   for (conv = lookup_conversions (basetype); conv; conv = TREE_CHAIN (conv))
1017     {
1018       int win = 0;
1019       tree candidate;
1020       tree cand = TREE_VALUE (conv);
1021
1022       if (winner && winner == cand)
1023         continue;
1024
1025       candidate = TREE_TYPE (TREE_TYPE (cand));
1026       if (TREE_CODE (candidate) == REFERENCE_TYPE)
1027         candidate = TREE_TYPE (candidate);
1028
1029       switch (TREE_CODE (candidate))
1030         {
1031         case BOOLEAN_TYPE:
1032         case INTEGER_TYPE:
1033           win = (desires & WANT_INT); break;
1034         case ENUMERAL_TYPE:
1035           win = (desires & WANT_ENUM); break;
1036         case REAL_TYPE:
1037           win = (desires & WANT_FLOAT); break;
1038         case POINTER_TYPE:
1039           win = (desires & WANT_POINTER); break;
1040
1041         default:
1042           break;
1043         }
1044
1045       if (win)
1046         {
1047           if (winner)
1048             {
1049               if (complain)
1050                 {
1051                   cp_error ("ambiguous default type conversion from `%T'",
1052                             basetype);
1053                   cp_error ("  candidate conversions include `%D' and `%D'",
1054                             winner, cand);
1055                 }
1056               return error_mark_node;
1057             }
1058           else
1059             winner = cand;
1060         }
1061     }
1062
1063   if (winner)
1064     {
1065       tree type = TREE_TYPE (TREE_TYPE (winner));
1066       if (TREE_CODE (type) == REFERENCE_TYPE)
1067         type = TREE_TYPE (type);
1068       return build_user_type_conversion (type, expr, LOOKUP_NORMAL);
1069     }
1070
1071   return NULL_TREE;
1072 }
1073
1074 /* Implements integral promotion (4.1) and float->double promotion.  */
1075
1076 tree
1077 type_promotes_to (type)
1078      tree type;
1079 {
1080   int type_quals;
1081
1082   if (type == error_mark_node)
1083     return error_mark_node;
1084
1085   type_quals = CP_TYPE_QUALS (type);
1086   type = TYPE_MAIN_VARIANT (type);
1087
1088   /* bool always promotes to int (not unsigned), even if it's the same
1089      size.  */
1090   if (type == boolean_type_node)
1091     type = integer_type_node;
1092
1093   /* Normally convert enums to int, but convert wide enums to something
1094      wider.  */
1095   else if (TREE_CODE (type) == ENUMERAL_TYPE
1096            || type == wchar_type_node)
1097     {
1098       int precision = MAX (TYPE_PRECISION (type),
1099                            TYPE_PRECISION (integer_type_node));
1100       tree totype = type_for_size (precision, 0);
1101       if (TREE_UNSIGNED (type)
1102           && ! int_fits_type_p (TYPE_MAX_VALUE (type), totype))
1103         type = type_for_size (precision, 1);
1104       else
1105         type = totype;
1106     }
1107   else if (C_PROMOTING_INTEGER_TYPE_P (type))
1108     {
1109       /* Retain unsignedness if really not getting bigger.  */
1110       if (TREE_UNSIGNED (type)
1111           && TYPE_PRECISION (type) == TYPE_PRECISION (integer_type_node))
1112         type = unsigned_type_node;
1113       else
1114         type = integer_type_node;
1115     }
1116   else if (type == float_type_node)
1117     type = double_type_node;
1118
1119   return cp_build_qualified_type (type, type_quals);
1120 }
1121
1122 /* The routines below this point are carefully written to conform to
1123    the standard.  They use the same terminology, and follow the rules
1124    closely.  Although they are used only in pt.c at the moment, they
1125    should presumably be used everywhere in the future.  */
1126
1127 /* Attempt to perform qualification conversions on EXPR to convert it
1128    to TYPE.  Return the resulting expression, or error_mark_node if
1129    the conversion was impossible.  */
1130
1131 tree 
1132 perform_qualification_conversions (type, expr)
1133      tree type;
1134      tree expr;
1135 {
1136   if (TREE_CODE (type) == POINTER_TYPE
1137       && TREE_CODE (TREE_TYPE (expr)) == POINTER_TYPE
1138       && comp_ptr_ttypes (TREE_TYPE (type), TREE_TYPE (TREE_TYPE (expr))))
1139     return build1 (NOP_EXPR, type, expr);
1140   else
1141     return error_mark_node;
1142 }