Eliminate source_location in favor of location_t
[official-gcc.git] / gcc / cp / cvt.c
blobeb1687377c3e049bd6164a0b6405b0ad90a96ddb
1 /* Language-level data type conversion for GNU C++.
2 Copyright (C) 1987-2018 Free Software Foundation, Inc.
3 Hacked by Michael Tiemann (tiemann@cygnus.com)
5 This file is part of GCC.
7 GCC 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 3, or (at your option)
10 any later version.
12 GCC 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.
17 You should have received a copy of the GNU General Public License
18 along with GCC; see the file COPYING3. If not see
19 <http://www.gnu.org/licenses/>. */
22 /* This file contains the functions for converting C++ expressions
23 to different data types. The only entry point is `convert'.
24 Every language front end must have a `convert' function
25 but what kind of conversions it does will depend on the language. */
27 #include "config.h"
28 #include "system.h"
29 #include "coretypes.h"
30 #include "target.h"
31 #include "cp-tree.h"
32 #include "stor-layout.h"
33 #include "flags.h"
34 #include "intl.h"
35 #include "convert.h"
36 #include "stringpool.h"
37 #include "attribs.h"
39 static tree convert_to_pointer_force (tree, tree, tsubst_flags_t);
40 static tree build_type_conversion (tree, tree);
41 static tree build_up_reference (tree, tree, int, tree, tsubst_flags_t);
42 static void diagnose_ref_binding (location_t, tree, tree, tree);
44 /* Change of width--truncation and extension of integers or reals--
45 is represented with NOP_EXPR. Proper functioning of many things
46 assumes that no other conversions can be NOP_EXPRs.
48 Conversion between integer and pointer is represented with CONVERT_EXPR.
49 Converting integer to real uses FLOAT_EXPR
50 and real to integer uses FIX_TRUNC_EXPR.
52 Here is a list of all the functions that assume that widening and
53 narrowing is always done with a NOP_EXPR:
54 In convert.c, convert_to_integer[_maybe_fold].
55 In c-typeck.c, build_binary_op_nodefault (boolean ops),
56 and c_common_truthvalue_conversion.
57 In expr.c: expand_expr, for operands of a MULT_EXPR.
58 In fold-const.c: fold.
59 In tree.c: get_narrower and get_unwidened.
61 C++: in multiple-inheritance, converting between pointers may involve
62 adjusting them by a delta stored within the class definition. */
64 /* Subroutines of `convert'. */
66 /* if converting pointer to pointer
67 if dealing with classes, check for derived->base or vice versa
68 else if dealing with method pointers, delegate
69 else convert blindly
70 else if converting class, pass off to build_type_conversion
71 else try C-style pointer conversion. */
73 static tree
74 cp_convert_to_pointer (tree type, tree expr, bool dofold,
75 tsubst_flags_t complain)
77 tree intype = TREE_TYPE (expr);
78 enum tree_code form;
79 tree rval;
80 location_t loc = cp_expr_loc_or_loc (expr, input_location);
82 if (intype == error_mark_node)
83 return error_mark_node;
85 if (MAYBE_CLASS_TYPE_P (intype))
87 intype = complete_type (intype);
88 if (!COMPLETE_TYPE_P (intype))
90 if (complain & tf_error)
91 error_at (loc, "can%'t convert from incomplete type %qH to %qI",
92 intype, type);
93 return error_mark_node;
96 rval = build_type_conversion (type, expr);
97 if (rval)
99 if ((complain & tf_error)
100 && rval == error_mark_node)
101 error_at (loc, "conversion of %qE from %qH to %qI is ambiguous",
102 expr, intype, type);
103 return rval;
107 /* Handle anachronistic conversions from (::*)() to cv void* or (*)(). */
108 if (TYPE_PTR_P (type)
109 && (TREE_CODE (TREE_TYPE (type)) == FUNCTION_TYPE
110 || VOID_TYPE_P (TREE_TYPE (type))))
112 if (TYPE_PTRMEMFUNC_P (intype)
113 || TREE_CODE (intype) == METHOD_TYPE)
114 return convert_member_func_to_ptr (type, expr, complain);
115 if (TYPE_PTR_P (TREE_TYPE (expr)))
116 return build_nop (type, expr);
117 intype = TREE_TYPE (expr);
120 if (expr == error_mark_node)
121 return error_mark_node;
123 form = TREE_CODE (intype);
125 if (INDIRECT_TYPE_P (intype))
127 intype = TYPE_MAIN_VARIANT (intype);
129 if (TYPE_MAIN_VARIANT (type) != intype
130 && TYPE_PTR_P (type)
131 && TREE_CODE (TREE_TYPE (type)) == RECORD_TYPE
132 && MAYBE_CLASS_TYPE_P (TREE_TYPE (type))
133 && MAYBE_CLASS_TYPE_P (TREE_TYPE (intype))
134 && TREE_CODE (TREE_TYPE (intype)) == RECORD_TYPE)
136 enum tree_code code = PLUS_EXPR;
137 tree binfo;
138 tree intype_class;
139 tree type_class;
140 bool same_p;
142 intype_class = TREE_TYPE (intype);
143 type_class = TREE_TYPE (type);
145 same_p = same_type_p (TYPE_MAIN_VARIANT (intype_class),
146 TYPE_MAIN_VARIANT (type_class));
147 binfo = NULL_TREE;
148 /* Try derived to base conversion. */
149 if (!same_p)
150 binfo = lookup_base (intype_class, type_class, ba_check,
151 NULL, complain);
152 if (!same_p && !binfo)
154 /* Try base to derived conversion. */
155 binfo = lookup_base (type_class, intype_class, ba_check,
156 NULL, complain);
157 code = MINUS_EXPR;
159 if (binfo == error_mark_node)
160 return error_mark_node;
161 if (binfo || same_p)
163 if (binfo)
164 expr = build_base_path (code, expr, binfo, 0, complain);
165 /* Add any qualifier conversions. */
166 return build_nop (type, expr);
170 if (TYPE_PTRMEMFUNC_P (type))
172 if (complain & tf_error)
173 error_at (loc, "cannot convert %qE from type %qH to type %qI",
174 expr, intype, type);
175 return error_mark_node;
178 return build_nop (type, expr);
180 else if ((TYPE_PTRDATAMEM_P (type) && TYPE_PTRDATAMEM_P (intype))
181 || (TYPE_PTRMEMFUNC_P (type) && TYPE_PTRMEMFUNC_P (intype)))
182 return convert_ptrmem (type, expr, /*allow_inverse_p=*/false,
183 /*c_cast_p=*/false, complain);
184 else if (TYPE_PTRMEMFUNC_P (intype))
186 if (!warn_pmf2ptr)
188 if (TREE_CODE (expr) == PTRMEM_CST)
189 return cp_convert_to_pointer (type, PTRMEM_CST_MEMBER (expr),
190 dofold, complain);
191 else if (TREE_CODE (expr) == OFFSET_REF)
193 tree object = TREE_OPERAND (expr, 0);
194 return get_member_function_from_ptrfunc (&object,
195 TREE_OPERAND (expr, 1),
196 complain);
199 if (complain & tf_error)
200 error_at (loc, "cannot convert %qE from type %qH to type %qI",
201 expr, intype, type);
202 return error_mark_node;
205 if (null_ptr_cst_p (expr))
207 if (TYPE_PTRMEMFUNC_P (type))
208 return build_ptrmemfunc (TYPE_PTRMEMFUNC_FN_TYPE (type), expr, 0,
209 /*c_cast_p=*/false, complain);
211 if (complain & tf_warning)
212 maybe_warn_zero_as_null_pointer_constant (expr, loc);
214 /* A NULL pointer-to-data-member is represented by -1, not by
215 zero. */
216 tree val = (TYPE_PTRDATAMEM_P (type)
217 ? build_int_cst_type (type, -1)
218 : build_int_cst (type, 0));
220 return (TREE_SIDE_EFFECTS (expr)
221 ? build2 (COMPOUND_EXPR, type, expr, val) : val);
223 else if (TYPE_PTRMEM_P (type) && INTEGRAL_CODE_P (form))
225 if (complain & tf_error)
226 error_at (loc, "invalid conversion from %qH to %qI", intype, type);
227 return error_mark_node;
230 if (INTEGRAL_CODE_P (form))
232 if (TYPE_PRECISION (intype) == POINTER_SIZE)
233 return build1 (CONVERT_EXPR, type, expr);
234 expr = cp_convert (c_common_type_for_size (POINTER_SIZE, 0), expr,
235 complain);
236 /* Modes may be different but sizes should be the same. There
237 is supposed to be some integral type that is the same width
238 as a pointer. */
239 gcc_assert (GET_MODE_SIZE (SCALAR_INT_TYPE_MODE (TREE_TYPE (expr)))
240 == GET_MODE_SIZE (SCALAR_INT_TYPE_MODE (type)));
242 /* FIXME needed because convert_to_pointer_maybe_fold still folds
243 conversion of constants. */
244 if (!dofold)
245 return build1 (CONVERT_EXPR, type, expr);
247 return convert_to_pointer_maybe_fold (type, expr, dofold);
250 if (type_unknown_p (expr))
251 return instantiate_type (type, expr, complain);
253 if (complain & tf_error)
254 error_at (loc, "cannot convert %qE from type %qH to type %qI",
255 expr, intype, type);
256 return error_mark_node;
259 /* Like convert, except permit conversions to take place which
260 are not normally allowed due to access restrictions
261 (such as conversion from sub-type to private super-type). */
263 static tree
264 convert_to_pointer_force (tree type, tree expr, tsubst_flags_t complain)
266 tree intype = TREE_TYPE (expr);
267 enum tree_code form = TREE_CODE (intype);
269 if (form == POINTER_TYPE)
271 intype = TYPE_MAIN_VARIANT (intype);
273 if (TYPE_MAIN_VARIANT (type) != intype
274 && TREE_CODE (TREE_TYPE (type)) == RECORD_TYPE
275 && MAYBE_CLASS_TYPE_P (TREE_TYPE (type))
276 && MAYBE_CLASS_TYPE_P (TREE_TYPE (intype))
277 && TREE_CODE (TREE_TYPE (intype)) == RECORD_TYPE)
279 enum tree_code code = PLUS_EXPR;
280 tree binfo;
282 binfo = lookup_base (TREE_TYPE (intype), TREE_TYPE (type),
283 ba_unique, NULL, complain);
284 if (!binfo)
286 binfo = lookup_base (TREE_TYPE (type), TREE_TYPE (intype),
287 ba_unique, NULL, complain);
288 code = MINUS_EXPR;
290 if (binfo == error_mark_node)
291 return error_mark_node;
292 if (binfo)
294 expr = build_base_path (code, expr, binfo, 0, complain);
295 if (expr == error_mark_node)
296 return error_mark_node;
297 /* Add any qualifier conversions. */
298 if (!same_type_p (TREE_TYPE (TREE_TYPE (expr)),
299 TREE_TYPE (type)))
300 expr = build_nop (type, expr);
301 return expr;
306 return cp_convert_to_pointer (type, expr, /*fold*/false, complain);
309 /* We are passing something to a function which requires a reference.
310 The type we are interested in is in TYPE. The initial
311 value we have to begin with is in ARG.
313 FLAGS controls how we manage access checking.
314 DIRECT_BIND in FLAGS controls how any temporaries are generated.
315 If DIRECT_BIND is set, DECL is the reference we're binding to. */
317 static tree
318 build_up_reference (tree type, tree arg, int flags, tree decl,
319 tsubst_flags_t complain)
321 tree rval;
322 tree argtype = TREE_TYPE (arg);
323 tree target_type = TREE_TYPE (type);
325 gcc_assert (TYPE_REF_P (type));
327 if ((flags & DIRECT_BIND) && ! lvalue_p (arg))
329 /* Create a new temporary variable. We can't just use a TARGET_EXPR
330 here because it needs to live as long as DECL. */
331 tree targ = arg;
333 arg = make_temporary_var_for_ref_to_temp (decl, target_type);
335 /* Process the initializer for the declaration. */
336 DECL_INITIAL (arg) = targ;
337 cp_finish_decl (arg, targ, /*init_const_expr_p=*/false, NULL_TREE,
338 LOOKUP_ONLYCONVERTING|DIRECT_BIND);
340 else if (!(flags & DIRECT_BIND) && ! obvalue_p (arg))
341 return get_target_expr_sfinae (arg, complain);
343 /* If we had a way to wrap this up, and say, if we ever needed its
344 address, transform all occurrences of the register, into a memory
345 reference we could win better. */
346 rval = cp_build_addr_expr (arg, complain);
347 if (rval == error_mark_node)
348 return error_mark_node;
350 if ((flags & LOOKUP_PROTECT)
351 && TYPE_MAIN_VARIANT (argtype) != TYPE_MAIN_VARIANT (target_type)
352 && MAYBE_CLASS_TYPE_P (argtype)
353 && MAYBE_CLASS_TYPE_P (target_type))
355 /* We go through lookup_base for the access control. */
356 tree binfo = lookup_base (argtype, target_type, ba_check,
357 NULL, complain);
358 if (binfo == error_mark_node)
359 return error_mark_node;
360 if (binfo == NULL_TREE)
361 return error_not_base_type (target_type, argtype);
362 rval = build_base_path (PLUS_EXPR, rval, binfo, 1, complain);
364 else
365 rval
366 = convert_to_pointer_force (build_pointer_type (target_type),
367 rval, complain);
368 return build_nop (type, rval);
371 /* Subroutine of convert_to_reference. REFTYPE is the target reference type.
372 INTYPE is the original rvalue type and DECL is an optional _DECL node
373 for diagnostics.
375 [dcl.init.ref] says that if an rvalue is used to
376 initialize a reference, then the reference must be to a
377 non-volatile const type. */
379 static void
380 diagnose_ref_binding (location_t loc, tree reftype, tree intype, tree decl)
382 tree ttl = TREE_TYPE (reftype);
384 if (!TYPE_REF_IS_RVALUE (reftype)
385 && !CP_TYPE_CONST_NON_VOLATILE_P (ttl))
387 const char *msg;
389 if (CP_TYPE_VOLATILE_P (ttl) && decl)
390 msg = G_("initialization of volatile reference type %q#T from "
391 "rvalue of type %qT");
392 else if (CP_TYPE_VOLATILE_P (ttl))
393 msg = G_("conversion to volatile reference type %q#T "
394 "from rvalue of type %qT");
395 else if (decl)
396 msg = G_("initialization of non-const reference type %q#T from "
397 "rvalue of type %qT");
398 else
399 msg = G_("conversion to non-const reference type %q#T from "
400 "rvalue of type %qT");
402 permerror (loc, msg, reftype, intype);
406 /* For C++: Only need to do one-level references, but cannot
407 get tripped up on signed/unsigned differences.
409 DECL is either NULL_TREE or the _DECL node for a reference that is being
410 initialized. It can be error_mark_node if we don't know the _DECL but
411 we know it's an initialization. */
413 tree
414 convert_to_reference (tree reftype, tree expr, int convtype,
415 int flags, tree decl, tsubst_flags_t complain)
417 tree type = TYPE_MAIN_VARIANT (TREE_TYPE (reftype));
418 tree intype;
419 tree rval = NULL_TREE;
420 tree rval_as_conversion = NULL_TREE;
421 bool can_convert_intype_to_type;
422 location_t loc = cp_expr_loc_or_loc (expr, input_location);
424 if (TREE_CODE (type) == FUNCTION_TYPE
425 && TREE_TYPE (expr) == unknown_type_node)
426 expr = instantiate_type (type, expr, complain);
428 if (expr == error_mark_node)
429 return error_mark_node;
431 intype = TREE_TYPE (expr);
433 gcc_assert (!TYPE_REF_P (intype));
434 gcc_assert (TYPE_REF_P (reftype));
436 intype = TYPE_MAIN_VARIANT (intype);
438 can_convert_intype_to_type = can_convert_standard (type, intype, complain);
440 if (!can_convert_intype_to_type
441 && (convtype & CONV_IMPLICIT) && MAYBE_CLASS_TYPE_P (intype)
442 && ! (flags & LOOKUP_NO_CONVERSION))
444 /* Look for a user-defined conversion to lvalue that we can use. */
446 rval_as_conversion
447 = build_type_conversion (reftype, expr);
449 if (rval_as_conversion && rval_as_conversion != error_mark_node
450 && lvalue_p (rval_as_conversion))
452 expr = rval_as_conversion;
453 rval_as_conversion = NULL_TREE;
454 intype = type;
455 can_convert_intype_to_type = 1;
459 if (((convtype & CONV_STATIC)
460 && can_convert_standard (intype, type, complain))
461 || ((convtype & CONV_IMPLICIT) && can_convert_intype_to_type))
464 tree ttl = TREE_TYPE (reftype);
465 tree ttr = lvalue_type (expr);
467 if ((complain & tf_error)
468 && ! lvalue_p (expr))
469 diagnose_ref_binding (loc, reftype, intype, decl);
471 if (! (convtype & CONV_CONST)
472 && !at_least_as_qualified_p (ttl, ttr))
474 if (complain & tf_error)
475 permerror (loc, "conversion from %qH to %qI discards qualifiers",
476 ttr, reftype);
477 else
478 return error_mark_node;
482 return build_up_reference (reftype, expr, flags, decl, complain);
484 else if ((convtype & CONV_REINTERPRET) && obvalue_p (expr))
486 /* When casting an lvalue to a reference type, just convert into
487 a pointer to the new type and deference it. This is allowed
488 by San Diego WP section 5.2.9 paragraph 12, though perhaps it
489 should be done directly (jason). (int &)ri ---> *(int*)&ri */
491 /* B* bp; A& ar = (A&)bp; is valid, but it's probably not what they
492 meant. */
493 if ((complain & tf_warning)
494 && TYPE_PTR_P (intype)
495 && (comptypes (TREE_TYPE (intype), type,
496 COMPARE_BASE | COMPARE_DERIVED)))
497 warning_at (loc, 0, "casting %qT to %qT does not dereference pointer",
498 intype, reftype);
500 rval = cp_build_addr_expr (expr, complain);
501 if (rval != error_mark_node)
502 rval = convert_force (build_pointer_type (TREE_TYPE (reftype)),
503 rval, 0, complain);
504 if (rval != error_mark_node)
505 rval = build1 (NOP_EXPR, reftype, rval);
507 else
509 rval = convert_for_initialization (NULL_TREE, type, expr, flags,
510 ICR_CONVERTING, 0, 0, complain);
511 if (rval == NULL_TREE || rval == error_mark_node)
512 return rval;
513 if (complain & tf_error)
514 diagnose_ref_binding (loc, reftype, intype, decl);
515 rval = build_up_reference (reftype, rval, flags, decl, complain);
518 if (rval)
520 /* If we found a way to convert earlier, then use it. */
521 return rval;
524 if (complain & tf_error)
525 error_at (loc, "cannot convert type %qH to type %qI", intype, reftype);
527 return error_mark_node;
530 /* We are using a reference VAL for its value. Bash that reference all the
531 way down to its lowest form. */
533 tree
534 convert_from_reference (tree val)
536 if (TREE_TYPE (val)
537 && TYPE_REF_P (TREE_TYPE (val)))
539 tree t = TREE_TYPE (TREE_TYPE (val));
540 tree ref = build1 (INDIRECT_REF, t, val);
542 mark_exp_read (val);
543 /* We *must* set TREE_READONLY when dereferencing a pointer to const,
544 so that we get the proper error message if the result is used
545 to assign to. Also, &* is supposed to be a no-op. */
546 TREE_READONLY (ref) = CP_TYPE_CONST_P (t);
547 TREE_THIS_VOLATILE (ref) = CP_TYPE_VOLATILE_P (t);
548 TREE_SIDE_EFFECTS (ref)
549 = (TREE_THIS_VOLATILE (ref) || TREE_SIDE_EFFECTS (val));
550 val = ref;
553 return val;
556 /* Really perform an lvalue-to-rvalue conversion, including copying an
557 argument of class type into a temporary. */
559 tree
560 force_rvalue (tree expr, tsubst_flags_t complain)
562 tree type = TREE_TYPE (expr);
563 if (MAYBE_CLASS_TYPE_P (type) && TREE_CODE (expr) != TARGET_EXPR)
565 vec<tree, va_gc> *args = make_tree_vector_single (expr);
566 expr = build_special_member_call (NULL_TREE, complete_ctor_identifier,
567 &args, type, LOOKUP_NORMAL, complain);
568 release_tree_vector (args);
569 expr = build_cplus_new (type, expr, complain);
571 else
572 expr = decay_conversion (expr, complain);
574 return expr;
578 /* If EXPR and ORIG are INTEGER_CSTs, return a version of EXPR that has
579 TREE_OVERFLOW set only if it is set in ORIG. Otherwise, return EXPR
580 unchanged. */
582 static tree
583 ignore_overflows (tree expr, tree orig)
585 if (TREE_CODE (expr) == INTEGER_CST
586 && TREE_CODE (orig) == INTEGER_CST
587 && TREE_OVERFLOW (expr) != TREE_OVERFLOW (orig))
589 gcc_assert (!TREE_OVERFLOW (orig));
590 /* Ensure constant sharing. */
591 expr = wide_int_to_tree (TREE_TYPE (expr), wi::to_wide (expr));
593 return expr;
596 /* Fold away simple conversions, but make sure TREE_OVERFLOW is set
597 properly. */
599 tree
600 cp_fold_convert (tree type, tree expr)
602 tree conv;
603 if (TREE_TYPE (expr) == type)
604 conv = expr;
605 else if (TREE_CODE (expr) == PTRMEM_CST
606 && same_type_p (TYPE_PTRMEM_CLASS_TYPE (type),
607 PTRMEM_CST_CLASS (expr)))
609 /* Avoid wrapping a PTRMEM_CST in NOP_EXPR. */
610 conv = copy_node (expr);
611 TREE_TYPE (conv) = type;
613 else if (TYPE_PTRMEM_P (type))
615 conv = convert_ptrmem (type, expr, true, false,
616 tf_warning_or_error);
617 conv = cp_fully_fold (conv);
619 else
621 conv = fold_convert (type, expr);
622 conv = ignore_overflows (conv, expr);
624 return conv;
627 /* C++ conversions, preference to static cast conversions. */
629 tree
630 cp_convert (tree type, tree expr, tsubst_flags_t complain)
632 return ocp_convert (type, expr, CONV_OLD_CONVERT, LOOKUP_NORMAL, complain);
635 /* C++ equivalent of convert_and_check but using cp_convert as the
636 conversion function.
638 Convert EXPR to TYPE, warning about conversion problems with constants.
639 Invoke this function on every expression that is converted implicitly,
640 i.e. because of language rules and not because of an explicit cast. */
642 tree
643 cp_convert_and_check (tree type, tree expr, tsubst_flags_t complain)
645 tree result;
647 if (TREE_TYPE (expr) == type)
648 return expr;
649 if (expr == error_mark_node)
650 return expr;
651 result = cp_convert (type, expr, complain);
653 if ((complain & tf_warning)
654 && c_inhibit_evaluation_warnings == 0)
656 tree folded = cp_fully_fold (expr);
657 tree folded_result;
658 if (folded == expr)
659 folded_result = result;
660 else
662 /* Avoid bogus -Wparentheses warnings. */
663 warning_sentinel w (warn_parentheses);
664 warning_sentinel c (warn_int_in_bool_context);
665 folded_result = cp_convert (type, folded, tf_none);
667 folded_result = fold_simple (folded_result);
668 if (!TREE_OVERFLOW_P (folded)
669 && folded_result != error_mark_node)
670 warnings_for_convert_and_check (cp_expr_loc_or_loc (expr, input_location),
671 type, folded, folded_result);
674 return result;
677 /* Conversion...
679 FLAGS indicates how we should behave. */
681 tree
682 ocp_convert (tree type, tree expr, int convtype, int flags,
683 tsubst_flags_t complain)
685 tree e = expr;
686 enum tree_code code = TREE_CODE (type);
687 const char *invalid_conv_diag;
688 tree e1;
689 location_t loc = cp_expr_loc_or_loc (expr, input_location);
690 bool dofold = (convtype & CONV_FOLD);
692 if (error_operand_p (e) || type == error_mark_node)
693 return error_mark_node;
695 complete_type (type);
696 complete_type (TREE_TYPE (expr));
698 if ((invalid_conv_diag
699 = targetm.invalid_conversion (TREE_TYPE (expr), type)))
701 if (complain & tf_error)
702 error (invalid_conv_diag);
703 return error_mark_node;
706 /* FIXME remove when moving to c_fully_fold model. */
707 if (!CLASS_TYPE_P (type))
709 e = mark_rvalue_use (e);
710 e = scalar_constant_value (e);
712 if (error_operand_p (e))
713 return error_mark_node;
715 if (NULLPTR_TYPE_P (type) && null_ptr_cst_p (e))
717 if (complain & tf_warning)
718 maybe_warn_zero_as_null_pointer_constant (e, loc);
720 if (!TREE_SIDE_EFFECTS (e))
721 return nullptr_node;
724 if (MAYBE_CLASS_TYPE_P (type) && (convtype & CONV_FORCE_TEMP))
725 /* We need a new temporary; don't take this shortcut. */;
726 else if (same_type_ignoring_top_level_qualifiers_p (type, TREE_TYPE (e)))
728 tree etype = TREE_TYPE (e);
729 if (same_type_p (type, etype))
730 /* The call to fold will not always remove the NOP_EXPR as
731 might be expected, since if one of the types is a typedef;
732 the comparison in fold is just equality of pointers, not a
733 call to comptypes. We don't call fold in this case because
734 that can result in infinite recursion; fold will call
735 convert, which will call ocp_convert, etc. */
736 return e;
737 /* For complex data types, we need to perform componentwise
738 conversion. */
739 else if (TREE_CODE (type) == COMPLEX_TYPE)
740 return convert_to_complex_maybe_fold (type, e, dofold);
741 else if (VECTOR_TYPE_P (type))
742 return convert_to_vector (type, e);
743 else if (TREE_CODE (e) == TARGET_EXPR)
745 /* Don't build a NOP_EXPR of class type. Instead, change the
746 type of the temporary. */
747 gcc_assert (same_type_ignoring_top_level_qualifiers_p (type, etype));
748 TREE_TYPE (e) = TREE_TYPE (TARGET_EXPR_SLOT (e)) = type;
749 return e;
751 else if (TREE_CODE (e) == CONSTRUCTOR)
753 gcc_assert (same_type_ignoring_top_level_qualifiers_p (type, etype));
754 TREE_TYPE (e) = type;
755 return e;
757 else
759 /* We shouldn't be treating objects of ADDRESSABLE type as
760 rvalues. */
761 gcc_assert (!TREE_ADDRESSABLE (type));
762 return build_nop (type, e);
766 e1 = targetm.convert_to_type (type, e);
767 if (e1)
768 return e1;
770 if (code == VOID_TYPE && (convtype & CONV_STATIC))
772 e = convert_to_void (e, ICV_CAST, complain);
773 return e;
776 if (INTEGRAL_CODE_P (code))
778 tree intype = TREE_TYPE (e);
779 tree converted;
781 if (TREE_CODE (type) == ENUMERAL_TYPE)
783 /* enum = enum, enum = int, enum = float, (enum)pointer are all
784 errors. */
785 if (((INTEGRAL_OR_ENUMERATION_TYPE_P (intype)
786 || TREE_CODE (intype) == REAL_TYPE)
787 && ! (convtype & CONV_STATIC))
788 || TYPE_PTR_P (intype))
790 if (complain & tf_error)
791 permerror (loc, "conversion from %q#T to %q#T", intype, type);
792 else
793 return error_mark_node;
796 /* [expr.static.cast]
798 8. A value of integral or enumeration type can be explicitly
799 converted to an enumeration type. The value is unchanged if
800 the original value is within the range of the enumeration
801 values. Otherwise, the resulting enumeration value is
802 unspecified. */
803 if ((complain & tf_warning)
804 && TREE_CODE (e) == INTEGER_CST
805 && ENUM_UNDERLYING_TYPE (type)
806 && !int_fits_type_p (e, ENUM_UNDERLYING_TYPE (type)))
807 warning_at (loc, OPT_Wconversion,
808 "the result of the conversion is unspecified because "
809 "%qE is outside the range of type %qT",
810 expr, type);
812 if (MAYBE_CLASS_TYPE_P (intype))
814 tree rval;
815 rval = build_type_conversion (type, e);
816 if (rval)
817 return rval;
818 if (complain & tf_error)
819 error_at (loc, "%q#T used where a %qT was expected", intype, type);
820 return error_mark_node;
822 if (code == BOOLEAN_TYPE)
824 if (VOID_TYPE_P (intype))
826 if (complain & tf_error)
827 error_at (loc,
828 "could not convert %qE from %<void%> to %<bool%>",
829 expr);
830 return error_mark_node;
833 /* We can't implicitly convert a scoped enum to bool, so convert
834 to the underlying type first. */
835 if (SCOPED_ENUM_P (intype) && (convtype & CONV_STATIC))
836 e = build_nop (ENUM_UNDERLYING_TYPE (intype), e);
837 if (complain & tf_warning)
838 return cp_truthvalue_conversion (e);
839 else
841 /* Prevent bogus -Wint-in-bool-context warnings coming
842 from c_common_truthvalue_conversion down the line. */
843 warning_sentinel w (warn_int_in_bool_context);
844 return cp_truthvalue_conversion (e);
848 converted = convert_to_integer_maybe_fold (type, e, dofold);
850 /* Ignore any integer overflow caused by the conversion. */
851 return ignore_overflows (converted, e);
853 if (INDIRECT_TYPE_P (type) || TYPE_PTRMEM_P (type))
854 return cp_convert_to_pointer (type, e, dofold, complain);
855 if (code == VECTOR_TYPE)
857 tree in_vtype = TREE_TYPE (e);
858 if (MAYBE_CLASS_TYPE_P (in_vtype))
860 tree ret_val;
861 ret_val = build_type_conversion (type, e);
862 if (ret_val)
863 return ret_val;
864 if (complain & tf_error)
865 error_at (loc, "%q#T used where a %qT was expected",
866 in_vtype, type);
867 return error_mark_node;
869 return convert_to_vector (type, e);
871 if (code == REAL_TYPE || code == COMPLEX_TYPE)
873 if (MAYBE_CLASS_TYPE_P (TREE_TYPE (e)))
875 tree rval;
876 rval = build_type_conversion (type, e);
877 if (rval)
878 return rval;
879 else if (complain & tf_error)
880 error_at (loc,
881 "%q#T used where a floating point value was expected",
882 TREE_TYPE (e));
884 if (code == REAL_TYPE)
885 return convert_to_real_maybe_fold (type, e, dofold);
886 else if (code == COMPLEX_TYPE)
887 return convert_to_complex_maybe_fold (type, e, dofold);
890 /* New C++ semantics: since assignment is now based on
891 memberwise copying, if the rhs type is derived from the
892 lhs type, then we may still do a conversion. */
893 if (RECORD_OR_UNION_CODE_P (code))
895 tree dtype = TREE_TYPE (e);
896 tree ctor = NULL_TREE;
898 dtype = TYPE_MAIN_VARIANT (dtype);
900 /* Conversion between aggregate types. New C++ semantics allow
901 objects of derived type to be cast to objects of base type.
902 Old semantics only allowed this between pointers.
904 There may be some ambiguity between using a constructor
905 vs. using a type conversion operator when both apply. */
907 ctor = e;
909 if (abstract_virtuals_error_sfinae (NULL_TREE, type, complain))
910 return error_mark_node;
912 if (BRACE_ENCLOSED_INITIALIZER_P (ctor))
913 ctor = perform_implicit_conversion (type, ctor, complain);
914 else if ((flags & LOOKUP_ONLYCONVERTING)
915 && ! (CLASS_TYPE_P (dtype) && DERIVED_FROM_P (type, dtype)))
916 /* For copy-initialization, first we create a temp of the proper type
917 with a user-defined conversion sequence, then we direct-initialize
918 the target with the temp (see [dcl.init]). */
919 ctor = build_user_type_conversion (type, ctor, flags, complain);
920 else
922 vec<tree, va_gc> *ctor_vec = make_tree_vector_single (ctor);
923 ctor = build_special_member_call (NULL_TREE,
924 complete_ctor_identifier,
925 &ctor_vec,
926 type, flags, complain);
927 release_tree_vector (ctor_vec);
929 if (ctor)
930 return build_cplus_new (type, ctor, complain);
933 if (complain & tf_error)
935 /* If the conversion failed and expr was an invalid use of pointer to
936 member function, try to report a meaningful error. */
937 if (invalid_nonstatic_memfn_p (loc, expr, complain))
938 /* We displayed the error message. */;
939 else
940 error_at (loc, "conversion from %qH to non-scalar type %qI requested",
941 TREE_TYPE (expr), type);
943 return error_mark_node;
946 /* If CALL is a call, return the callee; otherwise null. */
948 tree
949 cp_get_callee (tree call)
951 if (call == NULL_TREE)
952 return call;
953 else if (TREE_CODE (call) == CALL_EXPR)
954 return CALL_EXPR_FN (call);
955 else if (TREE_CODE (call) == AGGR_INIT_EXPR)
956 return AGGR_INIT_EXPR_FN (call);
957 return NULL_TREE;
960 /* FN is the callee of a CALL_EXPR or AGGR_INIT_EXPR; return the FUNCTION_DECL
961 if we can. */
963 tree
964 cp_get_fndecl_from_callee (tree fn, bool fold /* = true */)
966 if (fn == NULL_TREE)
967 return fn;
968 if (TREE_CODE (fn) == FUNCTION_DECL)
969 return fn;
970 tree type = TREE_TYPE (fn);
971 if (type == unknown_type_node)
972 return NULL_TREE;
973 gcc_assert (INDIRECT_TYPE_P (type));
974 if (fold)
975 fn = maybe_constant_init (fn);
976 STRIP_NOPS (fn);
977 if (TREE_CODE (fn) == ADDR_EXPR)
979 fn = TREE_OPERAND (fn, 0);
980 if (TREE_CODE (fn) == FUNCTION_DECL)
981 return fn;
983 return NULL_TREE;
986 /* Like get_callee_fndecl, but handles AGGR_INIT_EXPR as well and uses the
987 constexpr machinery. */
989 tree
990 cp_get_callee_fndecl (tree call)
992 return cp_get_fndecl_from_callee (cp_get_callee (call));
995 /* As above, but not using the constexpr machinery. */
997 tree
998 cp_get_callee_fndecl_nofold (tree call)
1000 return cp_get_fndecl_from_callee (cp_get_callee (call), false);
1003 /* Subroutine of convert_to_void. Warn if we're discarding something with
1004 attribute [[nodiscard]]. */
1006 static void
1007 maybe_warn_nodiscard (tree expr, impl_conv_void implicit)
1009 tree call = expr;
1010 if (TREE_CODE (expr) == TARGET_EXPR)
1011 call = TARGET_EXPR_INITIAL (expr);
1012 location_t loc = cp_expr_loc_or_loc (call, input_location);
1013 tree callee = cp_get_callee (call);
1014 if (!callee)
1015 return;
1017 tree type = TREE_TYPE (callee);
1018 if (TYPE_PTRMEMFUNC_P (type))
1019 type = TYPE_PTRMEMFUNC_FN_TYPE (type);
1020 if (INDIRECT_TYPE_P (type))
1021 type = TREE_TYPE (type);
1023 tree rettype = TREE_TYPE (type);
1024 tree fn = cp_get_fndecl_from_callee (callee);
1025 if (implicit != ICV_CAST && fn
1026 && lookup_attribute ("nodiscard", DECL_ATTRIBUTES (fn)))
1028 auto_diagnostic_group d;
1029 if (warning_at (loc, OPT_Wunused_result,
1030 "ignoring return value of %qD, "
1031 "declared with attribute nodiscard", fn))
1032 inform (DECL_SOURCE_LOCATION (fn), "declared here");
1034 else if (implicit != ICV_CAST
1035 && lookup_attribute ("nodiscard", TYPE_ATTRIBUTES (rettype)))
1037 auto_diagnostic_group d;
1038 if (warning_at (loc, OPT_Wunused_result,
1039 "ignoring returned value of type %qT, "
1040 "declared with attribute nodiscard", rettype))
1042 if (fn)
1043 inform (DECL_SOURCE_LOCATION (fn),
1044 "in call to %qD, declared here", fn);
1045 inform (DECL_SOURCE_LOCATION (TYPE_NAME (rettype)),
1046 "%qT declared here", rettype);
1049 else if (TREE_CODE (expr) == TARGET_EXPR
1050 && lookup_attribute ("warn_unused_result", TYPE_ATTRIBUTES (type)))
1052 /* The TARGET_EXPR confuses do_warn_unused_result into thinking that the
1053 result is used, so handle that case here. */
1054 if (fn)
1056 auto_diagnostic_group d;
1057 if (warning_at (loc, OPT_Wunused_result,
1058 "ignoring return value of %qD, "
1059 "declared with attribute warn_unused_result",
1060 fn))
1061 inform (DECL_SOURCE_LOCATION (fn), "declared here");
1063 else
1064 warning_at (loc, OPT_Wunused_result,
1065 "ignoring return value of function "
1066 "declared with attribute warn_unused_result");
1070 /* When an expression is used in a void context, its value is discarded and
1071 no lvalue-rvalue and similar conversions happen [expr.static.cast/4,
1072 stmt.expr/1, expr.comma/1]. This permits dereferencing an incomplete type
1073 in a void context. The C++ standard does not define what an `access' to an
1074 object is, but there is reason to believe that it is the lvalue to rvalue
1075 conversion -- if it were not, `*&*p = 1' would violate [expr]/4 in that it
1076 accesses `*p' not to calculate the value to be stored. But, dcl.type.cv/8
1077 indicates that volatile semantics should be the same between C and C++
1078 where ever possible. C leaves it implementation defined as to what
1079 constitutes an access to a volatile. So, we interpret `*vp' as a read of
1080 the volatile object `vp' points to, unless that is an incomplete type. For
1081 volatile references we do not do this interpretation, because that would
1082 make it impossible to ignore the reference return value from functions. We
1083 issue warnings in the confusing cases.
1085 The IMPLICIT is ICV_CAST when the user is explicitly converting an expression
1086 to void via a cast. If an expression is being implicitly converted, IMPLICIT
1087 indicates the context of the implicit conversion. */
1089 tree
1090 convert_to_void (tree expr, impl_conv_void implicit, tsubst_flags_t complain)
1092 location_t loc = cp_expr_loc_or_loc (expr, input_location);
1094 if (expr == error_mark_node
1095 || TREE_TYPE (expr) == error_mark_node)
1096 return error_mark_node;
1098 expr = maybe_undo_parenthesized_ref (expr);
1100 expr = mark_discarded_use (expr);
1101 if (implicit == ICV_CAST)
1102 /* An explicit cast to void avoids all -Wunused-but-set* warnings. */
1103 mark_exp_read (expr);
1105 if (!TREE_TYPE (expr))
1106 return expr;
1107 if (invalid_nonstatic_memfn_p (loc, expr, complain))
1108 return error_mark_node;
1109 if (TREE_CODE (expr) == PSEUDO_DTOR_EXPR)
1111 if (complain & tf_error)
1112 error_at (loc, "pseudo-destructor is not called");
1113 return error_mark_node;
1115 if (VOID_TYPE_P (TREE_TYPE (expr)))
1116 return expr;
1117 switch (TREE_CODE (expr))
1119 case COND_EXPR:
1121 /* The two parts of a cond expr might be separate lvalues. */
1122 tree op1 = TREE_OPERAND (expr,1);
1123 tree op2 = TREE_OPERAND (expr,2);
1124 bool side_effects = ((op1 && TREE_SIDE_EFFECTS (op1))
1125 || TREE_SIDE_EFFECTS (op2));
1126 tree new_op1, new_op2;
1127 new_op1 = NULL_TREE;
1128 if (implicit != ICV_CAST && !side_effects)
1130 if (op1)
1131 new_op1 = convert_to_void (op1, ICV_SECOND_OF_COND, complain);
1132 new_op2 = convert_to_void (op2, ICV_THIRD_OF_COND, complain);
1134 else
1136 if (op1)
1137 new_op1 = convert_to_void (op1, ICV_CAST, complain);
1138 new_op2 = convert_to_void (op2, ICV_CAST, complain);
1141 expr = build3 (COND_EXPR, TREE_TYPE (new_op2),
1142 TREE_OPERAND (expr, 0), new_op1, new_op2);
1143 break;
1146 case COMPOUND_EXPR:
1148 /* The second part of a compound expr contains the value. */
1149 tree op1 = TREE_OPERAND (expr,1);
1150 tree new_op1;
1151 if (implicit != ICV_CAST && !TREE_NO_WARNING (expr))
1152 new_op1 = convert_to_void (op1, ICV_RIGHT_OF_COMMA, complain);
1153 else
1154 new_op1 = convert_to_void (op1, ICV_CAST, complain);
1156 if (new_op1 != op1)
1158 tree t = build2 (COMPOUND_EXPR, TREE_TYPE (new_op1),
1159 TREE_OPERAND (expr, 0), new_op1);
1160 expr = t;
1163 break;
1166 case NON_LVALUE_EXPR:
1167 case NOP_EXPR:
1168 /* These have already decayed to rvalue. */
1169 break;
1171 case CALL_EXPR: /* We have a special meaning for volatile void fn(). */
1172 maybe_warn_nodiscard (expr, implicit);
1173 break;
1175 case INDIRECT_REF:
1177 tree type = TREE_TYPE (expr);
1178 int is_reference = TYPE_REF_P (TREE_TYPE (TREE_OPERAND (expr, 0)));
1179 int is_volatile = TYPE_VOLATILE (type);
1180 int is_complete = COMPLETE_TYPE_P (complete_type (type));
1182 /* Can't load the value if we don't know the type. */
1183 if (is_volatile && !is_complete)
1185 if (complain & tf_warning)
1186 switch (implicit)
1188 case ICV_CAST:
1189 warning_at (loc, 0, "conversion to void will not access "
1190 "object of incomplete type %qT", type);
1191 break;
1192 case ICV_SECOND_OF_COND:
1193 warning_at (loc, 0, "indirection will not access object of "
1194 "incomplete type %qT in second operand "
1195 "of conditional expression", type);
1196 break;
1197 case ICV_THIRD_OF_COND:
1198 warning_at (loc, 0, "indirection will not access object of "
1199 "incomplete type %qT in third operand "
1200 "of conditional expression", type);
1201 break;
1202 case ICV_RIGHT_OF_COMMA:
1203 warning_at (loc, 0, "indirection will not access object of "
1204 "incomplete type %qT in right operand of "
1205 "comma operator", type);
1206 break;
1207 case ICV_LEFT_OF_COMMA:
1208 warning_at (loc, 0, "indirection will not access object of "
1209 "incomplete type %qT in left operand of "
1210 "comma operator", type);
1211 break;
1212 case ICV_STATEMENT:
1213 warning_at (loc, 0, "indirection will not access object of "
1214 "incomplete type %qT in statement", type);
1215 break;
1216 case ICV_THIRD_IN_FOR:
1217 warning_at (loc, 0, "indirection will not access object of "
1218 "incomplete type %qT in for increment "
1219 "expression", type);
1220 break;
1221 default:
1222 gcc_unreachable ();
1225 /* Don't load the value if this is an implicit dereference, or if
1226 the type needs to be handled by ctors/dtors. */
1227 else if (is_volatile && is_reference)
1229 if (complain & tf_warning)
1230 switch (implicit)
1232 case ICV_CAST:
1233 warning_at (loc, 0, "conversion to void will not access "
1234 "object of type %qT", type);
1235 break;
1236 case ICV_SECOND_OF_COND:
1237 warning_at (loc, 0, "implicit dereference will not access "
1238 "object of type %qT in second operand of "
1239 "conditional expression", type);
1240 break;
1241 case ICV_THIRD_OF_COND:
1242 warning_at (loc, 0, "implicit dereference will not access "
1243 "object of type %qT in third operand of "
1244 "conditional expression", type);
1245 break;
1246 case ICV_RIGHT_OF_COMMA:
1247 warning_at (loc, 0, "implicit dereference will not access "
1248 "object of type %qT in right operand of "
1249 "comma operator", type);
1250 break;
1251 case ICV_LEFT_OF_COMMA:
1252 warning_at (loc, 0, "implicit dereference will not access "
1253 "object of type %qT in left operand of comma "
1254 "operator", type);
1255 break;
1256 case ICV_STATEMENT:
1257 warning_at (loc, 0, "implicit dereference will not access "
1258 "object of type %qT in statement", type);
1259 break;
1260 case ICV_THIRD_IN_FOR:
1261 warning_at (loc, 0, "implicit dereference will not access "
1262 "object of type %qT in for increment expression",
1263 type);
1264 break;
1265 default:
1266 gcc_unreachable ();
1269 else if (is_volatile && TREE_ADDRESSABLE (type))
1271 if (complain & tf_warning)
1272 switch (implicit)
1274 case ICV_CAST:
1275 warning_at (loc, 0, "conversion to void will not access "
1276 "object of non-trivially-copyable type %qT",
1277 type);
1278 break;
1279 case ICV_SECOND_OF_COND:
1280 warning_at (loc, 0, "indirection will not access object of "
1281 "non-trivially-copyable type %qT in second "
1282 "operand of conditional expression", type);
1283 break;
1284 case ICV_THIRD_OF_COND:
1285 warning_at (loc, 0, "indirection will not access object of "
1286 "non-trivially-copyable type %qT in third "
1287 "operand of conditional expression", type);
1288 break;
1289 case ICV_RIGHT_OF_COMMA:
1290 warning_at (loc, 0, "indirection will not access object of "
1291 "non-trivially-copyable type %qT in right "
1292 "operand of comma operator", type);
1293 break;
1294 case ICV_LEFT_OF_COMMA:
1295 warning_at (loc, 0, "indirection will not access object of "
1296 "non-trivially-copyable type %qT in left "
1297 "operand of comma operator", type);
1298 break;
1299 case ICV_STATEMENT:
1300 warning_at (loc, 0, "indirection will not access object of "
1301 "non-trivially-copyable type %qT in statement",
1302 type);
1303 break;
1304 case ICV_THIRD_IN_FOR:
1305 warning_at (loc, 0, "indirection will not access object of "
1306 "non-trivially-copyable type %qT in for "
1307 "increment expression", type);
1308 break;
1309 default:
1310 gcc_unreachable ();
1313 if (is_reference || !is_volatile || !is_complete || TREE_ADDRESSABLE (type))
1315 /* Emit a warning (if enabled) when the "effect-less" INDIRECT_REF
1316 operation is stripped off. Note that we don't warn about
1317 - an expression with TREE_NO_WARNING set. (For an example of
1318 such expressions, see build_over_call in call.c.)
1319 - automatic dereferencing of references, since the user cannot
1320 control it. (See also warn_if_unused_value() in c-common.c.) */
1321 if (warn_unused_value
1322 && implicit != ICV_CAST
1323 && (complain & tf_warning)
1324 && !TREE_NO_WARNING (expr)
1325 && !is_reference)
1326 warning_at (loc, OPT_Wunused_value, "value computed is not used");
1327 expr = TREE_OPERAND (expr, 0);
1328 if (TREE_CODE (expr) == CALL_EXPR)
1329 maybe_warn_nodiscard (expr, implicit);
1332 break;
1335 case VAR_DECL:
1337 /* External variables might be incomplete. */
1338 tree type = TREE_TYPE (expr);
1339 int is_complete = COMPLETE_TYPE_P (complete_type (type));
1341 if (TYPE_VOLATILE (type) && !is_complete && (complain & tf_warning))
1342 switch (implicit)
1344 case ICV_CAST:
1345 warning_at (loc, 0, "conversion to void will not access "
1346 "object %qE of incomplete type %qT", expr, type);
1347 break;
1348 case ICV_SECOND_OF_COND:
1349 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1350 "not be accessed in second operand of "
1351 "conditional expression", expr, type);
1352 break;
1353 case ICV_THIRD_OF_COND:
1354 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1355 "not be accessed in third operand of "
1356 "conditional expression", expr, type);
1357 break;
1358 case ICV_RIGHT_OF_COMMA:
1359 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1360 "not be accessed in right operand of comma operator",
1361 expr, type);
1362 break;
1363 case ICV_LEFT_OF_COMMA:
1364 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1365 "not be accessed in left operand of comma operator",
1366 expr, type);
1367 break;
1368 case ICV_STATEMENT:
1369 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1370 "not be accessed in statement", expr, type);
1371 break;
1372 case ICV_THIRD_IN_FOR:
1373 warning_at (loc, 0, "variable %qE of incomplete type %qT will "
1374 "not be accessed in for increment expression",
1375 expr, type);
1376 break;
1377 default:
1378 gcc_unreachable ();
1381 break;
1384 case TARGET_EXPR:
1385 /* Don't bother with the temporary object returned from a function if
1386 we don't use it, don't need to destroy it, and won't abort in
1387 assign_temp. We'll still
1388 allocate space for it in expand_call or declare_return_variable,
1389 but we don't need to track it through all the tree phases. */
1390 if (TARGET_EXPR_IMPLICIT_P (expr)
1391 && !TREE_ADDRESSABLE (TREE_TYPE (expr)))
1393 tree init = TARGET_EXPR_INITIAL (expr);
1394 if (TREE_CODE (init) == AGGR_INIT_EXPR
1395 && !AGGR_INIT_VIA_CTOR_P (init))
1397 tree fn = AGGR_INIT_EXPR_FN (init);
1398 expr = build_call_array_loc (input_location,
1399 TREE_TYPE (TREE_TYPE
1400 (TREE_TYPE (fn))),
1402 aggr_init_expr_nargs (init),
1403 AGGR_INIT_EXPR_ARGP (init));
1406 maybe_warn_nodiscard (expr, implicit);
1407 break;
1409 default:;
1411 expr = resolve_nondeduced_context (expr, complain);
1413 tree probe = expr;
1415 if (TREE_CODE (probe) == ADDR_EXPR)
1416 probe = TREE_OPERAND (expr, 0);
1417 if (type_unknown_p (probe))
1419 /* [over.over] enumerates the places where we can take the address
1420 of an overloaded function, and this is not one of them. */
1421 if (complain & tf_error)
1422 switch (implicit)
1424 case ICV_CAST:
1425 error_at (loc, "conversion to void "
1426 "cannot resolve address of overloaded function");
1427 break;
1428 case ICV_SECOND_OF_COND:
1429 error_at (loc, "second operand of conditional expression "
1430 "cannot resolve address of overloaded function");
1431 break;
1432 case ICV_THIRD_OF_COND:
1433 error_at (loc, "third operand of conditional expression "
1434 "cannot resolve address of overloaded function");
1435 break;
1436 case ICV_RIGHT_OF_COMMA:
1437 error_at (loc, "right operand of comma operator "
1438 "cannot resolve address of overloaded function");
1439 break;
1440 case ICV_LEFT_OF_COMMA:
1441 error_at (loc, "left operand of comma operator "
1442 "cannot resolve address of overloaded function");
1443 break;
1444 case ICV_STATEMENT:
1445 error_at (loc, "statement "
1446 "cannot resolve address of overloaded function");
1447 break;
1448 case ICV_THIRD_IN_FOR:
1449 error_at (loc, "for increment expression "
1450 "cannot resolve address of overloaded function");
1451 break;
1453 else
1454 return error_mark_node;
1455 expr = void_node;
1457 else if (implicit != ICV_CAST && probe == expr && is_overloaded_fn (probe))
1459 /* Only warn when there is no &. */
1460 if (complain & tf_warning)
1461 switch (implicit)
1463 case ICV_SECOND_OF_COND:
1464 warning_at (loc, OPT_Waddress,
1465 "second operand of conditional expression "
1466 "is a reference, not call, to function %qE", expr);
1467 break;
1468 case ICV_THIRD_OF_COND:
1469 warning_at (loc, OPT_Waddress,
1470 "third operand of conditional expression "
1471 "is a reference, not call, to function %qE", expr);
1472 break;
1473 case ICV_RIGHT_OF_COMMA:
1474 warning_at (loc, OPT_Waddress,
1475 "right operand of comma operator "
1476 "is a reference, not call, to function %qE", expr);
1477 break;
1478 case ICV_LEFT_OF_COMMA:
1479 warning_at (loc, OPT_Waddress,
1480 "left operand of comma operator "
1481 "is a reference, not call, to function %qE", expr);
1482 break;
1483 case ICV_STATEMENT:
1484 warning_at (loc, OPT_Waddress,
1485 "statement is a reference, not call, to function %qE",
1486 expr);
1487 break;
1488 case ICV_THIRD_IN_FOR:
1489 warning_at (loc, OPT_Waddress,
1490 "for increment expression "
1491 "is a reference, not call, to function %qE", expr);
1492 break;
1493 default:
1494 gcc_unreachable ();
1497 if (TREE_CODE (expr) == COMPONENT_REF)
1498 expr = TREE_OPERAND (expr, 0);
1502 if (expr != error_mark_node && !VOID_TYPE_P (TREE_TYPE (expr)))
1504 if (implicit != ICV_CAST
1505 && warn_unused_value
1506 && !TREE_NO_WARNING (expr)
1507 && !processing_template_decl)
1509 /* The middle end does not warn about expressions that have
1510 been explicitly cast to void, so we must do so here. */
1511 if (!TREE_SIDE_EFFECTS (expr)) {
1512 if (complain & tf_warning)
1513 switch (implicit)
1515 case ICV_SECOND_OF_COND:
1516 warning_at (loc, OPT_Wunused_value,
1517 "second operand of conditional expression "
1518 "has no effect");
1519 break;
1520 case ICV_THIRD_OF_COND:
1521 warning_at (loc, OPT_Wunused_value,
1522 "third operand of conditional expression "
1523 "has no effect");
1524 break;
1525 case ICV_RIGHT_OF_COMMA:
1526 warning_at (loc, OPT_Wunused_value,
1527 "right operand of comma operator has no effect");
1528 break;
1529 case ICV_LEFT_OF_COMMA:
1530 warning_at (loc, OPT_Wunused_value,
1531 "left operand of comma operator has no effect");
1532 break;
1533 case ICV_STATEMENT:
1534 warning_at (loc, OPT_Wunused_value,
1535 "statement has no effect");
1536 break;
1537 case ICV_THIRD_IN_FOR:
1538 warning_at (loc, OPT_Wunused_value,
1539 "for increment expression has no effect");
1540 break;
1541 default:
1542 gcc_unreachable ();
1545 else
1547 tree e;
1548 enum tree_code code;
1549 enum tree_code_class tclass;
1551 e = expr;
1552 /* We might like to warn about (say) "(int) f()", as the
1553 cast has no effect, but the compiler itself will
1554 generate implicit conversions under some
1555 circumstances. (For example a block copy will be
1556 turned into a call to "__builtin_memcpy", with a
1557 conversion of the return value to an appropriate
1558 type.) So, to avoid false positives, we strip
1559 conversions. Do not use STRIP_NOPs because it will
1560 not strip conversions to "void", as that is not a
1561 mode-preserving conversion. */
1562 while (TREE_CODE (e) == NOP_EXPR)
1563 e = TREE_OPERAND (e, 0);
1565 code = TREE_CODE (e);
1566 tclass = TREE_CODE_CLASS (code);
1567 if ((tclass == tcc_comparison
1568 || tclass == tcc_unary
1569 || (tclass == tcc_binary
1570 && !(code == MODIFY_EXPR
1571 || code == INIT_EXPR
1572 || code == PREDECREMENT_EXPR
1573 || code == PREINCREMENT_EXPR
1574 || code == POSTDECREMENT_EXPR
1575 || code == POSTINCREMENT_EXPR))
1576 || code == VEC_PERM_EXPR
1577 || code == VEC_COND_EXPR)
1578 && (complain & tf_warning))
1579 warning_at (loc, OPT_Wunused_value, "value computed is not used");
1582 expr = build1 (CONVERT_EXPR, void_type_node, expr);
1584 if (! TREE_SIDE_EFFECTS (expr))
1585 expr = void_node;
1586 return expr;
1589 /* Create an expression whose value is that of EXPR,
1590 converted to type TYPE. The TREE_TYPE of the value
1591 is always TYPE. This function implements all reasonable
1592 conversions; callers should filter out those that are
1593 not permitted by the language being compiled.
1595 Most of this routine is from build_reinterpret_cast.
1597 The back end cannot call cp_convert (what was convert) because
1598 conversions to/from basetypes may involve memory references
1599 (vbases) and adding or subtracting small values (multiple
1600 inheritance), but it calls convert from the constant folding code
1601 on subtrees of already built trees after it has ripped them apart.
1603 Also, if we ever support range variables, we'll probably also have to
1604 do a little bit more work. */
1606 tree
1607 convert (tree type, tree expr)
1609 tree intype;
1611 if (type == error_mark_node || expr == error_mark_node)
1612 return error_mark_node;
1614 intype = TREE_TYPE (expr);
1616 if (INDIRECT_TYPE_P (type) && INDIRECT_TYPE_P (intype))
1617 return build_nop (type, expr);
1619 return ocp_convert (type, expr, CONV_BACKEND_CONVERT,
1620 LOOKUP_NORMAL|LOOKUP_NO_CONVERSION,
1621 tf_warning_or_error);
1624 /* Like cp_convert, except permit conversions to take place which
1625 are not normally allowed due to access restrictions
1626 (such as conversion from sub-type to private super-type). */
1628 tree
1629 convert_force (tree type, tree expr, int convtype, tsubst_flags_t complain)
1631 tree e = expr;
1632 enum tree_code code = TREE_CODE (type);
1634 if (code == REFERENCE_TYPE)
1635 return convert_to_reference (type, e, CONV_C_CAST, 0,
1636 NULL_TREE, complain);
1638 if (code == POINTER_TYPE)
1639 return convert_to_pointer_force (type, e, complain);
1641 /* From typeck.c convert_for_assignment */
1642 if (((TYPE_PTR_P (TREE_TYPE (e)) && TREE_CODE (e) == ADDR_EXPR
1643 && TREE_CODE (TREE_TYPE (TREE_TYPE (e))) == METHOD_TYPE)
1644 || integer_zerop (e)
1645 || TYPE_PTRMEMFUNC_P (TREE_TYPE (e)))
1646 && TYPE_PTRMEMFUNC_P (type))
1647 /* compatible pointer to member functions. */
1648 return build_ptrmemfunc (TYPE_PTRMEMFUNC_FN_TYPE (type), e, 1,
1649 /*c_cast_p=*/1, complain);
1651 return ocp_convert (type, e, CONV_C_CAST|convtype, LOOKUP_NORMAL, complain);
1654 /* Convert an aggregate EXPR to type XTYPE. If a conversion
1655 exists, return the attempted conversion. This may
1656 return ERROR_MARK_NODE if the conversion is not
1657 allowed (references private members, etc).
1658 If no conversion exists, NULL_TREE is returned.
1660 FIXME: Ambiguity checking is wrong. Should choose one by the implicit
1661 object parameter, or by the second standard conversion sequence if
1662 that doesn't do it. This will probably wait for an overloading rewrite.
1663 (jason 8/9/95) */
1665 static tree
1666 build_type_conversion (tree xtype, tree expr)
1668 /* C++: check to see if we can convert this aggregate type
1669 into the required type. */
1670 return build_user_type_conversion (xtype, expr, LOOKUP_NORMAL,
1671 tf_warning_or_error);
1674 /* Convert the given EXPR to one of a group of types suitable for use in an
1675 expression. DESIRES is a combination of various WANT_* flags (q.v.)
1676 which indicates which types are suitable. If COMPLAIN is true, complain
1677 about ambiguity; otherwise, the caller will deal with it. */
1679 tree
1680 build_expr_type_conversion (int desires, tree expr, bool complain)
1682 tree basetype = TREE_TYPE (expr);
1683 tree conv = NULL_TREE;
1684 tree winner = NULL_TREE;
1686 if (null_node_p (expr)
1687 && (desires & WANT_INT)
1688 && !(desires & WANT_NULL))
1690 location_t loc =
1691 expansion_point_location_if_in_system_header (input_location);
1693 warning_at (loc, OPT_Wconversion_null,
1694 "converting NULL to non-pointer type");
1697 if (basetype == error_mark_node)
1698 return error_mark_node;
1700 if (! MAYBE_CLASS_TYPE_P (basetype))
1701 switch (TREE_CODE (basetype))
1703 case INTEGER_TYPE:
1704 if ((desires & WANT_NULL) && null_ptr_cst_p (expr))
1705 return expr;
1706 /* fall through. */
1708 case BOOLEAN_TYPE:
1709 return (desires & WANT_INT) ? expr : NULL_TREE;
1710 case ENUMERAL_TYPE:
1711 return (desires & WANT_ENUM) ? expr : NULL_TREE;
1712 case REAL_TYPE:
1713 return (desires & WANT_FLOAT) ? expr : NULL_TREE;
1714 case POINTER_TYPE:
1715 return (desires & WANT_POINTER) ? expr : NULL_TREE;
1717 case FUNCTION_TYPE:
1718 case ARRAY_TYPE:
1719 return (desires & WANT_POINTER) ? decay_conversion (expr,
1720 tf_warning_or_error)
1721 : NULL_TREE;
1723 case COMPLEX_TYPE:
1724 case VECTOR_TYPE:
1725 if ((desires & WANT_VECTOR_OR_COMPLEX) == 0)
1726 return NULL_TREE;
1727 switch (TREE_CODE (TREE_TYPE (basetype)))
1729 case INTEGER_TYPE:
1730 case BOOLEAN_TYPE:
1731 return (desires & WANT_INT) ? expr : NULL_TREE;
1732 case ENUMERAL_TYPE:
1733 return (desires & WANT_ENUM) ? expr : NULL_TREE;
1734 case REAL_TYPE:
1735 return (desires & WANT_FLOAT) ? expr : NULL_TREE;
1736 default:
1737 return NULL_TREE;
1740 default:
1741 return NULL_TREE;
1744 /* The code for conversions from class type is currently only used for
1745 delete expressions. Other expressions are handled by build_new_op. */
1746 if (!complete_type_or_maybe_complain (basetype, expr, complain))
1747 return error_mark_node;
1748 if (!TYPE_HAS_CONVERSION (basetype))
1749 return NULL_TREE;
1751 for (conv = lookup_conversions (basetype); conv; conv = TREE_CHAIN (conv))
1753 int win = 0;
1754 tree candidate;
1755 tree cand = TREE_VALUE (conv);
1756 cand = OVL_FIRST (cand);
1758 if (winner && winner == cand)
1759 continue;
1761 if (DECL_NONCONVERTING_P (cand))
1762 continue;
1764 candidate = non_reference (TREE_TYPE (TREE_TYPE (cand)));
1766 switch (TREE_CODE (candidate))
1768 case BOOLEAN_TYPE:
1769 case INTEGER_TYPE:
1770 win = (desires & WANT_INT); break;
1771 case ENUMERAL_TYPE:
1772 win = (desires & WANT_ENUM); break;
1773 case REAL_TYPE:
1774 win = (desires & WANT_FLOAT); break;
1775 case POINTER_TYPE:
1776 win = (desires & WANT_POINTER); break;
1778 case COMPLEX_TYPE:
1779 case VECTOR_TYPE:
1780 if ((desires & WANT_VECTOR_OR_COMPLEX) == 0)
1781 break;
1782 switch (TREE_CODE (TREE_TYPE (candidate)))
1784 case BOOLEAN_TYPE:
1785 case INTEGER_TYPE:
1786 win = (desires & WANT_INT); break;
1787 case ENUMERAL_TYPE:
1788 win = (desires & WANT_ENUM); break;
1789 case REAL_TYPE:
1790 win = (desires & WANT_FLOAT); break;
1791 default:
1792 break;
1794 break;
1796 default:
1797 /* A wildcard could be instantiated to match any desired
1798 type, but we can't deduce the template argument. */
1799 if (WILDCARD_TYPE_P (candidate))
1800 win = true;
1801 break;
1804 if (win)
1806 if (TREE_CODE (cand) == TEMPLATE_DECL)
1808 if (complain)
1809 error ("default type conversion can't deduce template"
1810 " argument for %qD", cand);
1811 return error_mark_node;
1814 if (winner)
1816 tree winner_type
1817 = non_reference (TREE_TYPE (TREE_TYPE (winner)));
1819 if (!same_type_ignoring_top_level_qualifiers_p (winner_type,
1820 candidate))
1822 if (complain)
1824 error ("ambiguous default type conversion from %qT",
1825 basetype);
1826 inform (input_location,
1827 " candidate conversions include %qD and %qD",
1828 winner, cand);
1830 return error_mark_node;
1834 winner = cand;
1838 if (winner)
1840 tree type = non_reference (TREE_TYPE (TREE_TYPE (winner)));
1841 return build_user_type_conversion (type, expr, LOOKUP_NORMAL,
1842 tf_warning_or_error);
1845 return NULL_TREE;
1848 /* Implements integral promotion (4.1) and float->double promotion. */
1850 tree
1851 type_promotes_to (tree type)
1853 tree promoted_type;
1855 if (type == error_mark_node)
1856 return error_mark_node;
1858 type = TYPE_MAIN_VARIANT (type);
1860 /* Check for promotions of target-defined types first. */
1861 promoted_type = targetm.promoted_type (type);
1862 if (promoted_type)
1863 return promoted_type;
1865 /* bool always promotes to int (not unsigned), even if it's the same
1866 size. */
1867 if (TREE_CODE (type) == BOOLEAN_TYPE)
1868 type = integer_type_node;
1870 /* Normally convert enums to int, but convert wide enums to something
1871 wider. Scoped enums don't promote, but pretend they do for backward
1872 ABI bug compatibility wrt varargs. */
1873 else if (TREE_CODE (type) == ENUMERAL_TYPE
1874 || type == char16_type_node
1875 || type == char32_type_node
1876 || type == wchar_type_node)
1878 tree prom = type;
1880 if (TREE_CODE (type) == ENUMERAL_TYPE)
1882 prom = ENUM_UNDERLYING_TYPE (prom);
1883 if (!ENUM_IS_SCOPED (type)
1884 && ENUM_FIXED_UNDERLYING_TYPE_P (type))
1886 /* ISO C++17, 7.6/4. A prvalue of an unscoped enumeration type
1887 whose underlying type is fixed (10.2) can be converted to a
1888 prvalue of its underlying type. Moreover, if integral promotion
1889 can be applied to its underlying type, a prvalue of an unscoped
1890 enumeration type whose underlying type is fixed can also be
1891 converted to a prvalue of the promoted underlying type. */
1892 return type_promotes_to (prom);
1896 int precision = MAX (TYPE_PRECISION (type),
1897 TYPE_PRECISION (integer_type_node));
1898 tree totype = c_common_type_for_size (precision, 0);
1899 if (TYPE_UNSIGNED (prom)
1900 && ! int_fits_type_p (TYPE_MAX_VALUE (prom), totype))
1901 prom = c_common_type_for_size (precision, 1);
1902 else
1903 prom = totype;
1904 if (SCOPED_ENUM_P (type))
1906 if (abi_version_crosses (6)
1907 && TYPE_MODE (prom) != TYPE_MODE (type))
1908 warning (OPT_Wabi, "scoped enum %qT passed through ... as "
1909 "%qT before -fabi-version=6, %qT after",
1910 type, prom, ENUM_UNDERLYING_TYPE (type));
1911 if (!abi_version_at_least (6))
1912 type = prom;
1914 else
1915 type = prom;
1917 else if (c_promoting_integer_type_p (type))
1919 /* Retain unsignedness if really not getting bigger. */
1920 if (TYPE_UNSIGNED (type)
1921 && TYPE_PRECISION (type) == TYPE_PRECISION (integer_type_node))
1922 type = unsigned_type_node;
1923 else
1924 type = integer_type_node;
1926 else if (type == float_type_node)
1927 type = double_type_node;
1929 return type;
1932 /* The routines below this point are carefully written to conform to
1933 the standard. They use the same terminology, and follow the rules
1934 closely. Although they are used only in pt.c at the moment, they
1935 should presumably be used everywhere in the future. */
1937 /* True iff EXPR can be converted to TYPE via a qualification conversion.
1938 Callers should check for identical types before calling this function. */
1940 bool
1941 can_convert_qual (tree type, tree expr)
1943 tree expr_type = TREE_TYPE (expr);
1944 gcc_assert (!same_type_p (type, expr_type));
1946 if (TYPE_PTR_P (type) && TYPE_PTR_P (expr_type))
1947 return comp_ptr_ttypes (TREE_TYPE (type), TREE_TYPE (expr_type));
1948 else if (TYPE_PTRMEM_P (type) && TYPE_PTRMEM_P (expr_type))
1949 return (same_type_p (TYPE_PTRMEM_CLASS_TYPE (type),
1950 TYPE_PTRMEM_CLASS_TYPE (expr_type))
1951 && comp_ptr_ttypes (TYPE_PTRMEM_POINTED_TO_TYPE (type),
1952 TYPE_PTRMEM_POINTED_TO_TYPE (expr_type)));
1953 else
1954 return false;
1957 /* Attempt to perform qualification conversions on EXPR to convert it
1958 to TYPE. Return the resulting expression, or error_mark_node if
1959 the conversion was impossible. Since this is only used by
1960 convert_nontype_argument, we fold the conversion. */
1962 tree
1963 perform_qualification_conversions (tree type, tree expr)
1965 tree expr_type;
1967 expr_type = TREE_TYPE (expr);
1969 if (same_type_p (type, expr_type))
1970 return expr;
1971 else if (can_convert_qual (type, expr))
1972 return cp_fold_convert (type, expr);
1973 else
1974 return error_mark_node;
1977 /* True iff T is a transaction-safe function type. */
1979 bool
1980 tx_safe_fn_type_p (tree t)
1982 if (TREE_CODE (t) != FUNCTION_TYPE
1983 && TREE_CODE (t) != METHOD_TYPE)
1984 return false;
1985 return !!lookup_attribute ("transaction_safe", TYPE_ATTRIBUTES (t));
1988 /* Return the transaction-unsafe variant of transaction-safe function type
1989 T. */
1991 tree
1992 tx_unsafe_fn_variant (tree t)
1994 gcc_assert (tx_safe_fn_type_p (t));
1995 tree attrs = remove_attribute ("transaction_safe",
1996 TYPE_ATTRIBUTES (t));
1997 return cp_build_type_attribute_variant (t, attrs);
2000 /* Return true iff FROM can convert to TO by a transaction-safety
2001 conversion. */
2003 static bool
2004 can_convert_tx_safety (tree to, tree from)
2006 return (flag_tm && tx_safe_fn_type_p (from)
2007 && same_type_p (to, tx_unsafe_fn_variant (from)));
2010 /* Return true iff FROM can convert to TO by dropping noexcept. */
2012 static bool
2013 noexcept_conv_p (tree to, tree from)
2015 if (!flag_noexcept_type)
2016 return false;
2018 tree t = non_reference (to);
2019 tree f = from;
2020 if (TYPE_PTRMEMFUNC_P (t)
2021 && TYPE_PTRMEMFUNC_P (f))
2023 t = TYPE_PTRMEMFUNC_FN_TYPE (t);
2024 f = TYPE_PTRMEMFUNC_FN_TYPE (f);
2026 if (TYPE_PTR_P (t)
2027 && TYPE_PTR_P (f))
2029 t = TREE_TYPE (t);
2030 f = TREE_TYPE (f);
2032 tree_code code = TREE_CODE (f);
2033 if (TREE_CODE (t) != code)
2034 return false;
2035 if (code != FUNCTION_TYPE && code != METHOD_TYPE)
2036 return false;
2037 if (!type_throw_all_p (t)
2038 || type_throw_all_p (f))
2039 return false;
2040 tree v = build_exception_variant (f, NULL_TREE);
2041 return same_type_p (t, v);
2044 /* Return true iff FROM can convert to TO by a function pointer conversion. */
2046 bool
2047 fnptr_conv_p (tree to, tree from)
2049 tree t = non_reference (to);
2050 tree f = from;
2051 if (TYPE_PTRMEMFUNC_P (t)
2052 && TYPE_PTRMEMFUNC_P (f))
2054 t = TYPE_PTRMEMFUNC_FN_TYPE (t);
2055 f = TYPE_PTRMEMFUNC_FN_TYPE (f);
2057 if (TYPE_PTR_P (t)
2058 && TYPE_PTR_P (f))
2060 t = TREE_TYPE (t);
2061 f = TREE_TYPE (f);
2064 return (noexcept_conv_p (t, f)
2065 || can_convert_tx_safety (t, f));
2068 /* Return FN with any NOP_EXPRs stripped that represent function pointer
2069 conversions or conversions to the same type. */
2071 tree
2072 strip_fnptr_conv (tree fn)
2074 while (TREE_CODE (fn) == NOP_EXPR)
2076 tree op = TREE_OPERAND (fn, 0);
2077 tree ft = TREE_TYPE (fn);
2078 tree ot = TREE_TYPE (op);
2079 if (same_type_p (ft, ot)
2080 || fnptr_conv_p (ft, ot))
2081 fn = op;
2082 else
2083 break;
2085 return fn;