xref: /dflybsd-src/contrib/gcc-8.0/gcc/cp/lambda.c (revision 38fd149817dfbff97799f62fcb70be98c4e32523)
1*38fd1498Szrj /* Perform the semantic phase of lambda parsing, i.e., the process of
2*38fd1498Szrj    building tree structure, checking semantic consistency, and
3*38fd1498Szrj    building RTL.  These routines are used both during actual parsing
4*38fd1498Szrj    and during the instantiation of template functions.
5*38fd1498Szrj 
6*38fd1498Szrj    Copyright (C) 1998-2018 Free Software Foundation, Inc.
7*38fd1498Szrj 
8*38fd1498Szrj    This file is part of GCC.
9*38fd1498Szrj 
10*38fd1498Szrj    GCC is free software; you can redistribute it and/or modify it
11*38fd1498Szrj    under the terms of the GNU General Public License as published by
12*38fd1498Szrj    the Free Software Foundation; either version 3, or (at your option)
13*38fd1498Szrj    any later version.
14*38fd1498Szrj 
15*38fd1498Szrj    GCC is distributed in the hope that it will be useful, but
16*38fd1498Szrj    WITHOUT ANY WARRANTY; without even the implied warranty of
17*38fd1498Szrj    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18*38fd1498Szrj    General Public License for more details.
19*38fd1498Szrj 
20*38fd1498Szrj You should have received a copy of the GNU General Public License
21*38fd1498Szrj along with GCC; see the file COPYING3.  If not see
22*38fd1498Szrj <http://www.gnu.org/licenses/>.  */
23*38fd1498Szrj 
24*38fd1498Szrj #include "config.h"
25*38fd1498Szrj #include "system.h"
26*38fd1498Szrj #include "coretypes.h"
27*38fd1498Szrj #include "cp-tree.h"
28*38fd1498Szrj #include "stringpool.h"
29*38fd1498Szrj #include "cgraph.h"
30*38fd1498Szrj #include "tree-iterator.h"
31*38fd1498Szrj #include "toplev.h"
32*38fd1498Szrj #include "gimplify.h"
33*38fd1498Szrj 
34*38fd1498Szrj /* Constructor for a lambda expression.  */
35*38fd1498Szrj 
36*38fd1498Szrj tree
37*38fd1498Szrj build_lambda_expr (void)
38*38fd1498Szrj {
39*38fd1498Szrj   tree lambda = make_node (LAMBDA_EXPR);
40*38fd1498Szrj   LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (lambda) = CPLD_NONE;
41*38fd1498Szrj   LAMBDA_EXPR_CAPTURE_LIST         (lambda) = NULL_TREE;
42*38fd1498Szrj   LAMBDA_EXPR_THIS_CAPTURE         (lambda) = NULL_TREE;
43*38fd1498Szrj   LAMBDA_EXPR_PENDING_PROXIES      (lambda) = NULL;
44*38fd1498Szrj   LAMBDA_EXPR_MUTABLE_P            (lambda) = false;
45*38fd1498Szrj   return lambda;
46*38fd1498Szrj }
47*38fd1498Szrj 
48*38fd1498Szrj /* Create the closure object for a LAMBDA_EXPR.  */
49*38fd1498Szrj 
50*38fd1498Szrj tree
51*38fd1498Szrj build_lambda_object (tree lambda_expr)
52*38fd1498Szrj {
53*38fd1498Szrj   /* Build aggregate constructor call.
54*38fd1498Szrj      - cp_parser_braced_list
55*38fd1498Szrj      - cp_parser_functional_cast  */
56*38fd1498Szrj   vec<constructor_elt, va_gc> *elts = NULL;
57*38fd1498Szrj   tree node, expr, type;
58*38fd1498Szrj   location_t saved_loc;
59*38fd1498Szrj 
60*38fd1498Szrj   if (processing_template_decl || lambda_expr == error_mark_node)
61*38fd1498Szrj     return lambda_expr;
62*38fd1498Szrj 
63*38fd1498Szrj   /* Make sure any error messages refer to the lambda-introducer.  */
64*38fd1498Szrj   saved_loc = input_location;
65*38fd1498Szrj   input_location = LAMBDA_EXPR_LOCATION (lambda_expr);
66*38fd1498Szrj 
67*38fd1498Szrj   for (node = LAMBDA_EXPR_CAPTURE_LIST (lambda_expr);
68*38fd1498Szrj        node;
69*38fd1498Szrj        node = TREE_CHAIN (node))
70*38fd1498Szrj     {
71*38fd1498Szrj       tree field = TREE_PURPOSE (node);
72*38fd1498Szrj       tree val = TREE_VALUE (node);
73*38fd1498Szrj 
74*38fd1498Szrj       if (field == error_mark_node)
75*38fd1498Szrj 	{
76*38fd1498Szrj 	  expr = error_mark_node;
77*38fd1498Szrj 	  goto out;
78*38fd1498Szrj 	}
79*38fd1498Szrj 
80*38fd1498Szrj       if (TREE_CODE (val) == TREE_LIST)
81*38fd1498Szrj 	val = build_x_compound_expr_from_list (val, ELK_INIT,
82*38fd1498Szrj 					       tf_warning_or_error);
83*38fd1498Szrj 
84*38fd1498Szrj       if (DECL_P (val))
85*38fd1498Szrj 	mark_used (val);
86*38fd1498Szrj 
87*38fd1498Szrj       /* Mere mortals can't copy arrays with aggregate initialization, so
88*38fd1498Szrj 	 do some magic to make it work here.  */
89*38fd1498Szrj       if (TREE_CODE (TREE_TYPE (field)) == ARRAY_TYPE)
90*38fd1498Szrj 	val = build_array_copy (val);
91*38fd1498Szrj       else if (DECL_NORMAL_CAPTURE_P (field)
92*38fd1498Szrj 	       && !DECL_VLA_CAPTURE_P (field)
93*38fd1498Szrj 	       && TREE_CODE (TREE_TYPE (field)) != REFERENCE_TYPE)
94*38fd1498Szrj 	{
95*38fd1498Szrj 	  /* "the entities that are captured by copy are used to
96*38fd1498Szrj 	     direct-initialize each corresponding non-static data
97*38fd1498Szrj 	     member of the resulting closure object."
98*38fd1498Szrj 
99*38fd1498Szrj 	     There's normally no way to express direct-initialization
100*38fd1498Szrj 	     from an element of a CONSTRUCTOR, so we build up a special
101*38fd1498Szrj 	     TARGET_EXPR to bypass the usual copy-initialization.  */
102*38fd1498Szrj 	  val = force_rvalue (val, tf_warning_or_error);
103*38fd1498Szrj 	  if (TREE_CODE (val) == TARGET_EXPR)
104*38fd1498Szrj 	    TARGET_EXPR_DIRECT_INIT_P (val) = true;
105*38fd1498Szrj 	}
106*38fd1498Szrj 
107*38fd1498Szrj       CONSTRUCTOR_APPEND_ELT (elts, DECL_NAME (field), val);
108*38fd1498Szrj     }
109*38fd1498Szrj 
110*38fd1498Szrj   expr = build_constructor (init_list_type_node, elts);
111*38fd1498Szrj   CONSTRUCTOR_IS_DIRECT_INIT (expr) = 1;
112*38fd1498Szrj 
113*38fd1498Szrj   /* N2927: "[The closure] class type is not an aggregate."
114*38fd1498Szrj      But we briefly treat it as an aggregate to make this simpler.  */
115*38fd1498Szrj   type = LAMBDA_EXPR_CLOSURE (lambda_expr);
116*38fd1498Szrj   CLASSTYPE_NON_AGGREGATE (type) = 0;
117*38fd1498Szrj   expr = finish_compound_literal (type, expr, tf_warning_or_error);
118*38fd1498Szrj   CLASSTYPE_NON_AGGREGATE (type) = 1;
119*38fd1498Szrj 
120*38fd1498Szrj  out:
121*38fd1498Szrj   input_location = saved_loc;
122*38fd1498Szrj   return expr;
123*38fd1498Szrj }
124*38fd1498Szrj 
125*38fd1498Szrj /* Return an initialized RECORD_TYPE for LAMBDA.
126*38fd1498Szrj    LAMBDA must have its explicit captures already.  */
127*38fd1498Szrj 
128*38fd1498Szrj tree
129*38fd1498Szrj begin_lambda_type (tree lambda)
130*38fd1498Szrj {
131*38fd1498Szrj   tree type;
132*38fd1498Szrj 
133*38fd1498Szrj   {
134*38fd1498Szrj     /* Unique name.  This is just like an unnamed class, but we cannot use
135*38fd1498Szrj        make_anon_name because of certain checks against TYPE_UNNAMED_P.  */
136*38fd1498Szrj     tree name;
137*38fd1498Szrj     name = make_lambda_name ();
138*38fd1498Szrj 
139*38fd1498Szrj     /* Create the new RECORD_TYPE for this lambda.  */
140*38fd1498Szrj     type = xref_tag (/*tag_code=*/record_type,
141*38fd1498Szrj                      name,
142*38fd1498Szrj                      /*scope=*/ts_lambda,
143*38fd1498Szrj                      /*template_header_p=*/false);
144*38fd1498Szrj     if (type == error_mark_node)
145*38fd1498Szrj       return error_mark_node;
146*38fd1498Szrj   }
147*38fd1498Szrj 
148*38fd1498Szrj   /* Designate it as a struct so that we can use aggregate initialization.  */
149*38fd1498Szrj   CLASSTYPE_DECLARED_CLASS (type) = false;
150*38fd1498Szrj 
151*38fd1498Szrj   /* Cross-reference the expression and the type.  */
152*38fd1498Szrj   LAMBDA_EXPR_CLOSURE (lambda) = type;
153*38fd1498Szrj   CLASSTYPE_LAMBDA_EXPR (type) = lambda;
154*38fd1498Szrj 
155*38fd1498Szrj   /* In C++17, assume the closure is literal; we'll clear the flag later if
156*38fd1498Szrj      necessary.  */
157*38fd1498Szrj   if (cxx_dialect >= cxx17)
158*38fd1498Szrj     CLASSTYPE_LITERAL_P (type) = true;
159*38fd1498Szrj 
160*38fd1498Szrj   /* Clear base types.  */
161*38fd1498Szrj   xref_basetypes (type, /*bases=*/NULL_TREE);
162*38fd1498Szrj 
163*38fd1498Szrj   /* Start the class.  */
164*38fd1498Szrj   type = begin_class_definition (type);
165*38fd1498Szrj 
166*38fd1498Szrj   return type;
167*38fd1498Szrj }
168*38fd1498Szrj 
169*38fd1498Szrj /* Returns the type to use for the return type of the operator() of a
170*38fd1498Szrj    closure class.  */
171*38fd1498Szrj 
172*38fd1498Szrj tree
173*38fd1498Szrj lambda_return_type (tree expr)
174*38fd1498Szrj {
175*38fd1498Szrj   if (expr == NULL_TREE)
176*38fd1498Szrj     return void_type_node;
177*38fd1498Szrj   if (type_unknown_p (expr)
178*38fd1498Szrj       || BRACE_ENCLOSED_INITIALIZER_P (expr))
179*38fd1498Szrj     {
180*38fd1498Szrj       cxx_incomplete_type_error (expr, TREE_TYPE (expr));
181*38fd1498Szrj       return error_mark_node;
182*38fd1498Szrj     }
183*38fd1498Szrj   gcc_checking_assert (!type_dependent_expression_p (expr));
184*38fd1498Szrj   return cv_unqualified (type_decays_to (unlowered_expr_type (expr)));
185*38fd1498Szrj }
186*38fd1498Szrj 
187*38fd1498Szrj /* Given a LAMBDA_EXPR or closure type LAMBDA, return the op() of the
188*38fd1498Szrj    closure type.  */
189*38fd1498Szrj 
190*38fd1498Szrj tree
191*38fd1498Szrj lambda_function (tree lambda)
192*38fd1498Szrj {
193*38fd1498Szrj   tree type;
194*38fd1498Szrj   if (TREE_CODE (lambda) == LAMBDA_EXPR)
195*38fd1498Szrj     type = LAMBDA_EXPR_CLOSURE (lambda);
196*38fd1498Szrj   else
197*38fd1498Szrj     type = lambda;
198*38fd1498Szrj   gcc_assert (LAMBDA_TYPE_P (type));
199*38fd1498Szrj   /* Don't let debug_tree cause instantiation.  */
200*38fd1498Szrj   if (CLASSTYPE_TEMPLATE_INSTANTIATION (type)
201*38fd1498Szrj       && !COMPLETE_OR_OPEN_TYPE_P (type))
202*38fd1498Szrj     return NULL_TREE;
203*38fd1498Szrj   lambda = lookup_member (type, call_op_identifier,
204*38fd1498Szrj 			  /*protect=*/0, /*want_type=*/false,
205*38fd1498Szrj 			  tf_warning_or_error);
206*38fd1498Szrj   if (lambda)
207*38fd1498Szrj     lambda = STRIP_TEMPLATE (get_first_fn (lambda));
208*38fd1498Szrj   return lambda;
209*38fd1498Szrj }
210*38fd1498Szrj 
211*38fd1498Szrj /* Returns the type to use for the FIELD_DECL corresponding to the
212*38fd1498Szrj    capture of EXPR.  EXPLICIT_INIT_P indicates whether this is a
213*38fd1498Szrj    C++14 init capture, and BY_REFERENCE_P indicates whether we're
214*38fd1498Szrj    capturing by reference.  */
215*38fd1498Szrj 
216*38fd1498Szrj tree
217*38fd1498Szrj lambda_capture_field_type (tree expr, bool explicit_init_p,
218*38fd1498Szrj 			   bool by_reference_p)
219*38fd1498Szrj {
220*38fd1498Szrj   tree type;
221*38fd1498Szrj   bool is_this = is_this_parameter (tree_strip_nop_conversions (expr));
222*38fd1498Szrj 
223*38fd1498Szrj   if (!is_this && type_dependent_expression_p (expr))
224*38fd1498Szrj     {
225*38fd1498Szrj       type = cxx_make_type (DECLTYPE_TYPE);
226*38fd1498Szrj       DECLTYPE_TYPE_EXPR (type) = expr;
227*38fd1498Szrj       DECLTYPE_FOR_LAMBDA_CAPTURE (type) = true;
228*38fd1498Szrj       DECLTYPE_FOR_INIT_CAPTURE (type) = explicit_init_p;
229*38fd1498Szrj       DECLTYPE_FOR_REF_CAPTURE (type) = by_reference_p;
230*38fd1498Szrj       SET_TYPE_STRUCTURAL_EQUALITY (type);
231*38fd1498Szrj     }
232*38fd1498Szrj   else if (!is_this && explicit_init_p)
233*38fd1498Szrj     {
234*38fd1498Szrj       tree auto_node = make_auto ();
235*38fd1498Szrj 
236*38fd1498Szrj       type = auto_node;
237*38fd1498Szrj       if (by_reference_p)
238*38fd1498Szrj 	/* Add the reference now, so deduction doesn't lose
239*38fd1498Szrj 	   outermost CV qualifiers of EXPR.  */
240*38fd1498Szrj 	type = build_reference_type (type);
241*38fd1498Szrj       type = do_auto_deduction (type, expr, auto_node);
242*38fd1498Szrj     }
243*38fd1498Szrj   else
244*38fd1498Szrj     {
245*38fd1498Szrj       type = non_reference (unlowered_expr_type (expr));
246*38fd1498Szrj 
247*38fd1498Szrj       if (!is_this
248*38fd1498Szrj 	  && (by_reference_p || TREE_CODE (type) == FUNCTION_TYPE))
249*38fd1498Szrj 	type = build_reference_type (type);
250*38fd1498Szrj     }
251*38fd1498Szrj 
252*38fd1498Szrj   return type;
253*38fd1498Szrj }
254*38fd1498Szrj 
255*38fd1498Szrj /* Returns true iff DECL is a lambda capture proxy variable created by
256*38fd1498Szrj    build_capture_proxy.  */
257*38fd1498Szrj 
258*38fd1498Szrj bool
259*38fd1498Szrj is_capture_proxy (tree decl)
260*38fd1498Szrj {
261*38fd1498Szrj   return (VAR_P (decl)
262*38fd1498Szrj 	  && DECL_HAS_VALUE_EXPR_P (decl)
263*38fd1498Szrj 	  && !DECL_ANON_UNION_VAR_P (decl)
264*38fd1498Szrj 	  && !DECL_DECOMPOSITION_P (decl)
265*38fd1498Szrj 	  && LAMBDA_FUNCTION_P (DECL_CONTEXT (decl)));
266*38fd1498Szrj }
267*38fd1498Szrj 
268*38fd1498Szrj /* Returns true iff DECL is a capture proxy for a normal capture
269*38fd1498Szrj    (i.e. without explicit initializer).  */
270*38fd1498Szrj 
271*38fd1498Szrj bool
272*38fd1498Szrj is_normal_capture_proxy (tree decl)
273*38fd1498Szrj {
274*38fd1498Szrj   if (!is_capture_proxy (decl))
275*38fd1498Szrj     /* It's not a capture proxy.  */
276*38fd1498Szrj     return false;
277*38fd1498Szrj 
278*38fd1498Szrj   if (variably_modified_type_p (TREE_TYPE (decl), NULL_TREE))
279*38fd1498Szrj     /* VLA capture.  */
280*38fd1498Szrj     return true;
281*38fd1498Szrj 
282*38fd1498Szrj   /* It is a capture proxy, is it a normal capture?  */
283*38fd1498Szrj   tree val = DECL_VALUE_EXPR (decl);
284*38fd1498Szrj   if (val == error_mark_node)
285*38fd1498Szrj     return true;
286*38fd1498Szrj 
287*38fd1498Szrj   if (TREE_CODE (val) == ADDR_EXPR)
288*38fd1498Szrj     val = TREE_OPERAND (val, 0);
289*38fd1498Szrj   gcc_assert (TREE_CODE (val) == COMPONENT_REF);
290*38fd1498Szrj   val = TREE_OPERAND (val, 1);
291*38fd1498Szrj   return DECL_NORMAL_CAPTURE_P (val);
292*38fd1498Szrj }
293*38fd1498Szrj 
294*38fd1498Szrj /* Returns true iff DECL is a capture proxy for a normal capture
295*38fd1498Szrj    of a constant variable.  */
296*38fd1498Szrj 
297*38fd1498Szrj bool
298*38fd1498Szrj is_constant_capture_proxy (tree decl)
299*38fd1498Szrj {
300*38fd1498Szrj   if (is_normal_capture_proxy (decl))
301*38fd1498Szrj     return decl_constant_var_p (DECL_CAPTURED_VARIABLE (decl));
302*38fd1498Szrj   return false;
303*38fd1498Szrj }
304*38fd1498Szrj 
305*38fd1498Szrj /* VAR is a capture proxy created by build_capture_proxy; add it to the
306*38fd1498Szrj    current function, which is the operator() for the appropriate lambda.  */
307*38fd1498Szrj 
308*38fd1498Szrj void
309*38fd1498Szrj insert_capture_proxy (tree var)
310*38fd1498Szrj {
311*38fd1498Szrj   if (is_normal_capture_proxy (var))
312*38fd1498Szrj     {
313*38fd1498Szrj       tree cap = DECL_CAPTURED_VARIABLE (var);
314*38fd1498Szrj       if (CHECKING_P)
315*38fd1498Szrj 	{
316*38fd1498Szrj 	  gcc_assert (!is_normal_capture_proxy (cap));
317*38fd1498Szrj 	  tree old = retrieve_local_specialization (cap);
318*38fd1498Szrj 	  if (old)
319*38fd1498Szrj 	    gcc_assert (DECL_CONTEXT (old) != DECL_CONTEXT (var));
320*38fd1498Szrj 	}
321*38fd1498Szrj       register_local_specialization (var, cap);
322*38fd1498Szrj     }
323*38fd1498Szrj 
324*38fd1498Szrj   /* Put the capture proxy in the extra body block so that it won't clash
325*38fd1498Szrj      with a later local variable.  */
326*38fd1498Szrj   pushdecl_outermost_localscope (var);
327*38fd1498Szrj 
328*38fd1498Szrj   /* And put a DECL_EXPR in the STATEMENT_LIST for the same block.  */
329*38fd1498Szrj   var = build_stmt (DECL_SOURCE_LOCATION (var), DECL_EXPR, var);
330*38fd1498Szrj   tree stmt_list = (*stmt_list_stack)[1];
331*38fd1498Szrj   gcc_assert (stmt_list);
332*38fd1498Szrj   append_to_statement_list_force (var, &stmt_list);
333*38fd1498Szrj }
334*38fd1498Szrj 
335*38fd1498Szrj /* We've just finished processing a lambda; if the containing scope is also
336*38fd1498Szrj    a lambda, insert any capture proxies that were created while processing
337*38fd1498Szrj    the nested lambda.  */
338*38fd1498Szrj 
339*38fd1498Szrj void
340*38fd1498Szrj insert_pending_capture_proxies (void)
341*38fd1498Szrj {
342*38fd1498Szrj   tree lam;
343*38fd1498Szrj   vec<tree, va_gc> *proxies;
344*38fd1498Szrj   unsigned i;
345*38fd1498Szrj 
346*38fd1498Szrj   if (!current_function_decl || !LAMBDA_FUNCTION_P (current_function_decl))
347*38fd1498Szrj     return;
348*38fd1498Szrj 
349*38fd1498Szrj   lam = CLASSTYPE_LAMBDA_EXPR (DECL_CONTEXT (current_function_decl));
350*38fd1498Szrj   proxies = LAMBDA_EXPR_PENDING_PROXIES (lam);
351*38fd1498Szrj   for (i = 0; i < vec_safe_length (proxies); ++i)
352*38fd1498Szrj     {
353*38fd1498Szrj       tree var = (*proxies)[i];
354*38fd1498Szrj       insert_capture_proxy (var);
355*38fd1498Szrj     }
356*38fd1498Szrj   release_tree_vector (LAMBDA_EXPR_PENDING_PROXIES (lam));
357*38fd1498Szrj   LAMBDA_EXPR_PENDING_PROXIES (lam) = NULL;
358*38fd1498Szrj }
359*38fd1498Szrj 
360*38fd1498Szrj /* Given REF, a COMPONENT_REF designating a field in the lambda closure,
361*38fd1498Szrj    return the type we want the proxy to have: the type of the field itself,
362*38fd1498Szrj    with added const-qualification if the lambda isn't mutable and the
363*38fd1498Szrj    capture is by value.  */
364*38fd1498Szrj 
365*38fd1498Szrj tree
366*38fd1498Szrj lambda_proxy_type (tree ref)
367*38fd1498Szrj {
368*38fd1498Szrj   tree type;
369*38fd1498Szrj   if (ref == error_mark_node)
370*38fd1498Szrj     return error_mark_node;
371*38fd1498Szrj   if (REFERENCE_REF_P (ref))
372*38fd1498Szrj     ref = TREE_OPERAND (ref, 0);
373*38fd1498Szrj   gcc_assert (TREE_CODE (ref) == COMPONENT_REF);
374*38fd1498Szrj   type = TREE_TYPE (ref);
375*38fd1498Szrj   if (!type || WILDCARD_TYPE_P (non_reference (type)))
376*38fd1498Szrj     {
377*38fd1498Szrj       type = cxx_make_type (DECLTYPE_TYPE);
378*38fd1498Szrj       DECLTYPE_TYPE_EXPR (type) = ref;
379*38fd1498Szrj       DECLTYPE_FOR_LAMBDA_PROXY (type) = true;
380*38fd1498Szrj       SET_TYPE_STRUCTURAL_EQUALITY (type);
381*38fd1498Szrj     }
382*38fd1498Szrj   if (DECL_PACK_P (TREE_OPERAND (ref, 1)))
383*38fd1498Szrj     type = make_pack_expansion (type);
384*38fd1498Szrj   return type;
385*38fd1498Szrj }
386*38fd1498Szrj 
387*38fd1498Szrj /* MEMBER is a capture field in a lambda closure class.  Now that we're
388*38fd1498Szrj    inside the operator(), build a placeholder var for future lookups and
389*38fd1498Szrj    debugging.  */
390*38fd1498Szrj 
391*38fd1498Szrj static tree
392*38fd1498Szrj build_capture_proxy (tree member, tree init)
393*38fd1498Szrj {
394*38fd1498Szrj   tree var, object, fn, closure, name, lam, type;
395*38fd1498Szrj 
396*38fd1498Szrj   if (PACK_EXPANSION_P (member))
397*38fd1498Szrj     member = PACK_EXPANSION_PATTERN (member);
398*38fd1498Szrj 
399*38fd1498Szrj   closure = DECL_CONTEXT (member);
400*38fd1498Szrj   fn = lambda_function (closure);
401*38fd1498Szrj   lam = CLASSTYPE_LAMBDA_EXPR (closure);
402*38fd1498Szrj 
403*38fd1498Szrj   /* The proxy variable forwards to the capture field.  */
404*38fd1498Szrj   object = build_fold_indirect_ref (DECL_ARGUMENTS (fn));
405*38fd1498Szrj   object = finish_non_static_data_member (member, object, NULL_TREE);
406*38fd1498Szrj   if (REFERENCE_REF_P (object))
407*38fd1498Szrj     object = TREE_OPERAND (object, 0);
408*38fd1498Szrj 
409*38fd1498Szrj   /* Remove the __ inserted by add_capture.  */
410*38fd1498Szrj   name = get_identifier (IDENTIFIER_POINTER (DECL_NAME (member)) + 2);
411*38fd1498Szrj 
412*38fd1498Szrj   type = lambda_proxy_type (object);
413*38fd1498Szrj 
414*38fd1498Szrj   if (name == this_identifier && !POINTER_TYPE_P (type))
415*38fd1498Szrj     {
416*38fd1498Szrj       type = build_pointer_type (type);
417*38fd1498Szrj       type = cp_build_qualified_type (type, TYPE_QUAL_CONST);
418*38fd1498Szrj       object = build_fold_addr_expr_with_type (object, type);
419*38fd1498Szrj     }
420*38fd1498Szrj 
421*38fd1498Szrj   if (DECL_VLA_CAPTURE_P (member))
422*38fd1498Szrj     {
423*38fd1498Szrj       /* Rebuild the VLA type from the pointer and maxindex.  */
424*38fd1498Szrj       tree field = next_initializable_field (TYPE_FIELDS (type));
425*38fd1498Szrj       tree ptr = build_simple_component_ref (object, field);
426*38fd1498Szrj       field = next_initializable_field (DECL_CHAIN (field));
427*38fd1498Szrj       tree max = build_simple_component_ref (object, field);
428*38fd1498Szrj       type = build_cplus_array_type (TREE_TYPE (TREE_TYPE (ptr)),
429*38fd1498Szrj 				     build_index_type (max));
430*38fd1498Szrj       type = build_reference_type (type);
431*38fd1498Szrj       REFERENCE_VLA_OK (type) = true;
432*38fd1498Szrj       object = convert (type, ptr);
433*38fd1498Szrj     }
434*38fd1498Szrj 
435*38fd1498Szrj   complete_type (type);
436*38fd1498Szrj 
437*38fd1498Szrj   var = build_decl (input_location, VAR_DECL, name, type);
438*38fd1498Szrj   SET_DECL_VALUE_EXPR (var, object);
439*38fd1498Szrj   DECL_HAS_VALUE_EXPR_P (var) = 1;
440*38fd1498Szrj   DECL_ARTIFICIAL (var) = 1;
441*38fd1498Szrj   TREE_USED (var) = 1;
442*38fd1498Szrj   DECL_CONTEXT (var) = fn;
443*38fd1498Szrj 
444*38fd1498Szrj   if (DECL_NORMAL_CAPTURE_P (member))
445*38fd1498Szrj     {
446*38fd1498Szrj       if (DECL_VLA_CAPTURE_P (member))
447*38fd1498Szrj 	{
448*38fd1498Szrj 	  init = CONSTRUCTOR_ELT (init, 0)->value;
449*38fd1498Szrj 	  init = TREE_OPERAND (init, 0); // Strip ADDR_EXPR.
450*38fd1498Szrj 	  init = TREE_OPERAND (init, 0); // Strip ARRAY_REF.
451*38fd1498Szrj 	}
452*38fd1498Szrj       else
453*38fd1498Szrj 	{
454*38fd1498Szrj 	  if (PACK_EXPANSION_P (init))
455*38fd1498Szrj 	    init = PACK_EXPANSION_PATTERN (init);
456*38fd1498Szrj 	}
457*38fd1498Szrj 
458*38fd1498Szrj       if (INDIRECT_REF_P (init))
459*38fd1498Szrj 	init = TREE_OPERAND (init, 0);
460*38fd1498Szrj       STRIP_NOPS (init);
461*38fd1498Szrj 
462*38fd1498Szrj       gcc_assert (VAR_P (init) || TREE_CODE (init) == PARM_DECL);
463*38fd1498Szrj       while (is_normal_capture_proxy (init))
464*38fd1498Szrj 	init = DECL_CAPTURED_VARIABLE (init);
465*38fd1498Szrj       retrofit_lang_decl (var);
466*38fd1498Szrj       DECL_CAPTURED_VARIABLE (var) = init;
467*38fd1498Szrj     }
468*38fd1498Szrj 
469*38fd1498Szrj   if (name == this_identifier)
470*38fd1498Szrj     {
471*38fd1498Szrj       gcc_assert (LAMBDA_EXPR_THIS_CAPTURE (lam) == member);
472*38fd1498Szrj       LAMBDA_EXPR_THIS_CAPTURE (lam) = var;
473*38fd1498Szrj     }
474*38fd1498Szrj 
475*38fd1498Szrj   if (fn == current_function_decl)
476*38fd1498Szrj     insert_capture_proxy (var);
477*38fd1498Szrj   else
478*38fd1498Szrj     vec_safe_push (LAMBDA_EXPR_PENDING_PROXIES (lam), var);
479*38fd1498Szrj 
480*38fd1498Szrj   return var;
481*38fd1498Szrj }
482*38fd1498Szrj 
483*38fd1498Szrj static GTY(()) tree ptr_id;
484*38fd1498Szrj static GTY(()) tree max_id;
485*38fd1498Szrj 
486*38fd1498Szrj /* Return a struct containing a pointer and a length for lambda capture of
487*38fd1498Szrj    an array of runtime length.  */
488*38fd1498Szrj 
489*38fd1498Szrj static tree
490*38fd1498Szrj vla_capture_type (tree array_type)
491*38fd1498Szrj {
492*38fd1498Szrj   tree type = xref_tag (record_type, make_anon_name (), ts_current, false);
493*38fd1498Szrj   xref_basetypes (type, NULL_TREE);
494*38fd1498Szrj   type = begin_class_definition (type);
495*38fd1498Szrj   if (!ptr_id)
496*38fd1498Szrj     {
497*38fd1498Szrj       ptr_id = get_identifier ("ptr");
498*38fd1498Szrj       max_id = get_identifier ("max");
499*38fd1498Szrj     }
500*38fd1498Szrj   tree ptrtype = build_pointer_type (TREE_TYPE (array_type));
501*38fd1498Szrj   tree field = build_decl (input_location, FIELD_DECL, ptr_id, ptrtype);
502*38fd1498Szrj   finish_member_declaration (field);
503*38fd1498Szrj   field = build_decl (input_location, FIELD_DECL, max_id, sizetype);
504*38fd1498Szrj   finish_member_declaration (field);
505*38fd1498Szrj   return finish_struct (type, NULL_TREE);
506*38fd1498Szrj }
507*38fd1498Szrj 
508*38fd1498Szrj /* From an ID and INITIALIZER, create a capture (by reference if
509*38fd1498Szrj    BY_REFERENCE_P is true), add it to the capture-list for LAMBDA,
510*38fd1498Szrj    and return it.  If ID is `this', BY_REFERENCE_P says whether
511*38fd1498Szrj    `*this' is captured by reference.  */
512*38fd1498Szrj 
513*38fd1498Szrj tree
514*38fd1498Szrj add_capture (tree lambda, tree id, tree orig_init, bool by_reference_p,
515*38fd1498Szrj 	     bool explicit_init_p)
516*38fd1498Szrj {
517*38fd1498Szrj   char *buf;
518*38fd1498Szrj   tree type, member, name;
519*38fd1498Szrj   bool vla = false;
520*38fd1498Szrj   bool variadic = false;
521*38fd1498Szrj   tree initializer = orig_init;
522*38fd1498Szrj 
523*38fd1498Szrj   if (PACK_EXPANSION_P (initializer))
524*38fd1498Szrj     {
525*38fd1498Szrj       initializer = PACK_EXPANSION_PATTERN (initializer);
526*38fd1498Szrj       variadic = true;
527*38fd1498Szrj     }
528*38fd1498Szrj 
529*38fd1498Szrj   if (TREE_CODE (initializer) == TREE_LIST
530*38fd1498Szrj       /* A pack expansion might end up with multiple elements.  */
531*38fd1498Szrj       && !PACK_EXPANSION_P (TREE_VALUE (initializer)))
532*38fd1498Szrj     initializer = build_x_compound_expr_from_list (initializer, ELK_INIT,
533*38fd1498Szrj 						   tf_warning_or_error);
534*38fd1498Szrj   type = TREE_TYPE (initializer);
535*38fd1498Szrj   if (type == error_mark_node)
536*38fd1498Szrj     return error_mark_node;
537*38fd1498Szrj 
538*38fd1498Szrj   if (array_of_runtime_bound_p (type))
539*38fd1498Szrj     {
540*38fd1498Szrj       vla = true;
541*38fd1498Szrj       if (!by_reference_p)
542*38fd1498Szrj 	error ("array of runtime bound cannot be captured by copy, "
543*38fd1498Szrj 	       "only by reference");
544*38fd1498Szrj 
545*38fd1498Szrj       /* For a VLA, we capture the address of the first element and the
546*38fd1498Szrj 	 maximum index, and then reconstruct the VLA for the proxy.  */
547*38fd1498Szrj       tree elt = cp_build_array_ref (input_location, initializer,
548*38fd1498Szrj 				     integer_zero_node, tf_warning_or_error);
549*38fd1498Szrj       initializer = build_constructor_va (init_list_type_node, 2,
550*38fd1498Szrj 					  NULL_TREE, build_address (elt),
551*38fd1498Szrj 					  NULL_TREE, array_type_nelts (type));
552*38fd1498Szrj       type = vla_capture_type (type);
553*38fd1498Szrj     }
554*38fd1498Szrj   else if (!dependent_type_p (type)
555*38fd1498Szrj 	   && variably_modified_type_p (type, NULL_TREE))
556*38fd1498Szrj     {
557*38fd1498Szrj       sorry ("capture of variably-modified type %qT that is not an N3639 array "
558*38fd1498Szrj 	     "of runtime bound", type);
559*38fd1498Szrj       if (TREE_CODE (type) == ARRAY_TYPE
560*38fd1498Szrj 	  && variably_modified_type_p (TREE_TYPE (type), NULL_TREE))
561*38fd1498Szrj 	inform (input_location, "because the array element type %qT has "
562*38fd1498Szrj 		"variable size", TREE_TYPE (type));
563*38fd1498Szrj       return error_mark_node;
564*38fd1498Szrj     }
565*38fd1498Szrj   else
566*38fd1498Szrj     {
567*38fd1498Szrj       type = lambda_capture_field_type (initializer, explicit_init_p,
568*38fd1498Szrj 					by_reference_p);
569*38fd1498Szrj       if (type == error_mark_node)
570*38fd1498Szrj 	return error_mark_node;
571*38fd1498Szrj 
572*38fd1498Szrj       if (id == this_identifier && !by_reference_p)
573*38fd1498Szrj 	{
574*38fd1498Szrj 	  gcc_assert (POINTER_TYPE_P (type));
575*38fd1498Szrj 	  type = TREE_TYPE (type);
576*38fd1498Szrj 	  initializer = cp_build_fold_indirect_ref (initializer);
577*38fd1498Szrj 	}
578*38fd1498Szrj 
579*38fd1498Szrj       if (dependent_type_p (type))
580*38fd1498Szrj 	;
581*38fd1498Szrj       else if (id != this_identifier && by_reference_p)
582*38fd1498Szrj 	{
583*38fd1498Szrj 	  if (!lvalue_p (initializer))
584*38fd1498Szrj 	    {
585*38fd1498Szrj 	      error ("cannot capture %qE by reference", initializer);
586*38fd1498Szrj 	      return error_mark_node;
587*38fd1498Szrj 	    }
588*38fd1498Szrj 	}
589*38fd1498Szrj       else
590*38fd1498Szrj 	{
591*38fd1498Szrj 	  /* Capture by copy requires a complete type.  */
592*38fd1498Szrj 	  type = complete_type (type);
593*38fd1498Szrj 	  if (!COMPLETE_TYPE_P (type))
594*38fd1498Szrj 	    {
595*38fd1498Szrj 	      error ("capture by copy of incomplete type %qT", type);
596*38fd1498Szrj 	      cxx_incomplete_type_inform (type);
597*38fd1498Szrj 	      return error_mark_node;
598*38fd1498Szrj 	    }
599*38fd1498Szrj 	}
600*38fd1498Szrj     }
601*38fd1498Szrj 
602*38fd1498Szrj   /* Add __ to the beginning of the field name so that user code
603*38fd1498Szrj      won't find the field with name lookup.  We can't just leave the name
604*38fd1498Szrj      unset because template instantiation uses the name to find
605*38fd1498Szrj      instantiated fields.  */
606*38fd1498Szrj   buf = (char *) alloca (IDENTIFIER_LENGTH (id) + 3);
607*38fd1498Szrj   buf[1] = buf[0] = '_';
608*38fd1498Szrj   memcpy (buf + 2, IDENTIFIER_POINTER (id),
609*38fd1498Szrj 	  IDENTIFIER_LENGTH (id) + 1);
610*38fd1498Szrj   name = get_identifier (buf);
611*38fd1498Szrj 
612*38fd1498Szrj   /* If TREE_TYPE isn't set, we're still in the introducer, so check
613*38fd1498Szrj      for duplicates.  */
614*38fd1498Szrj   if (!LAMBDA_EXPR_CLOSURE (lambda))
615*38fd1498Szrj     {
616*38fd1498Szrj       if (IDENTIFIER_MARKED (name))
617*38fd1498Szrj 	{
618*38fd1498Szrj 	  pedwarn (input_location, 0,
619*38fd1498Szrj 		   "already captured %qD in lambda expression", id);
620*38fd1498Szrj 	  return NULL_TREE;
621*38fd1498Szrj 	}
622*38fd1498Szrj       IDENTIFIER_MARKED (name) = true;
623*38fd1498Szrj     }
624*38fd1498Szrj 
625*38fd1498Szrj   if (variadic)
626*38fd1498Szrj     type = make_pack_expansion (type);
627*38fd1498Szrj 
628*38fd1498Szrj   /* Make member variable.  */
629*38fd1498Szrj   member = build_decl (input_location, FIELD_DECL, name, type);
630*38fd1498Szrj   DECL_VLA_CAPTURE_P (member) = vla;
631*38fd1498Szrj 
632*38fd1498Szrj   if (!explicit_init_p)
633*38fd1498Szrj     /* Normal captures are invisible to name lookup but uses are replaced
634*38fd1498Szrj        with references to the capture field; we implement this by only
635*38fd1498Szrj        really making them invisible in unevaluated context; see
636*38fd1498Szrj        qualify_lookup.  For now, let's make explicitly initialized captures
637*38fd1498Szrj        always visible.  */
638*38fd1498Szrj     DECL_NORMAL_CAPTURE_P (member) = true;
639*38fd1498Szrj 
640*38fd1498Szrj   if (id == this_identifier)
641*38fd1498Szrj     LAMBDA_EXPR_THIS_CAPTURE (lambda) = member;
642*38fd1498Szrj 
643*38fd1498Szrj   /* Add it to the appropriate closure class if we've started it.  */
644*38fd1498Szrj   if (current_class_type
645*38fd1498Szrj       && current_class_type == LAMBDA_EXPR_CLOSURE (lambda))
646*38fd1498Szrj     {
647*38fd1498Szrj       if (COMPLETE_TYPE_P (current_class_type))
648*38fd1498Szrj 	internal_error ("trying to capture %qD in instantiation of "
649*38fd1498Szrj 			"generic lambda", id);
650*38fd1498Szrj       finish_member_declaration (member);
651*38fd1498Szrj     }
652*38fd1498Szrj 
653*38fd1498Szrj   tree listmem = member;
654*38fd1498Szrj   if (variadic)
655*38fd1498Szrj     {
656*38fd1498Szrj       listmem = make_pack_expansion (member);
657*38fd1498Szrj       initializer = orig_init;
658*38fd1498Szrj     }
659*38fd1498Szrj   LAMBDA_EXPR_CAPTURE_LIST (lambda)
660*38fd1498Szrj     = tree_cons (listmem, initializer, LAMBDA_EXPR_CAPTURE_LIST (lambda));
661*38fd1498Szrj 
662*38fd1498Szrj   if (LAMBDA_EXPR_CLOSURE (lambda))
663*38fd1498Szrj     return build_capture_proxy (member, initializer);
664*38fd1498Szrj   /* For explicit captures we haven't started the function yet, so we wait
665*38fd1498Szrj      and build the proxy from cp_parser_lambda_body.  */
666*38fd1498Szrj   LAMBDA_CAPTURE_EXPLICIT_P (LAMBDA_EXPR_CAPTURE_LIST (lambda)) = true;
667*38fd1498Szrj   return NULL_TREE;
668*38fd1498Szrj }
669*38fd1498Szrj 
670*38fd1498Szrj /* Register all the capture members on the list CAPTURES, which is the
671*38fd1498Szrj    LAMBDA_EXPR_CAPTURE_LIST for the lambda after the introducer.  */
672*38fd1498Szrj 
673*38fd1498Szrj void
674*38fd1498Szrj register_capture_members (tree captures)
675*38fd1498Szrj {
676*38fd1498Szrj   if (captures == NULL_TREE)
677*38fd1498Szrj     return;
678*38fd1498Szrj 
679*38fd1498Szrj   register_capture_members (TREE_CHAIN (captures));
680*38fd1498Szrj 
681*38fd1498Szrj   tree field = TREE_PURPOSE (captures);
682*38fd1498Szrj   if (PACK_EXPANSION_P (field))
683*38fd1498Szrj     field = PACK_EXPANSION_PATTERN (field);
684*38fd1498Szrj 
685*38fd1498Szrj   /* We set this in add_capture to avoid duplicates.  */
686*38fd1498Szrj   IDENTIFIER_MARKED (DECL_NAME (field)) = false;
687*38fd1498Szrj   finish_member_declaration (field);
688*38fd1498Szrj }
689*38fd1498Szrj 
690*38fd1498Szrj /* Similar to add_capture, except this works on a stack of nested lambdas.
691*38fd1498Szrj    BY_REFERENCE_P in this case is derived from the default capture mode.
692*38fd1498Szrj    Returns the capture for the lambda at the bottom of the stack.  */
693*38fd1498Szrj 
694*38fd1498Szrj tree
695*38fd1498Szrj add_default_capture (tree lambda_stack, tree id, tree initializer)
696*38fd1498Szrj {
697*38fd1498Szrj   bool this_capture_p = (id == this_identifier);
698*38fd1498Szrj 
699*38fd1498Szrj   tree var = NULL_TREE;
700*38fd1498Szrj 
701*38fd1498Szrj   tree saved_class_type = current_class_type;
702*38fd1498Szrj 
703*38fd1498Szrj   tree node;
704*38fd1498Szrj 
705*38fd1498Szrj   for (node = lambda_stack;
706*38fd1498Szrj        node;
707*38fd1498Szrj        node = TREE_CHAIN (node))
708*38fd1498Szrj     {
709*38fd1498Szrj       tree lambda = TREE_VALUE (node);
710*38fd1498Szrj 
711*38fd1498Szrj       current_class_type = LAMBDA_EXPR_CLOSURE (lambda);
712*38fd1498Szrj       if (DECL_PACK_P (initializer))
713*38fd1498Szrj 	initializer = make_pack_expansion (initializer);
714*38fd1498Szrj       var = add_capture (lambda,
715*38fd1498Szrj                             id,
716*38fd1498Szrj                             initializer,
717*38fd1498Szrj                             /*by_reference_p=*/
718*38fd1498Szrj 			    (this_capture_p
719*38fd1498Szrj 			     || (LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (lambda)
720*38fd1498Szrj 				 == CPLD_REFERENCE)),
721*38fd1498Szrj 			    /*explicit_init_p=*/false);
722*38fd1498Szrj       initializer = convert_from_reference (var);
723*38fd1498Szrj     }
724*38fd1498Szrj 
725*38fd1498Szrj   current_class_type = saved_class_type;
726*38fd1498Szrj 
727*38fd1498Szrj   return var;
728*38fd1498Szrj }
729*38fd1498Szrj 
730*38fd1498Szrj /* Return the capture pertaining to a use of 'this' in LAMBDA, in the
731*38fd1498Szrj    form of an INDIRECT_REF, possibly adding it through default
732*38fd1498Szrj    capturing, if ADD_CAPTURE_P is true.  */
733*38fd1498Szrj 
734*38fd1498Szrj tree
735*38fd1498Szrj lambda_expr_this_capture (tree lambda, bool add_capture_p)
736*38fd1498Szrj {
737*38fd1498Szrj   tree result;
738*38fd1498Szrj 
739*38fd1498Szrj   tree this_capture = LAMBDA_EXPR_THIS_CAPTURE (lambda);
740*38fd1498Szrj 
741*38fd1498Szrj   /* In unevaluated context this isn't an odr-use, so don't capture.  */
742*38fd1498Szrj   if (cp_unevaluated_operand)
743*38fd1498Szrj     add_capture_p = false;
744*38fd1498Szrj 
745*38fd1498Szrj   /* Try to default capture 'this' if we can.  */
746*38fd1498Szrj   if (!this_capture
747*38fd1498Szrj       && (!add_capture_p
748*38fd1498Szrj           || LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (lambda) != CPLD_NONE))
749*38fd1498Szrj     {
750*38fd1498Szrj       tree lambda_stack = NULL_TREE;
751*38fd1498Szrj       tree init = NULL_TREE;
752*38fd1498Szrj 
753*38fd1498Szrj       /* If we are in a lambda function, we can move out until we hit:
754*38fd1498Szrj            1. a non-lambda function or NSDMI,
755*38fd1498Szrj            2. a lambda function capturing 'this', or
756*38fd1498Szrj            3. a non-default capturing lambda function.  */
757*38fd1498Szrj       for (tree tlambda = lambda; ;)
758*38fd1498Szrj 	{
759*38fd1498Szrj           lambda_stack = tree_cons (NULL_TREE,
760*38fd1498Szrj                                     tlambda,
761*38fd1498Szrj                                     lambda_stack);
762*38fd1498Szrj 
763*38fd1498Szrj 	  tree closure = LAMBDA_EXPR_CLOSURE (tlambda);
764*38fd1498Szrj 	  tree containing_function
765*38fd1498Szrj 	    = decl_function_context (TYPE_NAME (closure));
766*38fd1498Szrj 
767*38fd1498Szrj 	  tree ex = LAMBDA_EXPR_EXTRA_SCOPE (tlambda);
768*38fd1498Szrj 	  if (ex && TREE_CODE (ex) == FIELD_DECL)
769*38fd1498Szrj 	    {
770*38fd1498Szrj 	      /* Lambda in an NSDMI.  We don't have a function to look up
771*38fd1498Szrj 		 'this' in, but we can find (or rebuild) the fake one from
772*38fd1498Szrj 		 inject_this_parameter.  */
773*38fd1498Szrj 	      if (!containing_function && !COMPLETE_TYPE_P (closure))
774*38fd1498Szrj 		/* If we're parsing a lambda in a non-local class,
775*38fd1498Szrj 		   we can find the fake 'this' in scope_chain.  */
776*38fd1498Szrj 		init = scope_chain->x_current_class_ptr;
777*38fd1498Szrj 	      else
778*38fd1498Szrj 		/* Otherwise it's either gone or buried in
779*38fd1498Szrj 		   function_context_stack, so make another.  */
780*38fd1498Szrj 		init = build_this_parm (NULL_TREE, DECL_CONTEXT (ex),
781*38fd1498Szrj 					TYPE_UNQUALIFIED);
782*38fd1498Szrj 	      gcc_checking_assert
783*38fd1498Szrj 		(init && (TREE_TYPE (TREE_TYPE (init))
784*38fd1498Szrj 			  == current_nonlambda_class_type ()));
785*38fd1498Szrj 	      break;
786*38fd1498Szrj 	    }
787*38fd1498Szrj 
788*38fd1498Szrj 	  if (containing_function == NULL_TREE)
789*38fd1498Szrj 	    /* We ran out of scopes; there's no 'this' to capture.  */
790*38fd1498Szrj 	    break;
791*38fd1498Szrj 
792*38fd1498Szrj 	  if (!LAMBDA_FUNCTION_P (containing_function))
793*38fd1498Szrj 	    {
794*38fd1498Szrj 	      /* We found a non-lambda function.  */
795*38fd1498Szrj 	      if (DECL_NONSTATIC_MEMBER_FUNCTION_P (containing_function))
796*38fd1498Szrj 		/* First parameter is 'this'.  */
797*38fd1498Szrj 		init = DECL_ARGUMENTS (containing_function);
798*38fd1498Szrj 	      break;
799*38fd1498Szrj 	    }
800*38fd1498Szrj 
801*38fd1498Szrj 	  tlambda
802*38fd1498Szrj             = CLASSTYPE_LAMBDA_EXPR (DECL_CONTEXT (containing_function));
803*38fd1498Szrj 
804*38fd1498Szrj           if (LAMBDA_EXPR_THIS_CAPTURE (tlambda))
805*38fd1498Szrj 	    {
806*38fd1498Szrj 	      /* An outer lambda has already captured 'this'.  */
807*38fd1498Szrj 	      init = LAMBDA_EXPR_THIS_CAPTURE (tlambda);
808*38fd1498Szrj 	      break;
809*38fd1498Szrj 	    }
810*38fd1498Szrj 
811*38fd1498Szrj 	  if (LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (tlambda) == CPLD_NONE)
812*38fd1498Szrj 	    /* An outer lambda won't let us capture 'this'.  */
813*38fd1498Szrj 	    break;
814*38fd1498Szrj 	}
815*38fd1498Szrj 
816*38fd1498Szrj       if (init)
817*38fd1498Szrj         {
818*38fd1498Szrj           if (add_capture_p)
819*38fd1498Szrj 	    this_capture = add_default_capture (lambda_stack,
820*38fd1498Szrj 					        /*id=*/this_identifier,
821*38fd1498Szrj 					        init);
822*38fd1498Szrj           else
823*38fd1498Szrj 	    this_capture = init;
824*38fd1498Szrj         }
825*38fd1498Szrj     }
826*38fd1498Szrj 
827*38fd1498Szrj   if (cp_unevaluated_operand)
828*38fd1498Szrj     result = this_capture;
829*38fd1498Szrj   else if (!this_capture)
830*38fd1498Szrj     {
831*38fd1498Szrj       if (add_capture_p)
832*38fd1498Szrj 	{
833*38fd1498Szrj 	  error ("%<this%> was not captured for this lambda function");
834*38fd1498Szrj 	  result = error_mark_node;
835*38fd1498Szrj 	}
836*38fd1498Szrj       else
837*38fd1498Szrj 	result = NULL_TREE;
838*38fd1498Szrj     }
839*38fd1498Szrj   else
840*38fd1498Szrj     {
841*38fd1498Szrj       /* To make sure that current_class_ref is for the lambda.  */
842*38fd1498Szrj       gcc_assert (TYPE_MAIN_VARIANT (TREE_TYPE (current_class_ref))
843*38fd1498Szrj 		  == LAMBDA_EXPR_CLOSURE (lambda));
844*38fd1498Szrj 
845*38fd1498Szrj       result = this_capture;
846*38fd1498Szrj 
847*38fd1498Szrj       /* If 'this' is captured, each use of 'this' is transformed into an
848*38fd1498Szrj 	 access to the corresponding unnamed data member of the closure
849*38fd1498Szrj 	 type cast (_expr.cast_ 5.4) to the type of 'this'. [ The cast
850*38fd1498Szrj 	 ensures that the transformed expression is an rvalue. ] */
851*38fd1498Szrj       result = rvalue (result);
852*38fd1498Szrj     }
853*38fd1498Szrj 
854*38fd1498Szrj   return result;
855*38fd1498Szrj }
856*38fd1498Szrj 
857*38fd1498Szrj /* Return the innermost LAMBDA_EXPR we're currently in, if any.  */
858*38fd1498Szrj 
859*38fd1498Szrj tree
860*38fd1498Szrj current_lambda_expr (void)
861*38fd1498Szrj {
862*38fd1498Szrj   tree type = current_class_type;
863*38fd1498Szrj   while (type && !LAMBDA_TYPE_P (type))
864*38fd1498Szrj     type = decl_type_context (TYPE_NAME (type));
865*38fd1498Szrj   if (type)
866*38fd1498Szrj     return CLASSTYPE_LAMBDA_EXPR (type);
867*38fd1498Szrj   else
868*38fd1498Szrj     return NULL_TREE;
869*38fd1498Szrj }
870*38fd1498Szrj 
871*38fd1498Szrj /* Return the current LAMBDA_EXPR, if this is a resolvable dummy
872*38fd1498Szrj    object.  NULL otherwise..  */
873*38fd1498Szrj 
874*38fd1498Szrj static tree
875*38fd1498Szrj resolvable_dummy_lambda (tree object)
876*38fd1498Szrj {
877*38fd1498Szrj   if (!is_dummy_object (object))
878*38fd1498Szrj     return NULL_TREE;
879*38fd1498Szrj 
880*38fd1498Szrj   tree type = TYPE_MAIN_VARIANT (TREE_TYPE (object));
881*38fd1498Szrj   gcc_assert (!TYPE_PTR_P (type));
882*38fd1498Szrj 
883*38fd1498Szrj   if (type != current_class_type
884*38fd1498Szrj       && current_class_type
885*38fd1498Szrj       && LAMBDA_TYPE_P (current_class_type)
886*38fd1498Szrj       && lambda_function (current_class_type)
887*38fd1498Szrj       && DERIVED_FROM_P (type, current_nonlambda_class_type ()))
888*38fd1498Szrj     return CLASSTYPE_LAMBDA_EXPR (current_class_type);
889*38fd1498Szrj 
890*38fd1498Szrj   return NULL_TREE;
891*38fd1498Szrj }
892*38fd1498Szrj 
893*38fd1498Szrj /* We don't want to capture 'this' until we know we need it, i.e. after
894*38fd1498Szrj    overload resolution has chosen a non-static member function.  At that
895*38fd1498Szrj    point we call this function to turn a dummy object into a use of the
896*38fd1498Szrj    'this' capture.  */
897*38fd1498Szrj 
898*38fd1498Szrj tree
899*38fd1498Szrj maybe_resolve_dummy (tree object, bool add_capture_p)
900*38fd1498Szrj {
901*38fd1498Szrj   if (tree lam = resolvable_dummy_lambda (object))
902*38fd1498Szrj     if (tree cap = lambda_expr_this_capture (lam, add_capture_p))
903*38fd1498Szrj       if (cap != error_mark_node)
904*38fd1498Szrj 	object = build_fold_indirect_ref (cap);
905*38fd1498Szrj 
906*38fd1498Szrj   return object;
907*38fd1498Szrj }
908*38fd1498Szrj 
909*38fd1498Szrj /* When parsing a generic lambda containing an argument-dependent
910*38fd1498Szrj    member function call we defer overload resolution to instantiation
911*38fd1498Szrj    time.  But we have to know now whether to capture this or not.
912*38fd1498Szrj    Do that if FNS contains any non-static fns.
913*38fd1498Szrj    The std doesn't anticipate this case, but I expect this to be the
914*38fd1498Szrj    outcome of discussion.  */
915*38fd1498Szrj 
916*38fd1498Szrj void
917*38fd1498Szrj maybe_generic_this_capture (tree object, tree fns)
918*38fd1498Szrj {
919*38fd1498Szrj   if (tree lam = resolvable_dummy_lambda (object))
920*38fd1498Szrj     if (!LAMBDA_EXPR_THIS_CAPTURE (lam))
921*38fd1498Szrj       {
922*38fd1498Szrj 	/* We've not yet captured, so look at the function set of
923*38fd1498Szrj 	   interest.  */
924*38fd1498Szrj 	if (BASELINK_P (fns))
925*38fd1498Szrj 	  fns = BASELINK_FUNCTIONS (fns);
926*38fd1498Szrj 	bool id_expr = TREE_CODE (fns) == TEMPLATE_ID_EXPR;
927*38fd1498Szrj 	if (id_expr)
928*38fd1498Szrj 	  fns = TREE_OPERAND (fns, 0);
929*38fd1498Szrj 
930*38fd1498Szrj 	for (lkp_iterator iter (fns); iter; ++iter)
931*38fd1498Szrj 	  if ((!id_expr || TREE_CODE (*iter) == TEMPLATE_DECL)
932*38fd1498Szrj 	      && DECL_NONSTATIC_MEMBER_FUNCTION_P (*iter))
933*38fd1498Szrj 	    {
934*38fd1498Szrj 	      /* Found a non-static member.  Capture this.  */
935*38fd1498Szrj 	      lambda_expr_this_capture (lam, true);
936*38fd1498Szrj 	      break;
937*38fd1498Szrj 	    }
938*38fd1498Szrj       }
939*38fd1498Szrj }
940*38fd1498Szrj 
941*38fd1498Szrj /* Returns the innermost non-lambda function.  */
942*38fd1498Szrj 
943*38fd1498Szrj tree
944*38fd1498Szrj current_nonlambda_function (void)
945*38fd1498Szrj {
946*38fd1498Szrj   tree fn = current_function_decl;
947*38fd1498Szrj   while (fn && LAMBDA_FUNCTION_P (fn))
948*38fd1498Szrj     fn = decl_function_context (fn);
949*38fd1498Szrj   return fn;
950*38fd1498Szrj }
951*38fd1498Szrj 
952*38fd1498Szrj /* Returns the method basetype of the innermost non-lambda function, or
953*38fd1498Szrj    NULL_TREE if none.  */
954*38fd1498Szrj 
955*38fd1498Szrj tree
956*38fd1498Szrj nonlambda_method_basetype (void)
957*38fd1498Szrj {
958*38fd1498Szrj   tree fn, type;
959*38fd1498Szrj   if (!current_class_ref)
960*38fd1498Szrj     return NULL_TREE;
961*38fd1498Szrj 
962*38fd1498Szrj   type = current_class_type;
963*38fd1498Szrj   if (!type || !LAMBDA_TYPE_P (type))
964*38fd1498Szrj     return type;
965*38fd1498Szrj 
966*38fd1498Szrj   /* Find the nearest enclosing non-lambda function.  */
967*38fd1498Szrj   fn = TYPE_NAME (type);
968*38fd1498Szrj   do
969*38fd1498Szrj     fn = decl_function_context (fn);
970*38fd1498Szrj   while (fn && LAMBDA_FUNCTION_P (fn));
971*38fd1498Szrj 
972*38fd1498Szrj   if (!fn || !DECL_NONSTATIC_MEMBER_FUNCTION_P (fn))
973*38fd1498Szrj     return NULL_TREE;
974*38fd1498Szrj 
975*38fd1498Szrj   return TYPE_METHOD_BASETYPE (TREE_TYPE (fn));
976*38fd1498Szrj }
977*38fd1498Szrj 
978*38fd1498Szrj /* Like current_scope, but looking through lambdas.  */
979*38fd1498Szrj 
980*38fd1498Szrj tree
981*38fd1498Szrj current_nonlambda_scope (void)
982*38fd1498Szrj {
983*38fd1498Szrj   tree scope = current_scope ();
984*38fd1498Szrj   for (;;)
985*38fd1498Szrj     {
986*38fd1498Szrj       if (TREE_CODE (scope) == FUNCTION_DECL
987*38fd1498Szrj 	  && LAMBDA_FUNCTION_P (scope))
988*38fd1498Szrj 	{
989*38fd1498Szrj 	  scope = CP_TYPE_CONTEXT (DECL_CONTEXT (scope));
990*38fd1498Szrj 	  continue;
991*38fd1498Szrj 	}
992*38fd1498Szrj       else if (LAMBDA_TYPE_P (scope))
993*38fd1498Szrj 	{
994*38fd1498Szrj 	  scope = CP_TYPE_CONTEXT (scope);
995*38fd1498Szrj 	  continue;
996*38fd1498Szrj 	}
997*38fd1498Szrj       break;
998*38fd1498Szrj     }
999*38fd1498Szrj   return scope;
1000*38fd1498Szrj }
1001*38fd1498Szrj 
1002*38fd1498Szrj /* Helper function for maybe_add_lambda_conv_op; build a CALL_EXPR with
1003*38fd1498Szrj    indicated FN and NARGS, but do not initialize the return type or any of the
1004*38fd1498Szrj    argument slots.  */
1005*38fd1498Szrj 
1006*38fd1498Szrj static tree
1007*38fd1498Szrj prepare_op_call (tree fn, int nargs)
1008*38fd1498Szrj {
1009*38fd1498Szrj   tree t;
1010*38fd1498Szrj 
1011*38fd1498Szrj   t = build_vl_exp (CALL_EXPR, nargs + 3);
1012*38fd1498Szrj   CALL_EXPR_FN (t) = fn;
1013*38fd1498Szrj   CALL_EXPR_STATIC_CHAIN (t) = NULL;
1014*38fd1498Szrj 
1015*38fd1498Szrj   return t;
1016*38fd1498Szrj }
1017*38fd1498Szrj 
1018*38fd1498Szrj /* Return true iff CALLOP is the op() for a generic lambda.  */
1019*38fd1498Szrj 
1020*38fd1498Szrj bool
1021*38fd1498Szrj generic_lambda_fn_p (tree callop)
1022*38fd1498Szrj {
1023*38fd1498Szrj   return (LAMBDA_FUNCTION_P (callop)
1024*38fd1498Szrj 	  && DECL_TEMPLATE_INFO (callop)
1025*38fd1498Szrj 	  && PRIMARY_TEMPLATE_P (DECL_TI_TEMPLATE (callop)));
1026*38fd1498Szrj }
1027*38fd1498Szrj 
1028*38fd1498Szrj /* If the closure TYPE has a static op(), also add a conversion to function
1029*38fd1498Szrj    pointer.  */
1030*38fd1498Szrj 
1031*38fd1498Szrj void
1032*38fd1498Szrj maybe_add_lambda_conv_op (tree type)
1033*38fd1498Szrj {
1034*38fd1498Szrj   bool nested = (cfun != NULL);
1035*38fd1498Szrj   bool nested_def = decl_function_context (TYPE_MAIN_DECL (type));
1036*38fd1498Szrj   tree callop = lambda_function (type);
1037*38fd1498Szrj   tree lam = CLASSTYPE_LAMBDA_EXPR (type);
1038*38fd1498Szrj 
1039*38fd1498Szrj   if (LAMBDA_EXPR_CAPTURE_LIST (lam) != NULL_TREE
1040*38fd1498Szrj       || LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (lam) != CPLD_NONE)
1041*38fd1498Szrj     return;
1042*38fd1498Szrj 
1043*38fd1498Szrj   if (processing_template_decl)
1044*38fd1498Szrj     return;
1045*38fd1498Szrj 
1046*38fd1498Szrj   bool const generic_lambda_p = generic_lambda_fn_p (callop);
1047*38fd1498Szrj 
1048*38fd1498Szrj   if (!generic_lambda_p && DECL_INITIAL (callop) == NULL_TREE)
1049*38fd1498Szrj     {
1050*38fd1498Szrj       /* If the op() wasn't instantiated due to errors, give up.  */
1051*38fd1498Szrj       gcc_assert (errorcount || sorrycount);
1052*38fd1498Szrj       return;
1053*38fd1498Szrj     }
1054*38fd1498Szrj 
1055*38fd1498Szrj   /* Non-template conversion operators are defined directly with build_call_a
1056*38fd1498Szrj      and using DIRECT_ARGVEC for arguments (including 'this').  Templates are
1057*38fd1498Szrj      deferred and the CALL is built in-place.  In the case of a deduced return
1058*38fd1498Szrj      call op, the decltype expression, DECLTYPE_CALL, used as a substitute for
1059*38fd1498Szrj      the return type is also built in-place.  The arguments of DECLTYPE_CALL in
1060*38fd1498Szrj      the return expression may differ in flags from those in the body CALL.  In
1061*38fd1498Szrj      particular, parameter pack expansions are marked PACK_EXPANSION_LOCAL_P in
1062*38fd1498Szrj      the body CALL, but not in DECLTYPE_CALL.  */
1063*38fd1498Szrj 
1064*38fd1498Szrj   vec<tree, va_gc> *direct_argvec = 0;
1065*38fd1498Szrj   tree decltype_call = 0, call = 0;
1066*38fd1498Szrj   tree optype = TREE_TYPE (callop);
1067*38fd1498Szrj   tree fn_result = TREE_TYPE (optype);
1068*38fd1498Szrj 
1069*38fd1498Szrj   tree thisarg = build_nop (TREE_TYPE (DECL_ARGUMENTS (callop)),
1070*38fd1498Szrj 			    null_pointer_node);
1071*38fd1498Szrj   if (generic_lambda_p)
1072*38fd1498Szrj     {
1073*38fd1498Szrj       ++processing_template_decl;
1074*38fd1498Szrj 
1075*38fd1498Szrj       /* Prepare the dependent member call for the static member function
1076*38fd1498Szrj 	 '_FUN' and, potentially, prepare another call to be used in a decltype
1077*38fd1498Szrj 	 return expression for a deduced return call op to allow for simple
1078*38fd1498Szrj 	 implementation of the conversion operator.  */
1079*38fd1498Szrj 
1080*38fd1498Szrj       tree instance = cp_build_fold_indirect_ref (thisarg);
1081*38fd1498Szrj       tree objfn = build_min (COMPONENT_REF, NULL_TREE,
1082*38fd1498Szrj 			      instance, DECL_NAME (callop), NULL_TREE);
1083*38fd1498Szrj       int nargs = list_length (DECL_ARGUMENTS (callop)) - 1;
1084*38fd1498Szrj 
1085*38fd1498Szrj       call = prepare_op_call (objfn, nargs);
1086*38fd1498Szrj       if (type_uses_auto (fn_result))
1087*38fd1498Szrj 	decltype_call = prepare_op_call (objfn, nargs);
1088*38fd1498Szrj     }
1089*38fd1498Szrj   else
1090*38fd1498Szrj     {
1091*38fd1498Szrj       direct_argvec = make_tree_vector ();
1092*38fd1498Szrj       direct_argvec->quick_push (thisarg);
1093*38fd1498Szrj     }
1094*38fd1498Szrj 
1095*38fd1498Szrj   /* Copy CALLOP's argument list (as per 'copy_list') as FN_ARGS in order to
1096*38fd1498Szrj      declare the static member function "_FUN" below.  For each arg append to
1097*38fd1498Szrj      DIRECT_ARGVEC (for the non-template case) or populate the pre-allocated
1098*38fd1498Szrj      call args (for the template case).  If a parameter pack is found, expand
1099*38fd1498Szrj      it, flagging it as PACK_EXPANSION_LOCAL_P for the body call.  */
1100*38fd1498Szrj 
1101*38fd1498Szrj   tree fn_args = NULL_TREE;
1102*38fd1498Szrj   {
1103*38fd1498Szrj     int ix = 0;
1104*38fd1498Szrj     tree src = DECL_CHAIN (DECL_ARGUMENTS (callop));
1105*38fd1498Szrj     tree tgt = NULL;
1106*38fd1498Szrj 
1107*38fd1498Szrj     while (src)
1108*38fd1498Szrj       {
1109*38fd1498Szrj 	tree new_node = copy_node (src);
1110*38fd1498Szrj 
1111*38fd1498Szrj 	if (!fn_args)
1112*38fd1498Szrj 	  fn_args = tgt = new_node;
1113*38fd1498Szrj 	else
1114*38fd1498Szrj 	  {
1115*38fd1498Szrj 	    TREE_CHAIN (tgt) = new_node;
1116*38fd1498Szrj 	    tgt = new_node;
1117*38fd1498Szrj 	  }
1118*38fd1498Szrj 
1119*38fd1498Szrj 	mark_exp_read (tgt);
1120*38fd1498Szrj 
1121*38fd1498Szrj 	if (generic_lambda_p)
1122*38fd1498Szrj 	  {
1123*38fd1498Szrj 	    /* Avoid capturing variables in this context.  */
1124*38fd1498Szrj 	    ++cp_unevaluated_operand;
1125*38fd1498Szrj 	    tree a = forward_parm (tgt);
1126*38fd1498Szrj 	    --cp_unevaluated_operand;
1127*38fd1498Szrj 
1128*38fd1498Szrj 	    CALL_EXPR_ARG (call, ix) = a;
1129*38fd1498Szrj 	    if (decltype_call)
1130*38fd1498Szrj 	      CALL_EXPR_ARG (decltype_call, ix) = unshare_expr (a);
1131*38fd1498Szrj 
1132*38fd1498Szrj 	    if (PACK_EXPANSION_P (a))
1133*38fd1498Szrj 	      /* Set this after unsharing so it's not in decltype_call.  */
1134*38fd1498Szrj 	      PACK_EXPANSION_LOCAL_P (a) = true;
1135*38fd1498Szrj 
1136*38fd1498Szrj 	    ++ix;
1137*38fd1498Szrj 	  }
1138*38fd1498Szrj 	else
1139*38fd1498Szrj 	  vec_safe_push (direct_argvec, tgt);
1140*38fd1498Szrj 
1141*38fd1498Szrj 	src = TREE_CHAIN (src);
1142*38fd1498Szrj       }
1143*38fd1498Szrj   }
1144*38fd1498Szrj 
1145*38fd1498Szrj   if (generic_lambda_p)
1146*38fd1498Szrj     {
1147*38fd1498Szrj       if (decltype_call)
1148*38fd1498Szrj 	{
1149*38fd1498Szrj 	  fn_result = finish_decltype_type
1150*38fd1498Szrj 	    (decltype_call, /*id_expression_or_member_access_p=*/false,
1151*38fd1498Szrj 	     tf_warning_or_error);
1152*38fd1498Szrj 	}
1153*38fd1498Szrj     }
1154*38fd1498Szrj   else
1155*38fd1498Szrj     call = build_call_a (callop,
1156*38fd1498Szrj 			 direct_argvec->length (),
1157*38fd1498Szrj 			 direct_argvec->address ());
1158*38fd1498Szrj 
1159*38fd1498Szrj   CALL_FROM_THUNK_P (call) = 1;
1160*38fd1498Szrj   SET_EXPR_LOCATION (call, UNKNOWN_LOCATION);
1161*38fd1498Szrj 
1162*38fd1498Szrj   tree stattype = build_function_type (fn_result, FUNCTION_ARG_CHAIN (callop));
1163*38fd1498Szrj   stattype = (cp_build_type_attribute_variant
1164*38fd1498Szrj 	      (stattype, TYPE_ATTRIBUTES (optype)));
1165*38fd1498Szrj   if (flag_noexcept_type
1166*38fd1498Szrj       && TYPE_NOTHROW_P (TREE_TYPE (callop)))
1167*38fd1498Szrj     stattype = build_exception_variant (stattype, noexcept_true_spec);
1168*38fd1498Szrj 
1169*38fd1498Szrj   if (generic_lambda_p)
1170*38fd1498Szrj     --processing_template_decl;
1171*38fd1498Szrj 
1172*38fd1498Szrj   /* First build up the conversion op.  */
1173*38fd1498Szrj 
1174*38fd1498Szrj   tree rettype = build_pointer_type (stattype);
1175*38fd1498Szrj   tree name = make_conv_op_name (rettype);
1176*38fd1498Szrj   tree thistype = cp_build_qualified_type (type, TYPE_QUAL_CONST);
1177*38fd1498Szrj   tree fntype = build_method_type_directly (thistype, rettype, void_list_node);
1178*38fd1498Szrj   tree convfn = build_lang_decl (FUNCTION_DECL, name, fntype);
1179*38fd1498Szrj   SET_DECL_LANGUAGE (convfn, lang_cplusplus);
1180*38fd1498Szrj   tree fn = convfn;
1181*38fd1498Szrj   DECL_SOURCE_LOCATION (fn) = DECL_SOURCE_LOCATION (callop);
1182*38fd1498Szrj   SET_DECL_ALIGN (fn, MINIMUM_METHOD_BOUNDARY);
1183*38fd1498Szrj   grokclassfn (type, fn, NO_SPECIAL);
1184*38fd1498Szrj   set_linkage_according_to_type (type, fn);
1185*38fd1498Szrj   rest_of_decl_compilation (fn, namespace_bindings_p (), at_eof);
1186*38fd1498Szrj   DECL_IN_AGGR_P (fn) = 1;
1187*38fd1498Szrj   DECL_ARTIFICIAL (fn) = 1;
1188*38fd1498Szrj   DECL_NOT_REALLY_EXTERN (fn) = 1;
1189*38fd1498Szrj   DECL_DECLARED_INLINE_P (fn) = 1;
1190*38fd1498Szrj   DECL_ARGUMENTS (fn) = build_this_parm (fn, fntype, TYPE_QUAL_CONST);
1191*38fd1498Szrj 
1192*38fd1498Szrj   if (nested_def)
1193*38fd1498Szrj     DECL_INTERFACE_KNOWN (fn) = 1;
1194*38fd1498Szrj 
1195*38fd1498Szrj   if (generic_lambda_p)
1196*38fd1498Szrj     fn = add_inherited_template_parms (fn, DECL_TI_TEMPLATE (callop));
1197*38fd1498Szrj 
1198*38fd1498Szrj   add_method (type, fn, false);
1199*38fd1498Szrj 
1200*38fd1498Szrj   /* Generic thunk code fails for varargs; we'll complain in mark_used if
1201*38fd1498Szrj      the conversion op is used.  */
1202*38fd1498Szrj   if (varargs_function_p (callop))
1203*38fd1498Szrj     {
1204*38fd1498Szrj       DECL_DELETED_FN (fn) = 1;
1205*38fd1498Szrj       return;
1206*38fd1498Szrj     }
1207*38fd1498Szrj 
1208*38fd1498Szrj   /* Now build up the thunk to be returned.  */
1209*38fd1498Szrj 
1210*38fd1498Szrj   name = get_identifier ("_FUN");
1211*38fd1498Szrj   tree statfn = build_lang_decl (FUNCTION_DECL, name, stattype);
1212*38fd1498Szrj   SET_DECL_LANGUAGE (statfn, lang_cplusplus);
1213*38fd1498Szrj   fn = statfn;
1214*38fd1498Szrj   DECL_SOURCE_LOCATION (fn) = DECL_SOURCE_LOCATION (callop);
1215*38fd1498Szrj   grokclassfn (type, fn, NO_SPECIAL);
1216*38fd1498Szrj   set_linkage_according_to_type (type, fn);
1217*38fd1498Szrj   rest_of_decl_compilation (fn, namespace_bindings_p (), at_eof);
1218*38fd1498Szrj   DECL_IN_AGGR_P (fn) = 1;
1219*38fd1498Szrj   DECL_ARTIFICIAL (fn) = 1;
1220*38fd1498Szrj   DECL_NOT_REALLY_EXTERN (fn) = 1;
1221*38fd1498Szrj   DECL_DECLARED_INLINE_P (fn) = 1;
1222*38fd1498Szrj   DECL_STATIC_FUNCTION_P (fn) = 1;
1223*38fd1498Szrj   DECL_ARGUMENTS (fn) = fn_args;
1224*38fd1498Szrj   for (tree arg = fn_args; arg; arg = DECL_CHAIN (arg))
1225*38fd1498Szrj     {
1226*38fd1498Szrj       /* Avoid duplicate -Wshadow warnings.  */
1227*38fd1498Szrj       DECL_NAME (arg) = NULL_TREE;
1228*38fd1498Szrj       DECL_CONTEXT (arg) = fn;
1229*38fd1498Szrj     }
1230*38fd1498Szrj   if (nested_def)
1231*38fd1498Szrj     DECL_INTERFACE_KNOWN (fn) = 1;
1232*38fd1498Szrj 
1233*38fd1498Szrj   if (generic_lambda_p)
1234*38fd1498Szrj     fn = add_inherited_template_parms (fn, DECL_TI_TEMPLATE (callop));
1235*38fd1498Szrj 
1236*38fd1498Szrj   if (flag_sanitize & SANITIZE_NULL)
1237*38fd1498Szrj     /* Don't UBsan this function; we're deliberately calling op() with a null
1238*38fd1498Szrj        object argument.  */
1239*38fd1498Szrj     add_no_sanitize_value (fn, SANITIZE_UNDEFINED);
1240*38fd1498Szrj 
1241*38fd1498Szrj   add_method (type, fn, false);
1242*38fd1498Szrj 
1243*38fd1498Szrj   if (nested)
1244*38fd1498Szrj     push_function_context ();
1245*38fd1498Szrj   else
1246*38fd1498Szrj     /* Still increment function_depth so that we don't GC in the
1247*38fd1498Szrj        middle of an expression.  */
1248*38fd1498Szrj     ++function_depth;
1249*38fd1498Szrj 
1250*38fd1498Szrj   /* Generate the body of the thunk.  */
1251*38fd1498Szrj 
1252*38fd1498Szrj   start_preparsed_function (statfn, NULL_TREE,
1253*38fd1498Szrj 			    SF_PRE_PARSED | SF_INCLASS_INLINE);
1254*38fd1498Szrj   if (DECL_ONE_ONLY (statfn))
1255*38fd1498Szrj     {
1256*38fd1498Szrj       /* Put the thunk in the same comdat group as the call op.  */
1257*38fd1498Szrj       cgraph_node::get_create (statfn)->add_to_same_comdat_group
1258*38fd1498Szrj 	(cgraph_node::get_create (callop));
1259*38fd1498Szrj     }
1260*38fd1498Szrj   tree body = begin_function_body ();
1261*38fd1498Szrj   tree compound_stmt = begin_compound_stmt (0);
1262*38fd1498Szrj   if (!generic_lambda_p)
1263*38fd1498Szrj     {
1264*38fd1498Szrj       set_flags_from_callee (call);
1265*38fd1498Szrj       if (MAYBE_CLASS_TYPE_P (TREE_TYPE (call)))
1266*38fd1498Szrj 	call = build_cplus_new (TREE_TYPE (call), call, tf_warning_or_error);
1267*38fd1498Szrj     }
1268*38fd1498Szrj   call = convert_from_reference (call);
1269*38fd1498Szrj   finish_return_stmt (call);
1270*38fd1498Szrj 
1271*38fd1498Szrj   finish_compound_stmt (compound_stmt);
1272*38fd1498Szrj   finish_function_body (body);
1273*38fd1498Szrj 
1274*38fd1498Szrj   fn = finish_function (/*inline_p=*/true);
1275*38fd1498Szrj   if (!generic_lambda_p)
1276*38fd1498Szrj     expand_or_defer_fn (fn);
1277*38fd1498Szrj 
1278*38fd1498Szrj   /* Generate the body of the conversion op.  */
1279*38fd1498Szrj 
1280*38fd1498Szrj   start_preparsed_function (convfn, NULL_TREE,
1281*38fd1498Szrj 			    SF_PRE_PARSED | SF_INCLASS_INLINE);
1282*38fd1498Szrj   body = begin_function_body ();
1283*38fd1498Szrj   compound_stmt = begin_compound_stmt (0);
1284*38fd1498Szrj 
1285*38fd1498Szrj   /* decl_needed_p needs to see that it's used.  */
1286*38fd1498Szrj   TREE_USED (statfn) = 1;
1287*38fd1498Szrj   finish_return_stmt (decay_conversion (statfn, tf_warning_or_error));
1288*38fd1498Szrj 
1289*38fd1498Szrj   finish_compound_stmt (compound_stmt);
1290*38fd1498Szrj   finish_function_body (body);
1291*38fd1498Szrj 
1292*38fd1498Szrj   fn = finish_function (/*inline_p=*/true);
1293*38fd1498Szrj   if (!generic_lambda_p)
1294*38fd1498Szrj     expand_or_defer_fn (fn);
1295*38fd1498Szrj 
1296*38fd1498Szrj   if (nested)
1297*38fd1498Szrj     pop_function_context ();
1298*38fd1498Szrj   else
1299*38fd1498Szrj     --function_depth;
1300*38fd1498Szrj }
1301*38fd1498Szrj 
1302*38fd1498Szrj /* True if FN is the static function "_FUN" that gets returned from the lambda
1303*38fd1498Szrj    conversion operator.  */
1304*38fd1498Szrj 
1305*38fd1498Szrj bool
1306*38fd1498Szrj lambda_static_thunk_p (tree fn)
1307*38fd1498Szrj {
1308*38fd1498Szrj   return (fn && TREE_CODE (fn) == FUNCTION_DECL
1309*38fd1498Szrj 	  && DECL_ARTIFICIAL (fn)
1310*38fd1498Szrj 	  && DECL_STATIC_FUNCTION_P (fn)
1311*38fd1498Szrj 	  && LAMBDA_TYPE_P (CP_DECL_CONTEXT (fn)));
1312*38fd1498Szrj }
1313*38fd1498Szrj 
1314*38fd1498Szrj /* Returns true iff VAL is a lambda-related declaration which should
1315*38fd1498Szrj    be ignored by unqualified lookup.  */
1316*38fd1498Szrj 
1317*38fd1498Szrj bool
1318*38fd1498Szrj is_lambda_ignored_entity (tree val)
1319*38fd1498Szrj {
1320*38fd1498Szrj   /* Look past normal capture proxies.  */
1321*38fd1498Szrj   if (is_normal_capture_proxy (val))
1322*38fd1498Szrj     return true;
1323*38fd1498Szrj 
1324*38fd1498Szrj   /* Always ignore lambda fields, their names are only for debugging.  */
1325*38fd1498Szrj   if (TREE_CODE (val) == FIELD_DECL
1326*38fd1498Szrj       && CLASSTYPE_LAMBDA_EXPR (DECL_CONTEXT (val)))
1327*38fd1498Szrj     return true;
1328*38fd1498Szrj 
1329*38fd1498Szrj   /* None of the lookups that use qualify_lookup want the op() from the
1330*38fd1498Szrj      lambda; they want the one from the enclosing class.  */
1331*38fd1498Szrj   if (TREE_CODE (val) == FUNCTION_DECL && LAMBDA_FUNCTION_P (val))
1332*38fd1498Szrj     return true;
1333*38fd1498Szrj 
1334*38fd1498Szrj   return false;
1335*38fd1498Szrj }
1336*38fd1498Szrj 
1337*38fd1498Szrj /* Lambdas that appear in variable initializer or default argument scope
1338*38fd1498Szrj    get that in their mangling, so we need to record it.  We might as well
1339*38fd1498Szrj    use the count for function and namespace scopes as well.  */
1340*38fd1498Szrj static GTY(()) tree lambda_scope;
1341*38fd1498Szrj static GTY(()) int lambda_count;
1342*38fd1498Szrj struct GTY(()) tree_int
1343*38fd1498Szrj {
1344*38fd1498Szrj   tree t;
1345*38fd1498Szrj   int i;
1346*38fd1498Szrj };
1347*38fd1498Szrj static GTY(()) vec<tree_int, va_gc> *lambda_scope_stack;
1348*38fd1498Szrj 
1349*38fd1498Szrj void
1350*38fd1498Szrj start_lambda_scope (tree decl)
1351*38fd1498Szrj {
1352*38fd1498Szrj   tree_int ti;
1353*38fd1498Szrj   gcc_assert (decl);
1354*38fd1498Szrj   /* Once we're inside a function, we ignore variable scope and just push
1355*38fd1498Szrj      the function again so that popping works properly.  */
1356*38fd1498Szrj   if (current_function_decl && TREE_CODE (decl) == VAR_DECL)
1357*38fd1498Szrj     decl = current_function_decl;
1358*38fd1498Szrj   ti.t = lambda_scope;
1359*38fd1498Szrj   ti.i = lambda_count;
1360*38fd1498Szrj   vec_safe_push (lambda_scope_stack, ti);
1361*38fd1498Szrj   if (lambda_scope != decl)
1362*38fd1498Szrj     {
1363*38fd1498Szrj       /* Don't reset the count if we're still in the same function.  */
1364*38fd1498Szrj       lambda_scope = decl;
1365*38fd1498Szrj       lambda_count = 0;
1366*38fd1498Szrj     }
1367*38fd1498Szrj }
1368*38fd1498Szrj 
1369*38fd1498Szrj void
1370*38fd1498Szrj record_lambda_scope (tree lambda)
1371*38fd1498Szrj {
1372*38fd1498Szrj   LAMBDA_EXPR_EXTRA_SCOPE (lambda) = lambda_scope;
1373*38fd1498Szrj   LAMBDA_EXPR_DISCRIMINATOR (lambda) = lambda_count++;
1374*38fd1498Szrj }
1375*38fd1498Szrj 
1376*38fd1498Szrj void
1377*38fd1498Szrj finish_lambda_scope (void)
1378*38fd1498Szrj {
1379*38fd1498Szrj   tree_int *p = &lambda_scope_stack->last ();
1380*38fd1498Szrj   if (lambda_scope != p->t)
1381*38fd1498Szrj     {
1382*38fd1498Szrj       lambda_scope = p->t;
1383*38fd1498Szrj       lambda_count = p->i;
1384*38fd1498Szrj     }
1385*38fd1498Szrj   lambda_scope_stack->pop ();
1386*38fd1498Szrj }
1387*38fd1498Szrj 
1388*38fd1498Szrj tree
1389*38fd1498Szrj start_lambda_function (tree fco, tree lambda_expr)
1390*38fd1498Szrj {
1391*38fd1498Szrj   /* Let the front end know that we are going to be defining this
1392*38fd1498Szrj      function.  */
1393*38fd1498Szrj   start_preparsed_function (fco,
1394*38fd1498Szrj 			    NULL_TREE,
1395*38fd1498Szrj 			    SF_PRE_PARSED | SF_INCLASS_INLINE);
1396*38fd1498Szrj 
1397*38fd1498Szrj   tree body = begin_function_body ();
1398*38fd1498Szrj 
1399*38fd1498Szrj   /* Push the proxies for any explicit captures.  */
1400*38fd1498Szrj   for (tree cap = LAMBDA_EXPR_CAPTURE_LIST (lambda_expr); cap;
1401*38fd1498Szrj        cap = TREE_CHAIN (cap))
1402*38fd1498Szrj     build_capture_proxy (TREE_PURPOSE (cap), TREE_VALUE (cap));
1403*38fd1498Szrj 
1404*38fd1498Szrj   return body;
1405*38fd1498Szrj }
1406*38fd1498Szrj 
1407*38fd1498Szrj /* Subroutine of prune_lambda_captures: CAP is a node in
1408*38fd1498Szrj    LAMBDA_EXPR_CAPTURE_LIST.  Return the variable it captures for which we
1409*38fd1498Szrj    might optimize away the capture, or NULL_TREE if there is no such
1410*38fd1498Szrj    variable.  */
1411*38fd1498Szrj 
1412*38fd1498Szrj static tree
1413*38fd1498Szrj var_to_maybe_prune (tree cap)
1414*38fd1498Szrj {
1415*38fd1498Szrj   if (LAMBDA_CAPTURE_EXPLICIT_P (cap))
1416*38fd1498Szrj     /* Don't prune explicit captures.  */
1417*38fd1498Szrj     return NULL_TREE;
1418*38fd1498Szrj 
1419*38fd1498Szrj   tree mem = TREE_PURPOSE (cap);
1420*38fd1498Szrj   if (!DECL_P (mem) || !DECL_NORMAL_CAPTURE_P (mem))
1421*38fd1498Szrj     /* Packs and init-captures aren't captures of constant vars.  */
1422*38fd1498Szrj     return NULL_TREE;
1423*38fd1498Szrj 
1424*38fd1498Szrj   tree init = TREE_VALUE (cap);
1425*38fd1498Szrj   if (is_normal_capture_proxy (init))
1426*38fd1498Szrj     init = DECL_CAPTURED_VARIABLE (init);
1427*38fd1498Szrj   if (decl_constant_var_p (init))
1428*38fd1498Szrj     return init;
1429*38fd1498Szrj 
1430*38fd1498Szrj   return NULL_TREE;
1431*38fd1498Szrj }
1432*38fd1498Szrj 
1433*38fd1498Szrj /* walk_tree helper for prune_lambda_captures: Remember which capture proxies
1434*38fd1498Szrj    for constant variables are actually used in the lambda body.
1435*38fd1498Szrj 
1436*38fd1498Szrj    There will always be a DECL_EXPR for the capture proxy; remember it when we
1437*38fd1498Szrj    see it, but replace it with any other use.  */
1438*38fd1498Szrj 
1439*38fd1498Szrj static tree
1440*38fd1498Szrj mark_const_cap_r (tree *t, int *walk_subtrees, void *data)
1441*38fd1498Szrj {
1442*38fd1498Szrj   hash_map<tree,tree*> &const_vars = *(hash_map<tree,tree*>*)data;
1443*38fd1498Szrj 
1444*38fd1498Szrj   tree var = NULL_TREE;
1445*38fd1498Szrj   if (TREE_CODE (*t) == DECL_EXPR)
1446*38fd1498Szrj     {
1447*38fd1498Szrj       tree decl = DECL_EXPR_DECL (*t);
1448*38fd1498Szrj       if (is_constant_capture_proxy (decl))
1449*38fd1498Szrj 	var = DECL_CAPTURED_VARIABLE (decl);
1450*38fd1498Szrj       *walk_subtrees = 0;
1451*38fd1498Szrj     }
1452*38fd1498Szrj   else if (is_constant_capture_proxy (*t))
1453*38fd1498Szrj     var = DECL_CAPTURED_VARIABLE (*t);
1454*38fd1498Szrj 
1455*38fd1498Szrj   if (var)
1456*38fd1498Szrj     {
1457*38fd1498Szrj       tree *&slot = const_vars.get_or_insert (var);
1458*38fd1498Szrj       if (!slot || VAR_P (*t))
1459*38fd1498Szrj 	slot = t;
1460*38fd1498Szrj     }
1461*38fd1498Szrj 
1462*38fd1498Szrj   return NULL_TREE;
1463*38fd1498Szrj }
1464*38fd1498Szrj 
1465*38fd1498Szrj /* We're at the end of processing a lambda; go back and remove any captures of
1466*38fd1498Szrj    constant variables for which we've folded away all uses.  */
1467*38fd1498Szrj 
1468*38fd1498Szrj static void
1469*38fd1498Szrj prune_lambda_captures (tree body)
1470*38fd1498Szrj {
1471*38fd1498Szrj   tree lam = current_lambda_expr ();
1472*38fd1498Szrj   if (!LAMBDA_EXPR_CAPTURE_OPTIMIZED (lam))
1473*38fd1498Szrj     /* No uses were optimized away.  */
1474*38fd1498Szrj     return;
1475*38fd1498Szrj   if (LAMBDA_EXPR_DEFAULT_CAPTURE_MODE (lam) == CPLD_NONE)
1476*38fd1498Szrj     /* No default captures, and we don't prune explicit captures.  */
1477*38fd1498Szrj     return;
1478*38fd1498Szrj 
1479*38fd1498Szrj   hash_map<tree,tree*> const_vars;
1480*38fd1498Szrj 
1481*38fd1498Szrj   cp_walk_tree_without_duplicates (&body, mark_const_cap_r, &const_vars);
1482*38fd1498Szrj 
1483*38fd1498Szrj   tree *fieldp = &TYPE_FIELDS (LAMBDA_EXPR_CLOSURE (lam));
1484*38fd1498Szrj   for (tree *capp = &LAMBDA_EXPR_CAPTURE_LIST (lam); *capp; )
1485*38fd1498Szrj     {
1486*38fd1498Szrj       tree cap = *capp;
1487*38fd1498Szrj       if (tree var = var_to_maybe_prune (cap))
1488*38fd1498Szrj 	{
1489*38fd1498Szrj 	  tree *use = *const_vars.get (var);
1490*38fd1498Szrj 	  if (TREE_CODE (*use) == DECL_EXPR)
1491*38fd1498Szrj 	    {
1492*38fd1498Szrj 	      /* All uses of this capture were folded away, leaving only the
1493*38fd1498Szrj 		 proxy declaration.  */
1494*38fd1498Szrj 
1495*38fd1498Szrj 	      /* Splice the capture out of LAMBDA_EXPR_CAPTURE_LIST.  */
1496*38fd1498Szrj 	      *capp = TREE_CHAIN (cap);
1497*38fd1498Szrj 
1498*38fd1498Szrj 	      /* And out of TYPE_FIELDS.  */
1499*38fd1498Szrj 	      tree field = TREE_PURPOSE (cap);
1500*38fd1498Szrj 	      while (*fieldp != field)
1501*38fd1498Szrj 		fieldp = &DECL_CHAIN (*fieldp);
1502*38fd1498Szrj 	      *fieldp = DECL_CHAIN (*fieldp);
1503*38fd1498Szrj 
1504*38fd1498Szrj 	      /* And remove the capture proxy declaration.  */
1505*38fd1498Szrj 	      *use = void_node;
1506*38fd1498Szrj 	      continue;
1507*38fd1498Szrj 	    }
1508*38fd1498Szrj 	}
1509*38fd1498Szrj 
1510*38fd1498Szrj       capp = &TREE_CHAIN (cap);
1511*38fd1498Szrj     }
1512*38fd1498Szrj }
1513*38fd1498Szrj 
1514*38fd1498Szrj void
1515*38fd1498Szrj finish_lambda_function (tree body)
1516*38fd1498Szrj {
1517*38fd1498Szrj   finish_function_body (body);
1518*38fd1498Szrj 
1519*38fd1498Szrj   prune_lambda_captures (body);
1520*38fd1498Szrj 
1521*38fd1498Szrj   /* Finish the function and generate code for it if necessary.  */
1522*38fd1498Szrj   tree fn = finish_function (/*inline_p=*/true);
1523*38fd1498Szrj 
1524*38fd1498Szrj   /* Only expand if the call op is not a template.  */
1525*38fd1498Szrj   if (!DECL_TEMPLATE_INFO (fn))
1526*38fd1498Szrj     expand_or_defer_fn (fn);
1527*38fd1498Szrj }
1528*38fd1498Szrj 
1529*38fd1498Szrj #include "gt-cp-lambda.h"
1530