https://github.com/cor3ntin updated https://github.com/llvm/llvm-project/pull/131515
>From ae66e1cc48c721badc234ff5bc5a89aeb6cd2ea3 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Sun, 16 Mar 2025 14:04:15 +0100 Subject: [PATCH 01/15] [Clang][RFC] Intrododuce a builtin to determine the number of bindings that would be produced by ```cpp auto [...p] = expr; ``` This is necessary to implement P2300 (https://eel.is/c++draft/exec#snd.concepts-5), but can also be used to implement a general get<N> function that supports aggregates __builtin_structured_binding_size works like sizeof in that it supports both type and expression arguments. If the argument cannot be destructured, a sfinae-friendly error is produced. A type is considered a valid tuple if `std::tuple_size_v<T>` is a valid expression, even if there is no valid `std::tuple_element` specialization or suitable `get` function for that type. This is modeled as a UnaryExprOrTypeTraitExpr, but it is wrapped in a ConstantExpr because the structured binding size can only be established during sema. --- clang/docs/LanguageExtensions.rst | 30 ++++ clang/docs/ReleaseNotes.rst | 3 + .../clang/Basic/DiagnosticSemaKinds.td | 2 + clang/include/clang/Basic/TokenKinds.def | 2 +- clang/include/clang/Sema/Sema.h | 3 +- clang/lib/AST/ByteCode/Compiler.cpp | 2 + clang/lib/AST/ExprConstant.cpp | 5 + clang/lib/AST/ItaniumMangle.cpp | 9 + clang/lib/Parse/ParseExpr.cpp | 13 +- clang/lib/Sema/SemaDeclCXX.cpp | 123 +++++++++---- clang/lib/Sema/SemaExpr.cpp | 69 ++++++- clang/test/CodeGenCXX/builtins.cpp | 6 + .../mangle-structured-binding-size.cpp | 12 ++ .../builtin-structured-binding-size.cpp | 168 ++++++++++++++++++ 14 files changed, 405 insertions(+), 42 deletions(-) create mode 100644 clang/test/CodeGenCXX/mangle-structured-binding-size.cpp create mode 100644 clang/test/SemaCXX/builtin-structured-binding-size.cpp diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index cc12ff5bad353..9a5cd8f1e5f5d 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -434,6 +434,36 @@ __datasizeof ``__datasizeof`` behaves like ``sizeof``, except that it returns the size of the type ignoring tail padding. +.. _builtin_structured_binding_size-doc: + +__builtin_structured_binding_size (C++) +--------------------------------------- +``__builtin_structured_binding_size`` returns the *structured binding size* +([dcl.struct.bind]) of the type ``T`` (or unevaluate expression ``arg``) +passed as argument. + +This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = arg;``. +If the argument is not destructurable (ie not an array, vector, complex, +*tuple-like* type or destructurable class type), ``__builtin_structured_binding_size(T)`` +is not a valid expression (``__builtin_structured_binding_size`` is SFINEA-friendly). + +A type is considered a valid tuple if ``std::tuple_size_v<T>`` is a valid expression, +even if there is no valid ``std::tuple_element`` specialization or suitable +``get`` function for that type. + +.. code-block:: c++ + + template<std::size_t Idx, typename T> + requires (Idx < __builtin_structured_binding_size(T)) + decltype(auto) constexpr get_binding(T&& obj) { + auto && [...p] = std::forward<T>(obj); + return p...[Idx]; + } + struct S { int a = 0, b = 42; }; + static_assert(__builtin_structured_binding_size(S) == 2); + static_assert(get_binding<1>(S{}) == 42); + + _BitInt, _ExtInt ---------------- diff --git a/clang/docs/ReleaseNotes.rst b/clang/docs/ReleaseNotes.rst index 2a1c5ee2d788e..f49e389773e4e 100644 --- a/clang/docs/ReleaseNotes.rst +++ b/clang/docs/ReleaseNotes.rst @@ -74,6 +74,9 @@ What's New in Clang |release|? C++ Language Changes -------------------- +- Added a :ref:`__builtin_structured_binding_size <builtin_structured_binding_size-doc>` (T) + builtin that returns the number of structured bindings that would be produced by destructuring ``T``. + C++2c Feature Support ^^^^^^^^^^^^^^^^^^^^^ diff --git a/clang/include/clang/Basic/DiagnosticSemaKinds.td b/clang/include/clang/Basic/DiagnosticSemaKinds.td index 86c9c955c1c78..fad826c1c6336 100644 --- a/clang/include/clang/Basic/DiagnosticSemaKinds.td +++ b/clang/include/clang/Basic/DiagnosticSemaKinds.td @@ -591,6 +591,8 @@ def err_decomp_decl_std_tuple_size_not_constant : Error< "is not a valid integral constant expression">; def note_in_binding_decl_init : Note< "in implicit initialization of binding declaration %0">; +def err_arg_is_not_destructurable : Error< + "type %0 is not destructurable">; def err_std_type_trait_not_class_template : Error< "unsupported standard library implementation: " diff --git a/clang/include/clang/Basic/TokenKinds.def b/clang/include/clang/Basic/TokenKinds.def index 397a5d95709fb..bad9387673ef9 100644 --- a/clang/include/clang/Basic/TokenKinds.def +++ b/clang/include/clang/Basic/TokenKinds.def @@ -553,8 +553,8 @@ TYPE_TRAIT_2(__reference_converts_from_temporary, ReferenceConvertsFromTemporary // IsDeducible is only used internally by clang for CTAD implementation and // is not exposed to users. TYPE_TRAIT_2(/*EmptySpellingName*/, IsDeducible, KEYCXX) - TYPE_TRAIT_1(__is_bitwise_cloneable, IsBitwiseCloneable, KEYALL) +UNARY_EXPR_OR_TYPE_TRAIT(__builtin_structured_binding_size, StructuredBindingSize, KEYCXX) // Embarcadero Expression Traits EXPRESSION_TRAIT(__is_lvalue_expr, IsLValueExpr, KEYCXX) diff --git a/clang/include/clang/Sema/Sema.h b/clang/include/clang/Sema/Sema.h index 657350fa843b9..cd7078b119712 100644 --- a/clang/include/clang/Sema/Sema.h +++ b/clang/include/clang/Sema/Sema.h @@ -6095,7 +6095,8 @@ class Sema final : public SemaBase { RecordDecl *ClassDecl, const IdentifierInfo *Name); - unsigned GetDecompositionElementCount(QualType DecompType); + std::optional<unsigned int> GetDecompositionElementCount(QualType DecompType, + SourceLocation Loc); void CheckCompleteDecompositionDeclaration(DecompositionDecl *DD); /// Stack containing information needed when in C++2a an 'auto' is encountered diff --git a/clang/lib/AST/ByteCode/Compiler.cpp b/clang/lib/AST/ByteCode/Compiler.cpp index b9f88230007b5..0259605086b21 100644 --- a/clang/lib/AST/ByteCode/Compiler.cpp +++ b/clang/lib/AST/ByteCode/Compiler.cpp @@ -2154,6 +2154,8 @@ bool Compiler<Emitter>::VisitUnaryExprOrTypeTraitExpr( E->getArgumentType()), E); } + assert(Kind != UETT_StructuredBindingSize && + "should have been evaluated in Sema"); return false; } diff --git a/clang/lib/AST/ExprConstant.cpp b/clang/lib/AST/ExprConstant.cpp index f8e8aaddbfdbd..1763bbc18043d 100644 --- a/clang/lib/AST/ExprConstant.cpp +++ b/clang/lib/AST/ExprConstant.cpp @@ -14878,6 +14878,11 @@ bool IntExprEvaluator::VisitUnaryExprOrTypeTraitExpr( } return Success(Sizeof, E); } + case UETT_StructuredBindingSize: + // This can only be computed from Sema and has been cached. + // We can still get there from code that strips the outer ConstantExpr. + return false; + case UETT_OpenMPRequiredSimdAlign: assert(E->isArgumentType()); return Success( diff --git a/clang/lib/AST/ItaniumMangle.cpp b/clang/lib/AST/ItaniumMangle.cpp index b6ba36784f38a..12993d5cb35f1 100644 --- a/clang/lib/AST/ItaniumMangle.cpp +++ b/clang/lib/AST/ItaniumMangle.cpp @@ -5389,6 +5389,15 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, Diags.Report(DiagID); return; } + case UETT_StructuredBindingSize: + Out << "u11__builtin_structured_binding_size"; + if (SAE->isArgumentType()) + mangleType(SAE->getArgumentType()); + else + mangleTemplateArgExpr(SAE->getArgumentExpr()); + Out << 'E'; + break; + return; } break; } diff --git a/clang/lib/Parse/ParseExpr.cpp b/clang/lib/Parse/ParseExpr.cpp index 0c28972d6ed8f..2e3f0ce3194f5 100644 --- a/clang/lib/Parse/ParseExpr.cpp +++ b/clang/lib/Parse/ParseExpr.cpp @@ -1544,6 +1544,7 @@ ExprResult Parser::ParseCastExpression(CastParseKind ParseKind, // unary-expression: '__builtin_omp_required_simd_align' '(' type-name ')' case tok::kw___builtin_omp_required_simd_align: case tok::kw___builtin_vectorelements: + case tok::kw___builtin_structured_binding_size: if (NotPrimaryExpression) *NotPrimaryExpression = true; AllowSuffix = false; @@ -2463,7 +2464,8 @@ Parser::ParseExprAfterUnaryExprOrTypeTrait(const Token &OpTok, tok::kw___datasizeof, tok::kw___alignof, tok::kw_alignof, tok::kw__Alignof, tok::kw_vec_step, tok::kw___builtin_omp_required_simd_align, - tok::kw___builtin_vectorelements) && + tok::kw___builtin_vectorelements, + tok::kw___builtin_structured_binding_size) && "Not a typeof/sizeof/alignof/vec_step expression!"); ExprResult Operand; @@ -2473,7 +2475,8 @@ Parser::ParseExprAfterUnaryExprOrTypeTrait(const Token &OpTok, // If construct allows a form without parenthesis, user may forget to put // pathenthesis around type name. if (OpTok.isOneOf(tok::kw_sizeof, tok::kw___datasizeof, tok::kw___alignof, - tok::kw_alignof, tok::kw__Alignof)) { + tok::kw_alignof, tok::kw__Alignof, + tok::kw___builtin_structured_binding_size)) { if (isTypeIdUnambiguously()) { DeclSpec DS(AttrFactory); ParseSpecifierQualifierList(DS); @@ -2599,7 +2602,8 @@ ExprResult Parser::ParseUnaryExprOrTypeTraitExpression() { assert(Tok.isOneOf(tok::kw_sizeof, tok::kw___datasizeof, tok::kw___alignof, tok::kw_alignof, tok::kw__Alignof, tok::kw_vec_step, tok::kw___builtin_omp_required_simd_align, - tok::kw___builtin_vectorelements) && + tok::kw___builtin_vectorelements, + tok::kw___builtin_structured_binding_size) && "Not a sizeof/alignof/vec_step expression!"); Token OpTok = Tok; ConsumeToken(); @@ -2687,6 +2691,9 @@ ExprResult Parser::ParseUnaryExprOrTypeTraitExpression() { case tok::kw___datasizeof: ExprKind = UETT_DataSizeOf; break; + case tok::kw___builtin_structured_binding_size: + ExprKind = UETT_StructuredBindingSize; + break; case tok::kw___builtin_vectorelements: ExprKind = UETT_VectorElements; break; diff --git a/clang/lib/Sema/SemaDeclCXX.cpp b/clang/lib/Sema/SemaDeclCXX.cpp index a02bd8335fa20..164e81e1cfa61 100644 --- a/clang/lib/Sema/SemaDeclCXX.cpp +++ b/clang/lib/Sema/SemaDeclCXX.cpp @@ -1475,6 +1475,48 @@ static DeclAccessPair findDecomposableBaseClass(Sema &S, SourceLocation Loc, return DeclAccessPair::make(const_cast<CXXRecordDecl*>(ClassWithFields), AS); } +static bool CheckMemberDecompositionFields(Sema &S, SourceLocation Loc, + const CXXRecordDecl *OrigRD, + QualType DecompType, + DeclAccessPair BasePair) { + const CXXRecordDecl *RD = cast_or_null<CXXRecordDecl>(BasePair.getDecl()); + if (!RD) + return true; + + for (auto *FD : RD->fields()) { + if (FD->isUnnamedBitField()) + continue; + + // All the non-static data members are required to be nameable, so they + // must all have names. + if (!FD->getDeclName()) { + if (RD->isLambda()) { + S.Diag(Loc, diag::err_decomp_decl_lambda); + S.Diag(RD->getLocation(), diag::note_lambda_decl); + return true; + } + + if (FD->isAnonymousStructOrUnion()) { + S.Diag(Loc, diag::err_decomp_decl_anon_union_member) + << DecompType << FD->getType()->isUnionType(); + S.Diag(FD->getLocation(), diag::note_declared_at); + return true; + } + + // FIXME: Are there any other ways we could have an anonymous member? + } + // The field must be accessible in the context of the structured binding. + // We already checked that the base class is accessible. + // FIXME: Add 'const' to AccessedEntity's classes so we can remove the + // const_cast here. + S.CheckStructuredBindingMemberAccess( + Loc, const_cast<CXXRecordDecl *>(OrigRD), + DeclAccessPair::make(FD, CXXRecordDecl::MergeAccess( + BasePair.getAccess(), FD->getAccess()))); + } + return false; +} + static bool checkMemberDecomposition(Sema &S, ArrayRef<BindingDecl*> Bindings, ValueDecl *Src, QualType DecompType, const CXXRecordDecl *OrigRD) { @@ -1503,43 +1545,20 @@ static bool checkMemberDecomposition(Sema &S, ArrayRef<BindingDecl*> Bindings, auto FlatBindings = DD->flat_bindings(); assert(llvm::range_size(FlatBindings) == NumFields); auto FlatBindingsItr = FlatBindings.begin(); + + if (CheckMemberDecompositionFields(S, Src->getLocation(), OrigRD, DecompType, + BasePair)) + return true; + for (auto *FD : RD->fields()) { if (FD->isUnnamedBitField()) continue; - // All the non-static data members are required to be nameable, so they - // must all have names. - if (!FD->getDeclName()) { - if (RD->isLambda()) { - S.Diag(Src->getLocation(), diag::err_decomp_decl_lambda); - S.Diag(RD->getLocation(), diag::note_lambda_decl); - return true; - } - - if (FD->isAnonymousStructOrUnion()) { - S.Diag(Src->getLocation(), diag::err_decomp_decl_anon_union_member) - << DecompType << FD->getType()->isUnionType(); - S.Diag(FD->getLocation(), diag::note_declared_at); - return true; - } - - // FIXME: Are there any other ways we could have an anonymous member? - } - // We have a real field to bind. assert(FlatBindingsItr != FlatBindings.end()); BindingDecl *B = *(FlatBindingsItr++); SourceLocation Loc = B->getLocation(); - // The field must be accessible in the context of the structured binding. - // We already checked that the base class is accessible. - // FIXME: Add 'const' to AccessedEntity's classes so we can remove the - // const_cast here. - S.CheckStructuredBindingMemberAccess( - Loc, const_cast<CXXRecordDecl *>(OrigRD), - DeclAccessPair::make(FD, CXXRecordDecl::MergeAccess( - BasePair.getAccess(), FD->getAccess()))); - // Initialize the binding to Src.FD. ExprResult E = S.BuildDeclRefExpr(Src, DecompType, VK_LValue, Loc); if (E.isInvalid()) @@ -1642,6 +1661,50 @@ void Sema::CheckCompleteDecompositionDeclaration(DecompositionDecl *DD) { DD->setInvalidDecl(); } +std::optional<unsigned> Sema::GetDecompositionElementCount(QualType T, + SourceLocation Loc) { + const ASTContext &Ctx = getASTContext(); + assert(!T->isDependentType()); + if (auto *CAT = Ctx.getAsConstantArrayType(T)) + return CAT->getSize().getZExtValue(); + if (auto *VT = T->getAs<VectorType>()) + return VT->getNumElements(); + if (T->getAs<ComplexType>()) + return 2; + + llvm::APSInt TupleSize(Ctx.getTypeSize(Ctx.getSizeType())); + switch (isTupleLike(*this, Loc, T, TupleSize)) { + case IsTupleLike::Error: + return {}; + case IsTupleLike::TupleLike: + return TupleSize.getExtValue(); + case IsTupleLike::NotTupleLike: + break; + } + CXXRecordDecl *OrigRD = T->getAsCXXRecordDecl(); + if (!OrigRD || OrigRD->isUnion()) { + return std::nullopt; + } + + if (RequireCompleteType(Loc, T, diag::err_incomplete_type)) + return std::nullopt; + + CXXCastPath BasePath; + DeclAccessPair BasePair = + findDecomposableBaseClass(*this, Loc, OrigRD, BasePath); + const CXXRecordDecl *RD = cast_or_null<CXXRecordDecl>(BasePair.getDecl()); + if (!RD) + return std::nullopt; + + unsigned NumFields = llvm::count_if( + RD->fields(), [](FieldDecl *FD) { return !FD->isUnnamedBitField(); }); + + if (CheckMemberDecompositionFields(*this, Loc, OrigRD, T, BasePair)) + return true; + + return NumFields; +} + void Sema::MergeVarDeclExceptionSpecs(VarDecl *New, VarDecl *Old) { // Shortcut if exceptions are disabled. if (!getLangOpts().CXXExceptions) @@ -17262,8 +17325,8 @@ void Sema::DiagnoseStaticAssertDetails(const Expr *E) { Expr::EvalResult Result; SmallString<12> ValueString; bool Print; - } DiagSide[2] = {{LHS, Expr::EvalResult(), {}, false}, - {RHS, Expr::EvalResult(), {}, false}}; + } DiagSide[2] = {{Op->getLHS(), Expr::EvalResult(), {}, false}, + {Op->getRHS(), Expr::EvalResult(), {}, false}}; for (unsigned I = 0; I < 2; I++) { const Expr *Side = DiagSide[I].Cond; diff --git a/clang/lib/Sema/SemaExpr.cpp b/clang/lib/Sema/SemaExpr.cpp index e19136b394800..8766331a0df59 100644 --- a/clang/lib/Sema/SemaExpr.cpp +++ b/clang/lib/Sema/SemaExpr.cpp @@ -4160,6 +4160,54 @@ static bool CheckVecStepTraitOperandType(Sema &S, QualType T, return false; } +static ExprResult BuildStructuredBindingSizeTraitImpl(Sema &S, QualType T, + Expr *E, + TypeSourceInfo *TInfo, + SourceLocation Loc, + SourceRange ArgRange) { + assert(!!E != !!TInfo); + assert(!T->isDependentType()); + std::optional<unsigned> Size = + S.GetDecompositionElementCount(T, ArgRange.getBegin()); + if (!Size) { + return S.Diag(Loc, diag::err_arg_is_not_destructurable) << T << ArgRange; + return ExprError(); + } + Expr *Inner; + if (E) + Inner = new (S.getASTContext()) UnaryExprOrTypeTraitExpr( + UnaryExprOrTypeTrait::UETT_StructuredBindingSize, E, + S.getASTContext().getSizeType(), Loc, E->getEndLoc()); + + else + Inner = new (S.getASTContext()) UnaryExprOrTypeTraitExpr( + UnaryExprOrTypeTrait::UETT_StructuredBindingSize, TInfo, + S.getASTContext().getSizeType(), Loc, ArgRange.getEnd()); + + // Computing the number of bindings requires Sema and is non-trivial, + // so we cache the result now. + llvm::APSInt V = + S.getASTContext().MakeIntValue(*Size, S.getASTContext().getSizeType()); + return ConstantExpr::Create(S.getASTContext(), Inner, APValue{V}); +} + +static ExprResult BuildStructuredBindingSizeTrait(Sema &S, + TypeSourceInfo *TInfo, + SourceLocation Loc, + SourceRange ArgRange) { + return BuildStructuredBindingSizeTraitImpl(S, TInfo->getType(), + /*Expr=*/nullptr, TInfo, Loc, + ArgRange); +} + +static ExprResult BuildStructuredBindingSizeTrait(Sema &S, SourceLocation OpLoc, + Expr *E) { + + return BuildStructuredBindingSizeTraitImpl(S, E->getType(), E, + /*TInfo=*/nullptr, OpLoc, + E->getSourceRange()); +} + static bool CheckVectorElementsTraitOperandType(Sema &S, QualType T, SourceLocation Loc, SourceRange ArgRange) { @@ -4650,10 +4698,14 @@ ExprResult Sema::CreateUnaryExprOrTypeTraitExpr(TypeSourceInfo *TInfo, QualType T = TInfo->getType(); - if (!T->isDependentType() && - CheckUnaryExprOrTypeTraitOperand(T, OpLoc, R, ExprKind, - getTraitSpelling(ExprKind))) - return ExprError(); + if (!T->isDependentType()) { + if (ExprKind == UETT_StructuredBindingSize) + return BuildStructuredBindingSizeTrait(*this, TInfo, OpLoc, R); + + if (CheckUnaryExprOrTypeTraitOperand(T, OpLoc, R, ExprKind, + getTraitSpelling(ExprKind))) + return ExprError(); + } // Adds overload of TransformToPotentiallyEvaluated for TypeSourceInfo to // properly deal with VLAs in nested calls of sizeof and typeof. @@ -4680,14 +4732,17 @@ Sema::CreateUnaryExprOrTypeTraitExpr(Expr *E, SourceLocation OpLoc, bool isInvalid = false; if (E->isTypeDependent()) { // Delay type-checking for type-dependent expressions. + } else if (ExprKind == UETT_StructuredBindingSize) { + // Custom logic + return BuildStructuredBindingSizeTrait(*this, OpLoc, E); } else if (ExprKind == UETT_AlignOf || ExprKind == UETT_PreferredAlignOf) { isInvalid = CheckAlignOfExpr(*this, E, ExprKind); } else if (ExprKind == UETT_VecStep) { isInvalid = CheckVecStepExpr(E); } else if (ExprKind == UETT_OpenMPRequiredSimdAlign) { - Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); - isInvalid = true; - } else if (E->refersToBitField()) { // C99 6.5.3.4p1. + Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); + isInvalid = true; + } else if (E->refersToBitField()) { // C99 6.5.3.4p1. Diag(E->getExprLoc(), diag::err_sizeof_alignof_typeof_bitfield) << 0; isInvalid = true; } else if (ExprKind == UETT_VectorElements) { diff --git a/clang/test/CodeGenCXX/builtins.cpp b/clang/test/CodeGenCXX/builtins.cpp index 37f9491d12d04..9169f3a3276d3 100644 --- a/clang/test/CodeGenCXX/builtins.cpp +++ b/clang/test/CodeGenCXX/builtins.cpp @@ -77,3 +77,9 @@ int constexpr_overflow_result() { // CHECK: [[RET_VAL:%.+]] = load i32, ptr [[Z]] // CHECK: ret i32 [[RET_VAL]] } + +int structured_binding_size() { + struct S2 {int a, b;}; + return __builtin_structured_binding_size(S2); + // CHECK: ret i32 2 +} diff --git a/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp b/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp new file mode 100644 index 0000000000000..5b53ed8d7166d --- /dev/null +++ b/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp @@ -0,0 +1,12 @@ +// RUN: %clang_cc1 -std=c++11 -emit-llvm %s -o - -triple=x86_64-linux-gnu | FileCheck %s + +struct S {}; + +template <class T> void f1(decltype(__builtin_structured_binding_size(T))) {} +template void f1<S>(__SIZE_TYPE__); +// CHECK: void @_Z2f1I1SEvDTu11__builtin_structured_binding_sizeT_EE + +template <class T> void f2(decltype(__builtin_structured_binding_size(T{}))) {} +template void f2<S>(__SIZE_TYPE__); +// CHECK: void @_Z2f2I1SEvDTu11__builtin_structured_binding_sizeXtlT_EEEE + diff --git a/clang/test/SemaCXX/builtin-structured-binding-size.cpp b/clang/test/SemaCXX/builtin-structured-binding-size.cpp new file mode 100644 index 0000000000000..460f2881ff5dc --- /dev/null +++ b/clang/test/SemaCXX/builtin-structured-binding-size.cpp @@ -0,0 +1,168 @@ +// RUN: %clang_cc1 %s -std=c++2c -fsyntax-only -verify + +struct S0 {}; +struct S1 {int a;}; +struct S2 {int a; int b;}; +struct S3 {double a; int b; int c;}; + + + +struct SD : S1 {}; +struct SE1 : S1 { int b;}; + +class P1 {int a;}; // #note-private + + +template <typename T> +concept is_destructurable = requires { + { __builtin_structured_binding_size(T) }; +}; + +static_assert(__builtin_structured_binding_size(S0) == 0); +static_assert(__is_same_as(decltype(__builtin_structured_binding_size(S0)), decltype(sizeof(void*)))); + +static_assert(__builtin_structured_binding_size(S1) == 0); +// expected-error@-1 {{static assertion failed due to requirement '__builtin_structured_binding_size(S1) == 0'}} \ +// expected-note@-1 {{expression evaluates to '1 == 0'}} +static_assert(__builtin_structured_binding_size(S1) == 1); +static_assert(__builtin_structured_binding_size(SD) == 1); +static_assert(__builtin_structured_binding_size(SE1) == 1); +// expected-error@-1 {{cannot decompose class type 'SE1': both it and its base class 'S1' have non-static data members}} \ +// expected-error@-1 {{type 'SE1' is not destructurable}} + + +static_assert(__builtin_structured_binding_size(int[0]) == 0); +static_assert(__builtin_structured_binding_size(int[1]) == 1); +static_assert(__builtin_structured_binding_size(int[42]) == 42); + +using vec2 = int __attribute__((__vector_size__(2 * sizeof(int)))); +using vec3 = int __attribute__((__vector_size__(3 * sizeof(int)))); +static_assert(__builtin_structured_binding_size(vec2) == 2); +static_assert(__builtin_structured_binding_size(vec3) == 3); +static_assert(__builtin_structured_binding_size(__builtin_complex(0., 0.)) == 2); +static_assert(__builtin_structured_binding_size(decltype(__builtin_complex(0., 0.))) == 2); + + +int VLASize; // expected-note {{declared here}} +static_assert(__builtin_structured_binding_size(int[VLASize]) == 42); +// expected-error@-1 {{type 'int[VLASize]' is not destructurable}} \ +// expected-warning@-1 {{variable length arrays in C++ are a Clang extension}} \ +// expected-note@-1 {{read of non-const variable 'VLASize' is not allowed in a constant expression}} + + +struct Incomplete; // expected-note {{forward declaration of 'Incomplete'}} +static_assert(__builtin_structured_binding_size(Incomplete) == 1); +// expected-error@-1 {{incomplete type 'Incomplete' where a complete type is required}} \ +// expected-error@-1 {{type 'Incomplete' is not destructurable}} +static_assert(__builtin_structured_binding_size(Incomplete[]) == 1); +// expected-error@-1 {{type 'Incomplete[]' is not destructurable}} +static_assert(__builtin_structured_binding_size(Incomplete[0]) == 0); +static_assert(__builtin_structured_binding_size(Incomplete[1]) == 1); +static_assert(__builtin_structured_binding_size(Incomplete[42]) == 42); + + +static_assert(__builtin_structured_binding_size(P1) == 0); +// expected-error@-1 {{static assertion failed due to requirement '__builtin_structured_binding_size(P1) == 0'}} \ +// expected-note@-1 {{expression evaluates to '1 == 0'}} \ +// expected-error@-1 {{cannot decompose private member 'a' of 'P1}} \ +// expected-note@#note-private {{implicitly declared private here}} + + +static_assert(is_destructurable<S0>); +static_assert(is_destructurable<S1>); +static_assert(!is_destructurable<SE1>); +static_assert(!is_destructurable<int>); +static_assert(!is_destructurable<int[]>); +static_assert(is_destructurable<int[1]>); +static_assert(!is_destructurable<P1>); + +template <typename T> +constexpr int f() {return 0;}; +template <typename T> +requires is_destructurable<T> +constexpr int f() {return 1;}; + +static_assert(f<int>() == 0); +static_assert(f<S0>() == 1); + +struct T0; +struct T1; +struct T42; +struct TSizeError; + +namespace std { + +template <typename> +struct tuple_size; + +template <> +struct tuple_size<T0> { + static constexpr int value = 0; +}; + +template <> +struct tuple_size<T1> { + static constexpr int value = 1; +}; + +template <> +struct tuple_size<T42> { + static constexpr int value = 42; +}; + +template <> +struct tuple_size<TSizeError> { + static constexpr void* value = nullptr; +}; + +static_assert(__builtin_structured_binding_size(T0) == 0); +static_assert(__builtin_structured_binding_size(T1) == 1); +static_assert(__builtin_structured_binding_size(T42) == 42); +static_assert(__builtin_structured_binding_size(TSizeError) == 42); +// expected-error@-1 {{cannot decompose this type; 'std::tuple_size<TSizeError>::value' is not a valid integral constant expression}} \ +// expected-error@-1 {{type 'TSizeError' is not destructurable}} +static_assert(!is_destructurable<TSizeError>); +} + + +void test_expr(S1 & s1, S2 && s2, T0 & t0, int i, const S1 & s1c, int arr[2]) { + static_assert(__builtin_structured_binding_size(s1) == 1); + static_assert(__builtin_structured_binding_size(s1c) == 1); + static_assert(__builtin_structured_binding_size(s2) == 2); + static_assert(__builtin_structured_binding_size(t0) == 0); + static_assert(__builtin_structured_binding_size(i)); + // expected-error@-1 {{type 'int' is not destructurable}} + static_assert(__builtin_structured_binding_size(arr) == 1); + // expected-error@-1 {{type 'int *' is not destructurable}} +} + + +// Check we can implement std::exec::tag_of_t +template <typename T> +struct type_identity { + using type = T; +}; +template<typename T> T &&declval(); + +template <typename T> +requires (__builtin_structured_binding_size(T) >=2) +consteval auto tag_of_impl(T& t) { + auto && [tag, ..._] = t; + return type_identity<decltype(auto(tag))>{}; +} + +template <typename T> +requires (__builtin_structured_binding_size(T) >=2) // #tag-of-constr +using tag_of_t = decltype(tag_of_impl(declval<T&>()))::type; + +static_assert(__is_same_as(tag_of_t<S2>, int)); +static_assert(__is_same_as(tag_of_t<S3>, double)); + + +static_assert(__is_same_as(tag_of_t<S1>, int)); +// expected-error@-1 {{constraints not satisfied for alias template 'tag_of_t' [with T = S1]}} \ +// expected-note@#tag-of-constr {{because '__builtin_structured_binding_size(S1) >= 2' (1 >= 2) evaluated to false}} + +static_assert(__is_same_as(tag_of_t<int>, int)); // error +// expected-error@-1 {{constraints not satisfied for alias template 'tag_of_t' [with T = int]}} +// expected-note@#tag-of-constr {{because substituted constraint expression is ill-formed: type 'int' is not destructurable}} >From f706e54760b5527e2b5749d29af0913a346e7695 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Sun, 16 Mar 2025 15:16:32 +0100 Subject: [PATCH 02/15] fix tests --- clang/include/clang/AST/Stmt.h | 2 +- clang/lib/Sema/SemaDeclCXX.cpp | 12 ++++++++++-- 2 files changed, 11 insertions(+), 3 deletions(-) diff --git a/clang/include/clang/AST/Stmt.h b/clang/include/clang/AST/Stmt.h index 604ac51d478cf..476aa2c8c393a 100644 --- a/clang/include/clang/AST/Stmt.h +++ b/clang/include/clang/AST/Stmt.h @@ -531,7 +531,7 @@ class alignas(void *) Stmt { unsigned : NumExprBits; LLVM_PREFERRED_TYPE(UnaryExprOrTypeTrait) - unsigned Kind : 3; + unsigned Kind : 4; LLVM_PREFERRED_TYPE(bool) unsigned IsType : 1; // true if operand is a type, false if an expression. }; diff --git a/clang/lib/Sema/SemaDeclCXX.cpp b/clang/lib/Sema/SemaDeclCXX.cpp index 164e81e1cfa61..53ca94011f158 100644 --- a/clang/lib/Sema/SemaDeclCXX.cpp +++ b/clang/lib/Sema/SemaDeclCXX.cpp @@ -17320,13 +17320,21 @@ void Sema::DiagnoseStaticAssertDetails(const Expr *E) { if (!UsefulToPrintExpr(LHS) && !UsefulToPrintExpr(RHS)) return; + auto UseCachedValue = [](const Expr *Outer, const Expr *Inner) { + if (const ConstantExpr *E = dyn_cast<ConstantExpr>(Outer); + E && !E->getAPValueResult().isAbsent()) + return Outer; + return Inner; + }; + struct { const clang::Expr *Cond; Expr::EvalResult Result; SmallString<12> ValueString; bool Print; - } DiagSide[2] = {{Op->getLHS(), Expr::EvalResult(), {}, false}, - {Op->getRHS(), Expr::EvalResult(), {}, false}}; + } DiagSide[2] = { + {UseCachedValue(Op->getLHS(), LHS), Expr::EvalResult(), {}, false}, + {UseCachedValue(Op->getRHS(), RHS), Expr::EvalResult(), {}, false}}; for (unsigned I = 0; I < 2; I++) { const Expr *Side = DiagSide[I].Cond; >From 766d4083b1e104ab5e6c9f717081ff298437e6e6 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 09:08:23 +0100 Subject: [PATCH 03/15] fix mangling --- clang/docs/LanguageExtensions.rst | 2 +- clang/lib/AST/ItaniumMangle.cpp | 75 +++++++------------ .../mangle-structured-binding-size.cpp | 4 +- 3 files changed, 28 insertions(+), 53 deletions(-) diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index 9a5cd8f1e5f5d..33087ff9307b7 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -439,7 +439,7 @@ type ignoring tail padding. __builtin_structured_binding_size (C++) --------------------------------------- ``__builtin_structured_binding_size`` returns the *structured binding size* -([dcl.struct.bind]) of the type ``T`` (or unevaluate expression ``arg``) +([dcl.struct.bind]) of the type ``T`` (or unevaluated expression ``arg``) passed as argument. This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = arg;``. diff --git a/clang/lib/AST/ItaniumMangle.cpp b/clang/lib/AST/ItaniumMangle.cpp index 12993d5cb35f1..2e887849ebe8a 100644 --- a/clang/lib/AST/ItaniumMangle.cpp +++ b/clang/lib/AST/ItaniumMangle.cpp @@ -5327,7 +5327,19 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, } }; - switch(SAE->getKind()) { + auto MangleExtensionBuiltin = [&](const UnaryExprOrTypeTraitExpr *E, + StringRef Name = {}) { + if (Name.empty()) + Name = getTraitSpelling(E->getKind()); + Out << 'u' << Name.size() << Name; + if (SAE->isArgumentType()) + mangleType(SAE->getArgumentType()); + else + mangleTemplateArgExpr(SAE->getArgumentExpr()); + Out << 'E'; + }; + + switch (SAE->getKind()) { case UETT_SizeOf: Out << 's'; MangleAlignofSizeofArg(); @@ -5337,12 +5349,7 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, // have acted differently since Clang 8, but were previously mangled the // same.) if (!isCompatibleWith(LangOptions::ClangABI::Ver11)) { - Out << "u11__alignof__"; - if (SAE->isArgumentType()) - mangleType(SAE->getArgumentType()); - else - mangleTemplateArgExpr(SAE->getArgumentExpr()); - Out << 'E'; + MangleExtensionBuiltin(SAE, "__alignof"); break; } [[fallthrough]]; @@ -5350,54 +5357,22 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, Out << 'a'; MangleAlignofSizeofArg(); break; + + case UETT_StructuredBindingSize: + MangleExtensionBuiltin(SAE); + break; + + case UETT_VectorElements: + case UETT_OpenMPRequiredSimdAlign: + case UETT_VecStep: + case UETT_PtrAuthTypeDiscriminator: case UETT_DataSizeOf: { - DiagnosticsEngine &Diags = Context.getDiags(); - unsigned DiagID = - Diags.getCustomDiagID(DiagnosticsEngine::Error, - "cannot yet mangle __datasizeof expression"); - Diags.Report(DiagID); - return; - } - case UETT_PtrAuthTypeDiscriminator: { DiagnosticsEngine &Diags = Context.getDiags(); unsigned DiagID = Diags.getCustomDiagID( - DiagnosticsEngine::Error, - "cannot yet mangle __builtin_ptrauth_type_discriminator expression"); - Diags.Report(E->getExprLoc(), DiagID); + DiagnosticsEngine::Error, "cannot yet mangle %0 expression"); + Diags.Report(E->getExprLoc(), DiagID) << getTraitSpelling(SAE->getKind()); return; } - case UETT_VecStep: { - DiagnosticsEngine &Diags = Context.getDiags(); - unsigned DiagID = Diags.getCustomDiagID(DiagnosticsEngine::Error, - "cannot yet mangle vec_step expression"); - Diags.Report(DiagID); - return; - } - case UETT_OpenMPRequiredSimdAlign: { - DiagnosticsEngine &Diags = Context.getDiags(); - unsigned DiagID = Diags.getCustomDiagID( - DiagnosticsEngine::Error, - "cannot yet mangle __builtin_omp_required_simd_align expression"); - Diags.Report(DiagID); - return; - } - case UETT_VectorElements: { - DiagnosticsEngine &Diags = Context.getDiags(); - unsigned DiagID = Diags.getCustomDiagID( - DiagnosticsEngine::Error, - "cannot yet mangle __builtin_vectorelements expression"); - Diags.Report(DiagID); - return; - } - case UETT_StructuredBindingSize: - Out << "u11__builtin_structured_binding_size"; - if (SAE->isArgumentType()) - mangleType(SAE->getArgumentType()); - else - mangleTemplateArgExpr(SAE->getArgumentExpr()); - Out << 'E'; - break; - return; } break; } diff --git a/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp b/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp index 5b53ed8d7166d..80e4063b9d556 100644 --- a/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp +++ b/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp @@ -4,9 +4,9 @@ struct S {}; template <class T> void f1(decltype(__builtin_structured_binding_size(T))) {} template void f1<S>(__SIZE_TYPE__); -// CHECK: void @_Z2f1I1SEvDTu11__builtin_structured_binding_sizeT_EE +// CHECK: void @_Z2f1I1SEvDTu33__builtin_structured_binding_sizeT_EE template <class T> void f2(decltype(__builtin_structured_binding_size(T{}))) {} template void f2<S>(__SIZE_TYPE__); -// CHECK: void @_Z2f2I1SEvDTu11__builtin_structured_binding_sizeXtlT_EEEE +// CHECK: void @_Z2f2I1SEvDTu33__builtin_structured_binding_sizeXtlT_EEEE >From d9d04595707a877b598ec28dd990aa36129a935e Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 09:48:36 +0100 Subject: [PATCH 04/15] Clarify docs --- clang/docs/LanguageExtensions.rst | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index 33087ff9307b7..3a52e16ad0c6d 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -443,11 +443,12 @@ __builtin_structured_binding_size (C++) passed as argument. This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = arg;``. -If the argument is not destructurable (ie not an array, vector, complex, -*tuple-like* type or destructurable class type), ``__builtin_structured_binding_size(T)`` -is not a valid expression (``__builtin_structured_binding_size`` is SFINEA-friendly). +If the argument is not destructurable (ie not a builtin array, builtin SIMD vector, +builtin complex, *tuple-like* type or destructurable class type), +``__builtin_structured_binding_size(T)`` is not a valid expression +(``__builtin_structured_binding_size`` is SFINEA-friendly). -A type is considered a valid tuple if ``std::tuple_size_v<T>`` is a valid expression, +A type is considered a valid *tuple-like* if ``std::tuple_size_v<T>`` is a valid expression, even if there is no valid ``std::tuple_element`` specialization or suitable ``get`` function for that type. >From 556e08abe9297f6d3bcaabdb75e17384a887b3b4 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 10:05:15 +0100 Subject: [PATCH 05/15] remove extraneous returm statement --- clang/lib/Sema/SemaExpr.cpp | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/clang/lib/Sema/SemaExpr.cpp b/clang/lib/Sema/SemaExpr.cpp index 8766331a0df59..0d26ed506e6fb 100644 --- a/clang/lib/Sema/SemaExpr.cpp +++ b/clang/lib/Sema/SemaExpr.cpp @@ -4169,10 +4169,10 @@ static ExprResult BuildStructuredBindingSizeTraitImpl(Sema &S, QualType T, assert(!T->isDependentType()); std::optional<unsigned> Size = S.GetDecompositionElementCount(T, ArgRange.getBegin()); - if (!Size) { + + if (!Size) return S.Diag(Loc, diag::err_arg_is_not_destructurable) << T << ArgRange; - return ExprError(); - } + Expr *Inner; if (E) Inner = new (S.getASTContext()) UnaryExprOrTypeTraitExpr( >From e9b51623d690be2607d8566357c1cd0b6b27cf75 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 14:11:06 +0100 Subject: [PATCH 06/15] fix __alignof mangling --- clang/lib/AST/ItaniumMangle.cpp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/clang/lib/AST/ItaniumMangle.cpp b/clang/lib/AST/ItaniumMangle.cpp index 2e887849ebe8a..babfec5e45290 100644 --- a/clang/lib/AST/ItaniumMangle.cpp +++ b/clang/lib/AST/ItaniumMangle.cpp @@ -5349,7 +5349,7 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, // have acted differently since Clang 8, but were previously mangled the // same.) if (!isCompatibleWith(LangOptions::ClangABI::Ver11)) { - MangleExtensionBuiltin(SAE, "__alignof"); + MangleExtensionBuiltin(SAE, "__alignof__"); break; } [[fallthrough]]; >From d08ccf644dbe642bba21fe425d934606441f5161 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 15:08:00 +0100 Subject: [PATCH 07/15] use mangleVendorType --- clang/lib/AST/ItaniumMangle.cpp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/clang/lib/AST/ItaniumMangle.cpp b/clang/lib/AST/ItaniumMangle.cpp index babfec5e45290..6bbede5b10684 100644 --- a/clang/lib/AST/ItaniumMangle.cpp +++ b/clang/lib/AST/ItaniumMangle.cpp @@ -5331,7 +5331,7 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, StringRef Name = {}) { if (Name.empty()) Name = getTraitSpelling(E->getKind()); - Out << 'u' << Name.size() << Name; + mangleVendorType(Name); if (SAE->isArgumentType()) mangleType(SAE->getArgumentType()); else >From 178e462bc98560748b4201cac893e21d856fd298 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 17:12:58 +0100 Subject: [PATCH 08/15] model the builtin as a type trait --- clang/docs/LanguageExtensions.rst | 62 +++++++++--------- clang/include/clang/AST/ExprCXX.h | 29 ++++++++- clang/include/clang/AST/Stmt.h | 10 +-- clang/include/clang/Basic/TokenKinds.def | 2 +- clang/lib/AST/ASTImporter.cpp | 13 ++-- clang/lib/AST/ByteCode/Compiler.cpp | 12 ++-- clang/lib/AST/ExprCXX.cpp | 40 +++++++++++- clang/lib/AST/ExprConstant.cpp | 12 ++-- clang/lib/AST/ItaniumMangle.cpp | 4 -- clang/lib/CodeGen/CGExprScalar.cpp | 7 ++- clang/lib/Parse/ParseExpr.cpp | 13 +--- clang/lib/Sema/SemaDeclCXX.cpp | 12 +--- clang/lib/Sema/SemaExpr.cpp | 63 ++----------------- clang/lib/Sema/SemaExprCXX.cpp | 41 ++++++++++++ clang/lib/Serialization/ASTReaderStmt.cpp | 10 ++- clang/lib/Serialization/ASTWriterStmt.cpp | 5 ++ clang/lib/StaticAnalyzer/Core/SValBuilder.cpp | 6 +- .../mangle-structured-binding-size.cpp | 12 ---- clang/test/CodeGenCXX/mangle.cpp | 6 ++ .../builtin-structured-binding-size.cpp | 30 ++++----- 20 files changed, 216 insertions(+), 173 deletions(-) delete mode 100644 clang/test/CodeGenCXX/mangle-structured-binding-size.cpp diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index 3a52e16ad0c6d..b95067bedb07a 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -434,36 +434,6 @@ __datasizeof ``__datasizeof`` behaves like ``sizeof``, except that it returns the size of the type ignoring tail padding. -.. _builtin_structured_binding_size-doc: - -__builtin_structured_binding_size (C++) ---------------------------------------- -``__builtin_structured_binding_size`` returns the *structured binding size* -([dcl.struct.bind]) of the type ``T`` (or unevaluated expression ``arg``) -passed as argument. - -This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = arg;``. -If the argument is not destructurable (ie not a builtin array, builtin SIMD vector, -builtin complex, *tuple-like* type or destructurable class type), -``__builtin_structured_binding_size(T)`` is not a valid expression -(``__builtin_structured_binding_size`` is SFINEA-friendly). - -A type is considered a valid *tuple-like* if ``std::tuple_size_v<T>`` is a valid expression, -even if there is no valid ``std::tuple_element`` specialization or suitable -``get`` function for that type. - -.. code-block:: c++ - - template<std::size_t Idx, typename T> - requires (Idx < __builtin_structured_binding_size(T)) - decltype(auto) constexpr get_binding(T&& obj) { - auto && [...p] = std::forward<T>(obj); - return p...[Idx]; - } - struct S { int a = 0, b = 42; }; - static_assert(__builtin_structured_binding_size(S) == 2); - static_assert(get_binding<1>(S{}) == 42); - _BitInt, _ExtInt ---------------- @@ -1942,6 +1912,38 @@ A simplistic usage example as might be seen in standard C++ headers follows: // Emulate type trait for compatibility with other compilers. #endif + +.. _builtin_structured_binding_size-doc: + +__builtin_structured_binding_size (C++) +--------------------------------------- + +The ``__builtin_structured_binding_size(T)`` type trait returns +the *structured binding size* ([dcl.struct.bind]) of type ``T`` + +This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = declval<T&>();``. +If the argument is not destructurable (ie not a builtin array, builtin SIMD vector, +builtin complex, *tuple-like* type or destructurable class type), +``__builtin_structured_binding_size(T)`` is not a valid expression +(``__builtin_structured_binding_size`` is SFINAE-friendly). + +A type is considered a valid *tuple-like* if ``std::tuple_size_v<T>`` is a valid expression, +even if there is no valid ``std::tuple_element`` specialization or suitable +``get`` function for that type. + +.. code-block:: c++ + + template<std::size_t Idx, typename T> + requires (Idx < __builtin_structured_binding_size(T)) + decltype(auto) constexpr get_binding(T&& obj) { + auto && [...p] = std::forward<T>(obj); + return p...[Idx]; + } + struct S { int a = 0, b = 42; }; + static_assert(__builtin_structured_binding_size(S) == 2); + static_assert(get_binding<1>(S{}) == 42); + + Blocks ====== diff --git a/clang/include/clang/AST/ExprCXX.h b/clang/include/clang/AST/ExprCXX.h index abc65e77da021..e1f82d0ec009e 100644 --- a/clang/include/clang/AST/ExprCXX.h +++ b/clang/include/clang/AST/ExprCXX.h @@ -2765,7 +2765,7 @@ class CXXPseudoDestructorExpr : public Expr { /// \endcode class TypeTraitExpr final : public Expr, - private llvm::TrailingObjects<TypeTraitExpr, TypeSourceInfo *> { + private llvm::TrailingObjects<TypeTraitExpr, APValue, TypeSourceInfo *> { /// The location of the type trait keyword. SourceLocation Loc; @@ -2780,6 +2780,10 @@ class TypeTraitExpr final SourceLocation RParenLoc, bool Value); + TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, + ArrayRef<TypeSourceInfo *> Args, SourceLocation RParenLoc, + APValue Value); + TypeTraitExpr(EmptyShell Empty) : Expr(TypeTraitExprClass, Empty) {} size_t numTrailingObjects(OverloadToken<TypeSourceInfo *>) const { @@ -2798,7 +2802,13 @@ class TypeTraitExpr final SourceLocation RParenLoc, bool Value); + static TypeTraitExpr *Create(const ASTContext &C, QualType T, + SourceLocation Loc, TypeTrait Kind, + ArrayRef<TypeSourceInfo *> Args, + SourceLocation RParenLoc, APValue Value); + static TypeTraitExpr *CreateDeserialized(const ASTContext &C, + bool IsStoredAsBool, unsigned NumArgs); /// Determine which type trait this expression uses. @@ -2806,11 +2816,20 @@ class TypeTraitExpr final return static_cast<TypeTrait>(TypeTraitExprBits.Kind); } - bool getValue() const { - assert(!isValueDependent()); + bool isStoredAsBoolean() const { + return TypeTraitExprBits.IsBooleanTypeTrait; + } + + bool getBoolValue() const { + assert(!isValueDependent() && TypeTraitExprBits.IsBooleanTypeTrait); return TypeTraitExprBits.Value; } + const APValue &getAPValue() const { + assert(!isValueDependent() && !TypeTraitExprBits.IsBooleanTypeTrait); + return *getTrailingObjects<APValue>(); + } + /// Determine the number of arguments to this type trait. unsigned getNumArgs() const { return TypeTraitExprBits.NumArgs; } @@ -2840,6 +2859,10 @@ class TypeTraitExpr final const_child_range children() const { return const_child_range(const_child_iterator(), const_child_iterator()); } + + unsigned numTrailingObjects(OverloadToken<APValue>) const { + return TypeTraitExprBits.IsBooleanTypeTrait ? 0 : 1; + } }; /// An Embarcadero array type trait, as used in the implementation of diff --git a/clang/include/clang/AST/Stmt.h b/clang/include/clang/AST/Stmt.h index 476aa2c8c393a..382348fad7037 100644 --- a/clang/include/clang/AST/Stmt.h +++ b/clang/include/clang/AST/Stmt.h @@ -531,7 +531,7 @@ class alignas(void *) Stmt { unsigned : NumExprBits; LLVM_PREFERRED_TYPE(UnaryExprOrTypeTrait) - unsigned Kind : 4; + unsigned Kind : 3; LLVM_PREFERRED_TYPE(bool) unsigned IsType : 1; // true if operand is a type, false if an expression. }; @@ -954,11 +954,13 @@ class alignas(void *) Stmt { LLVM_PREFERRED_TYPE(TypeTrait) unsigned Kind : 8; - /// If this expression is not value-dependent, this indicates whether - /// the trait evaluated true or false. LLVM_PREFERRED_TYPE(bool) - unsigned Value : 1; + unsigned IsBooleanTypeTrait : 1; + /// If this expression is a non value-dependent boolean trait, + /// this indicates whether the trait evaluated true or false. + LLVM_PREFERRED_TYPE(bool) + unsigned Value : 1; /// The number of arguments to this type trait. According to [implimits] /// 8 bits would be enough, but we require (and test for) at least 16 bits /// to mirror FunctionType. diff --git a/clang/include/clang/Basic/TokenKinds.def b/clang/include/clang/Basic/TokenKinds.def index bad9387673ef9..1bf9f43f80986 100644 --- a/clang/include/clang/Basic/TokenKinds.def +++ b/clang/include/clang/Basic/TokenKinds.def @@ -554,7 +554,7 @@ TYPE_TRAIT_2(__reference_converts_from_temporary, ReferenceConvertsFromTemporary // is not exposed to users. TYPE_TRAIT_2(/*EmptySpellingName*/, IsDeducible, KEYCXX) TYPE_TRAIT_1(__is_bitwise_cloneable, IsBitwiseCloneable, KEYALL) -UNARY_EXPR_OR_TYPE_TRAIT(__builtin_structured_binding_size, StructuredBindingSize, KEYCXX) +TYPE_TRAIT_1(__builtin_structured_binding_size, StructuredBindingSize, KEYCXX) // Embarcadero Expression Traits EXPRESSION_TRAIT(__is_lvalue_expr, IsLValueExpr, KEYCXX) diff --git a/clang/lib/AST/ASTImporter.cpp b/clang/lib/AST/ASTImporter.cpp index 0d9b5afc4e4a6..ece9a4fb2c533 100644 --- a/clang/lib/AST/ASTImporter.cpp +++ b/clang/lib/AST/ASTImporter.cpp @@ -8957,11 +8957,14 @@ ExpectedStmt ASTNodeImporter::VisitTypeTraitExpr(TypeTraitExpr *E) { // According to Sema::BuildTypeTrait(), if E is value-dependent, // Value is always false. - bool ToValue = (E->isValueDependent() ? false : E->getValue()); - - return TypeTraitExpr::Create( - Importer.getToContext(), ToType, ToBeginLoc, E->getTrait(), ToArgs, - ToEndLoc, ToValue); + if (E->isValueDependent() || E->isStoredAsBoolean()) { + bool ToValue = (E->isValueDependent() ? false : E->getBoolValue()); + return TypeTraitExpr::Create(Importer.getToContext(), ToType, ToBeginLoc, + E->getTrait(), ToArgs, ToEndLoc, ToValue); + } + return TypeTraitExpr::Create(Importer.getToContext(), ToType, ToBeginLoc, + E->getTrait(), ToArgs, ToEndLoc, + E->getAPValue()); } ExpectedStmt ASTNodeImporter::VisitCXXTypeidExpr(CXXTypeidExpr *E) { diff --git a/clang/lib/AST/ByteCode/Compiler.cpp b/clang/lib/AST/ByteCode/Compiler.cpp index 0259605086b21..02d536183f02d 100644 --- a/clang/lib/AST/ByteCode/Compiler.cpp +++ b/clang/lib/AST/ByteCode/Compiler.cpp @@ -2154,8 +2154,6 @@ bool Compiler<Emitter>::VisitUnaryExprOrTypeTraitExpr( E->getArgumentType()), E); } - assert(Kind != UETT_StructuredBindingSize && - "should have been evaluated in Sema"); return false; } @@ -2846,9 +2844,13 @@ template <class Emitter> bool Compiler<Emitter>::VisitTypeTraitExpr(const TypeTraitExpr *E) { if (DiscardResult) return true; - if (E->getType()->isBooleanType()) - return this->emitConstBool(E->getValue(), E); - return this->emitConst(E->getValue(), E); + if (E->isStoredAsBoolean()) { + if (E->getType()->isBooleanType()) + return this->emitConstBool(E->getBoolValue(), E); + return this->emitConst(E->getBoolValue(), E); + } + PrimType T = classifyPrim(E->getType()); + return this->visitAPValue(E->getAPValue(), T, E); } template <class Emitter> diff --git a/clang/lib/AST/ExprCXX.cpp b/clang/lib/AST/ExprCXX.cpp index c8d61e2cf3f26..0b32ecd215efa 100644 --- a/clang/lib/AST/ExprCXX.cpp +++ b/clang/lib/AST/ExprCXX.cpp @@ -1861,6 +1861,7 @@ TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, TypeTraitExprBits.Kind = Kind; assert(static_cast<unsigned>(Kind) == TypeTraitExprBits.Kind && "TypeTraitExprBits.Kind overflow!"); + TypeTraitExprBits.IsBooleanTypeTrait = true; TypeTraitExprBits.Value = Value; TypeTraitExprBits.NumArgs = Args.size(); assert(Args.size() == TypeTraitExprBits.NumArgs && @@ -1873,19 +1874,54 @@ TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, setDependence(computeDependence(this)); } +TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, + ArrayRef<TypeSourceInfo *> Args, + SourceLocation RParenLoc, APValue Value) + : Expr(TypeTraitExprClass, T, VK_PRValue, OK_Ordinary), Loc(Loc), + RParenLoc(RParenLoc) { + assert(Kind <= TT_Last && "invalid enum value!"); + TypeTraitExprBits.Kind = Kind; + assert(static_cast<unsigned>(Kind) == TypeTraitExprBits.Kind && + "TypeTraitExprBits.Kind overflow!"); + TypeTraitExprBits.IsBooleanTypeTrait = false; + TypeTraitExprBits.NumArgs = Args.size(); + assert(Args.size() == TypeTraitExprBits.NumArgs && + "TypeTraitExprBits.NumArgs overflow!"); + + *getTrailingObjects<APValue>() = Value; + + auto **ToArgs = getTrailingObjects<TypeSourceInfo *>(); + for (unsigned I = 0, N = Args.size(); I != N; ++I) + ToArgs[I] = Args[I]; + + setDependence(computeDependence(this)); +} + TypeTraitExpr *TypeTraitExpr::Create(const ASTContext &C, QualType T, SourceLocation Loc, TypeTrait Kind, ArrayRef<TypeSourceInfo *> Args, SourceLocation RParenLoc, bool Value) { - void *Mem = C.Allocate(totalSizeToAlloc<TypeSourceInfo *>(Args.size())); + void *Mem = + C.Allocate(totalSizeToAlloc<APValue, TypeSourceInfo *>(0, Args.size())); + return new (Mem) TypeTraitExpr(T, Loc, Kind, Args, RParenLoc, Value); +} + +TypeTraitExpr *TypeTraitExpr::Create(const ASTContext &C, QualType T, + SourceLocation Loc, TypeTrait Kind, + ArrayRef<TypeSourceInfo *> Args, + SourceLocation RParenLoc, APValue Value) { + void *Mem = + C.Allocate(totalSizeToAlloc<APValue, TypeSourceInfo *>(1, Args.size())); return new (Mem) TypeTraitExpr(T, Loc, Kind, Args, RParenLoc, Value); } TypeTraitExpr *TypeTraitExpr::CreateDeserialized(const ASTContext &C, + bool IsStoredAsBool, unsigned NumArgs) { - void *Mem = C.Allocate(totalSizeToAlloc<TypeSourceInfo *>(NumArgs)); + void *Mem = C.Allocate(totalSizeToAlloc<APValue, TypeSourceInfo *>( + IsStoredAsBool ? 0 : 1, NumArgs)); return new (Mem) TypeTraitExpr(EmptyShell()); } diff --git a/clang/lib/AST/ExprConstant.cpp b/clang/lib/AST/ExprConstant.cpp index 1763bbc18043d..6bc2daefa3ee9 100644 --- a/clang/lib/AST/ExprConstant.cpp +++ b/clang/lib/AST/ExprConstant.cpp @@ -12102,7 +12102,12 @@ class IntExprEvaluator } bool VisitTypeTraitExpr(const TypeTraitExpr *E) { - return Success(E->getValue(), E); + if (E->isStoredAsBoolean()) + return Success(E->getBoolValue(), E); + if (E->getAPValue().isAbsent()) + return false; + assert(E->getAPValue().isInt() && "APValue type not supported"); + return Success(E->getAPValue().getInt(), E); } bool VisitArrayTypeTraitExpr(const ArrayTypeTraitExpr *E) { @@ -14878,11 +14883,6 @@ bool IntExprEvaluator::VisitUnaryExprOrTypeTraitExpr( } return Success(Sizeof, E); } - case UETT_StructuredBindingSize: - // This can only be computed from Sema and has been cached. - // We can still get there from code that strips the outer ConstantExpr. - return false; - case UETT_OpenMPRequiredSimdAlign: assert(E->isArgumentType()); return Success( diff --git a/clang/lib/AST/ItaniumMangle.cpp b/clang/lib/AST/ItaniumMangle.cpp index 6bbede5b10684..c79f3e2999583 100644 --- a/clang/lib/AST/ItaniumMangle.cpp +++ b/clang/lib/AST/ItaniumMangle.cpp @@ -5358,10 +5358,6 @@ void CXXNameMangler::mangleExpression(const Expr *E, unsigned Arity, MangleAlignofSizeofArg(); break; - case UETT_StructuredBindingSize: - MangleExtensionBuiltin(SAE); - break; - case UETT_VectorElements: case UETT_OpenMPRequiredSimdAlign: case UETT_VecStep: diff --git a/clang/lib/CodeGen/CGExprScalar.cpp b/clang/lib/CodeGen/CGExprScalar.cpp index 6646057b9d772..eccdcdb497f84 100644 --- a/clang/lib/CodeGen/CGExprScalar.cpp +++ b/clang/lib/CodeGen/CGExprScalar.cpp @@ -724,7 +724,12 @@ class ScalarExprEmitter } Value *VisitTypeTraitExpr(const TypeTraitExpr *E) { - return llvm::ConstantInt::get(ConvertType(E->getType()), E->getValue()); + if (E->isStoredAsBoolean()) + return llvm::ConstantInt::get(ConvertType(E->getType()), + E->getBoolValue()); + assert(E->getAPValue().isInt() && "APValue type not supported"); + return llvm::ConstantInt::get(ConvertType(E->getType()), + E->getAPValue().getInt()); } Value *VisitConceptSpecializationExpr(const ConceptSpecializationExpr *E) { diff --git a/clang/lib/Parse/ParseExpr.cpp b/clang/lib/Parse/ParseExpr.cpp index 2e3f0ce3194f5..0c28972d6ed8f 100644 --- a/clang/lib/Parse/ParseExpr.cpp +++ b/clang/lib/Parse/ParseExpr.cpp @@ -1544,7 +1544,6 @@ ExprResult Parser::ParseCastExpression(CastParseKind ParseKind, // unary-expression: '__builtin_omp_required_simd_align' '(' type-name ')' case tok::kw___builtin_omp_required_simd_align: case tok::kw___builtin_vectorelements: - case tok::kw___builtin_structured_binding_size: if (NotPrimaryExpression) *NotPrimaryExpression = true; AllowSuffix = false; @@ -2464,8 +2463,7 @@ Parser::ParseExprAfterUnaryExprOrTypeTrait(const Token &OpTok, tok::kw___datasizeof, tok::kw___alignof, tok::kw_alignof, tok::kw__Alignof, tok::kw_vec_step, tok::kw___builtin_omp_required_simd_align, - tok::kw___builtin_vectorelements, - tok::kw___builtin_structured_binding_size) && + tok::kw___builtin_vectorelements) && "Not a typeof/sizeof/alignof/vec_step expression!"); ExprResult Operand; @@ -2475,8 +2473,7 @@ Parser::ParseExprAfterUnaryExprOrTypeTrait(const Token &OpTok, // If construct allows a form without parenthesis, user may forget to put // pathenthesis around type name. if (OpTok.isOneOf(tok::kw_sizeof, tok::kw___datasizeof, tok::kw___alignof, - tok::kw_alignof, tok::kw__Alignof, - tok::kw___builtin_structured_binding_size)) { + tok::kw_alignof, tok::kw__Alignof)) { if (isTypeIdUnambiguously()) { DeclSpec DS(AttrFactory); ParseSpecifierQualifierList(DS); @@ -2602,8 +2599,7 @@ ExprResult Parser::ParseUnaryExprOrTypeTraitExpression() { assert(Tok.isOneOf(tok::kw_sizeof, tok::kw___datasizeof, tok::kw___alignof, tok::kw_alignof, tok::kw__Alignof, tok::kw_vec_step, tok::kw___builtin_omp_required_simd_align, - tok::kw___builtin_vectorelements, - tok::kw___builtin_structured_binding_size) && + tok::kw___builtin_vectorelements) && "Not a sizeof/alignof/vec_step expression!"); Token OpTok = Tok; ConsumeToken(); @@ -2691,9 +2687,6 @@ ExprResult Parser::ParseUnaryExprOrTypeTraitExpression() { case tok::kw___datasizeof: ExprKind = UETT_DataSizeOf; break; - case tok::kw___builtin_structured_binding_size: - ExprKind = UETT_StructuredBindingSize; - break; case tok::kw___builtin_vectorelements: ExprKind = UETT_VectorElements; break; diff --git a/clang/lib/Sema/SemaDeclCXX.cpp b/clang/lib/Sema/SemaDeclCXX.cpp index 53ca94011f158..f98c21a873504 100644 --- a/clang/lib/Sema/SemaDeclCXX.cpp +++ b/clang/lib/Sema/SemaDeclCXX.cpp @@ -17320,21 +17320,13 @@ void Sema::DiagnoseStaticAssertDetails(const Expr *E) { if (!UsefulToPrintExpr(LHS) && !UsefulToPrintExpr(RHS)) return; - auto UseCachedValue = [](const Expr *Outer, const Expr *Inner) { - if (const ConstantExpr *E = dyn_cast<ConstantExpr>(Outer); - E && !E->getAPValueResult().isAbsent()) - return Outer; - return Inner; - }; - struct { const clang::Expr *Cond; Expr::EvalResult Result; SmallString<12> ValueString; bool Print; - } DiagSide[2] = { - {UseCachedValue(Op->getLHS(), LHS), Expr::EvalResult(), {}, false}, - {UseCachedValue(Op->getRHS(), RHS), Expr::EvalResult(), {}, false}}; + } DiagSide[2] = {{LHS, Expr::EvalResult(), {}, false}, + {RHS, Expr::EvalResult(), {}, false}}; for (unsigned I = 0; I < 2; I++) { const Expr *Side = DiagSide[I].Cond; diff --git a/clang/lib/Sema/SemaExpr.cpp b/clang/lib/Sema/SemaExpr.cpp index 0d26ed506e6fb..1bfe03c66a977 100644 --- a/clang/lib/Sema/SemaExpr.cpp +++ b/clang/lib/Sema/SemaExpr.cpp @@ -4160,54 +4160,6 @@ static bool CheckVecStepTraitOperandType(Sema &S, QualType T, return false; } -static ExprResult BuildStructuredBindingSizeTraitImpl(Sema &S, QualType T, - Expr *E, - TypeSourceInfo *TInfo, - SourceLocation Loc, - SourceRange ArgRange) { - assert(!!E != !!TInfo); - assert(!T->isDependentType()); - std::optional<unsigned> Size = - S.GetDecompositionElementCount(T, ArgRange.getBegin()); - - if (!Size) - return S.Diag(Loc, diag::err_arg_is_not_destructurable) << T << ArgRange; - - Expr *Inner; - if (E) - Inner = new (S.getASTContext()) UnaryExprOrTypeTraitExpr( - UnaryExprOrTypeTrait::UETT_StructuredBindingSize, E, - S.getASTContext().getSizeType(), Loc, E->getEndLoc()); - - else - Inner = new (S.getASTContext()) UnaryExprOrTypeTraitExpr( - UnaryExprOrTypeTrait::UETT_StructuredBindingSize, TInfo, - S.getASTContext().getSizeType(), Loc, ArgRange.getEnd()); - - // Computing the number of bindings requires Sema and is non-trivial, - // so we cache the result now. - llvm::APSInt V = - S.getASTContext().MakeIntValue(*Size, S.getASTContext().getSizeType()); - return ConstantExpr::Create(S.getASTContext(), Inner, APValue{V}); -} - -static ExprResult BuildStructuredBindingSizeTrait(Sema &S, - TypeSourceInfo *TInfo, - SourceLocation Loc, - SourceRange ArgRange) { - return BuildStructuredBindingSizeTraitImpl(S, TInfo->getType(), - /*Expr=*/nullptr, TInfo, Loc, - ArgRange); -} - -static ExprResult BuildStructuredBindingSizeTrait(Sema &S, SourceLocation OpLoc, - Expr *E) { - - return BuildStructuredBindingSizeTraitImpl(S, E->getType(), E, - /*TInfo=*/nullptr, OpLoc, - E->getSourceRange()); -} - static bool CheckVectorElementsTraitOperandType(Sema &S, QualType T, SourceLocation Loc, SourceRange ArgRange) { @@ -4698,14 +4650,10 @@ ExprResult Sema::CreateUnaryExprOrTypeTraitExpr(TypeSourceInfo *TInfo, QualType T = TInfo->getType(); - if (!T->isDependentType()) { - if (ExprKind == UETT_StructuredBindingSize) - return BuildStructuredBindingSizeTrait(*this, TInfo, OpLoc, R); - - if (CheckUnaryExprOrTypeTraitOperand(T, OpLoc, R, ExprKind, - getTraitSpelling(ExprKind))) - return ExprError(); - } + if (!T->isDependentType() && + CheckUnaryExprOrTypeTraitOperand(T, OpLoc, R, ExprKind, + getTraitSpelling(ExprKind))) + return ExprError(); // Adds overload of TransformToPotentiallyEvaluated for TypeSourceInfo to // properly deal with VLAs in nested calls of sizeof and typeof. @@ -4732,9 +4680,6 @@ Sema::CreateUnaryExprOrTypeTraitExpr(Expr *E, SourceLocation OpLoc, bool isInvalid = false; if (E->isTypeDependent()) { // Delay type-checking for type-dependent expressions. - } else if (ExprKind == UETT_StructuredBindingSize) { - // Custom logic - return BuildStructuredBindingSizeTrait(*this, OpLoc, E); } else if (ExprKind == UETT_AlignOf || ExprKind == UETT_PreferredAlignOf) { isInvalid = CheckAlignOfExpr(*this, E, ExprKind); } else if (ExprKind == UETT_VecStep) { diff --git a/clang/lib/Sema/SemaExprCXX.cpp b/clang/lib/Sema/SemaExprCXX.cpp index 34219e0235a74..b31d9303ff577 100644 --- a/clang/lib/Sema/SemaExprCXX.cpp +++ b/clang/lib/Sema/SemaExprCXX.cpp @@ -5066,6 +5066,10 @@ static bool CheckUnaryTypeTraitTypeCompleteness(Sema &S, TypeTrait UTT, case UTT_IsInterfaceClass: return true; + // We diagnose incomplete class types later + case UTT_StructuredBindingSize: + return true; + // C++14 [meta.unary.prop]: // If T is a non-union class type, T shall be a complete type. case UTT_IsEmpty: @@ -5813,6 +5817,34 @@ static ExprResult CheckConvertibilityForTypeTraits( return Result; } +static APValue EvaluateSizeTTypeTrait(Sema &S, TypeTrait Kind, + SourceLocation KWLoc, + ArrayRef<TypeSourceInfo *> Args, + SourceLocation RParenLoc, + bool IsDependent) { + if (IsDependent) + return APValue(); + + switch (Kind) { + case TypeTrait::UTT_StructuredBindingSize: { + QualType T = Args[0]->getType(); + SourceRange ArgRange = Args[0]->getTypeLoc().getSourceRange(); + std::optional<unsigned> Size = + S.GetDecompositionElementCount(T, ArgRange.getBegin()); + if (!Size) { + S.Diag(KWLoc, diag::err_arg_is_not_destructurable) << T << ArgRange; + return APValue(); + } + llvm::APSInt V = + S.getASTContext().MakeIntValue(*Size, S.getASTContext().getSizeType()); + return APValue{V}; + break; + } + default: + llvm_unreachable("Not a SizeT type trait"); + } +} + static bool EvaluateBooleanTypeTrait(Sema &S, TypeTrait Kind, SourceLocation KWLoc, ArrayRef<TypeSourceInfo *> Args, @@ -6014,9 +6046,12 @@ bool Sema::CheckTypeTraitArity(unsigned Arity, SourceLocation Loc, size_t N) { enum class TypeTraitReturnType { Bool, + SizeT, }; static TypeTraitReturnType GetReturnType(TypeTrait Kind) { + if (Kind == TypeTrait::UTT_StructuredBindingSize) + return TypeTraitReturnType::SizeT; return TypeTraitReturnType::Bool; } @@ -6047,6 +6082,12 @@ ExprResult Sema::BuildTypeTrait(TypeTrait Kind, SourceLocation KWLoc, return TypeTraitExpr::Create(Context, Context.getLogicalOperationType(), KWLoc, Kind, Args, RParenLoc, Result); } + case TypeTraitReturnType::SizeT: { + APValue Result = + EvaluateSizeTTypeTrait(*this, Kind, KWLoc, Args, RParenLoc, Dependent); + return TypeTraitExpr::Create(Context, Context.getSizeType(), KWLoc, Kind, + Args, RParenLoc, Result); + } } llvm_unreachable("unhandled type trait return type"); } diff --git a/clang/lib/Serialization/ASTReaderStmt.cpp b/clang/lib/Serialization/ASTReaderStmt.cpp index 48f9f89bd6e4c..f8556ecc739d9 100644 --- a/clang/lib/Serialization/ASTReaderStmt.cpp +++ b/clang/lib/Serialization/ASTReaderStmt.cpp @@ -2135,9 +2135,14 @@ void ASTStmtReader::VisitUnresolvedLookupExpr(UnresolvedLookupExpr *E) { void ASTStmtReader::VisitTypeTraitExpr(TypeTraitExpr *E) { VisitExpr(E); + E->TypeTraitExprBits.IsBooleanTypeTrait = Record.readInt(); E->TypeTraitExprBits.NumArgs = Record.readInt(); E->TypeTraitExprBits.Kind = Record.readInt(); E->TypeTraitExprBits.Value = Record.readInt(); + + if (!E->TypeTraitExprBits.IsBooleanTypeTrait) + *E->getTrailingObjects<APValue>() = Record.readAPValue(); + SourceRange Range = readSourceRange(); E->Loc = Range.getBegin(); E->RParenLoc = Range.getEnd(); @@ -4298,8 +4303,9 @@ Stmt *ASTReader::ReadStmtFromStream(ModuleFile &F) { } case EXPR_TYPE_TRAIT: - S = TypeTraitExpr::CreateDeserialized(Context, - Record[ASTStmtReader::NumExprFields]); + S = TypeTraitExpr::CreateDeserialized( + Context, Record[ASTStmtReader::NumExprFields], + Record[ASTStmtReader::NumExprFields + 1]); break; case EXPR_ARRAY_TYPE_TRAIT: diff --git a/clang/lib/Serialization/ASTWriterStmt.cpp b/clang/lib/Serialization/ASTWriterStmt.cpp index aa5a7854394a0..3f47216cd8172 100644 --- a/clang/lib/Serialization/ASTWriterStmt.cpp +++ b/clang/lib/Serialization/ASTWriterStmt.cpp @@ -2140,9 +2140,14 @@ void ASTStmtWriter::VisitUnresolvedLookupExpr(UnresolvedLookupExpr *E) { void ASTStmtWriter::VisitTypeTraitExpr(TypeTraitExpr *E) { VisitExpr(E); + Record.push_back(E->TypeTraitExprBits.IsBooleanTypeTrait); Record.push_back(E->TypeTraitExprBits.NumArgs); Record.push_back(E->TypeTraitExprBits.Kind); // FIXME: Stable encoding Record.push_back(E->TypeTraitExprBits.Value); + + if (!E->TypeTraitExprBits.IsBooleanTypeTrait) + Record.AddAPValue(E->getAPValue()); + Record.AddSourceRange(E->getSourceRange()); for (unsigned I = 0, N = E->getNumArgs(); I != N; ++I) Record.AddTypeSourceInfo(E->getArg(I)); diff --git a/clang/lib/StaticAnalyzer/Core/SValBuilder.cpp b/clang/lib/StaticAnalyzer/Core/SValBuilder.cpp index 4f45b24be86c1..b4cf72910fa86 100644 --- a/clang/lib/StaticAnalyzer/Core/SValBuilder.cpp +++ b/clang/lib/StaticAnalyzer/Core/SValBuilder.cpp @@ -368,7 +368,11 @@ std::optional<SVal> SValBuilder::getConstantVal(const Expr *E) { case Stmt::TypeTraitExprClass: { const auto *TE = cast<TypeTraitExpr>(E); - return makeTruthVal(TE->getValue(), TE->getType()); + if (TE->isStoredAsBoolean()) + return makeTruthVal(TE->getBoolValue(), TE->getType()); + if (TE->getType()->isIntegralOrEnumerationType()) + return makeIntVal(TE->getAPValue().getInt()); + return std::nullopt; } case Stmt::IntegerLiteralClass: diff --git a/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp b/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp deleted file mode 100644 index 80e4063b9d556..0000000000000 --- a/clang/test/CodeGenCXX/mangle-structured-binding-size.cpp +++ /dev/null @@ -1,12 +0,0 @@ -// RUN: %clang_cc1 -std=c++11 -emit-llvm %s -o - -triple=x86_64-linux-gnu | FileCheck %s - -struct S {}; - -template <class T> void f1(decltype(__builtin_structured_binding_size(T))) {} -template void f1<S>(__SIZE_TYPE__); -// CHECK: void @_Z2f1I1SEvDTu33__builtin_structured_binding_sizeT_EE - -template <class T> void f2(decltype(__builtin_structured_binding_size(T{}))) {} -template void f2<S>(__SIZE_TYPE__); -// CHECK: void @_Z2f2I1SEvDTu33__builtin_structured_binding_sizeXtlT_EEEE - diff --git a/clang/test/CodeGenCXX/mangle.cpp b/clang/test/CodeGenCXX/mangle.cpp index c5b472670e8c0..cf506aff92f0e 100644 --- a/clang/test/CodeGenCXX/mangle.cpp +++ b/clang/test/CodeGenCXX/mangle.cpp @@ -1158,6 +1158,12 @@ template void f16<int>(int, __remove_volatile(int)); template <typename T> void f17(T, __remove_restrict(T)) {} template void f17<int>(int, __remove_restrict(int)); // CHECK-LABEL: @_ZN6test553f17IiEEvT_u17__remove_restrictIS1_E + +struct S{}; +template <class T> void f18(decltype(__builtin_structured_binding_size(T))) {} +template void f18<S>(__SIZE_TYPE__); +// CHECK: void @_ZN6test553f18INS_1SEEEvDTu33__builtin_structured_binding_sizeT_EE + } // namespace test55 namespace test56 { diff --git a/clang/test/SemaCXX/builtin-structured-binding-size.cpp b/clang/test/SemaCXX/builtin-structured-binding-size.cpp index 460f2881ff5dc..54736215e3b58 100644 --- a/clang/test/SemaCXX/builtin-structured-binding-size.cpp +++ b/clang/test/SemaCXX/builtin-structured-binding-size.cpp @@ -1,4 +1,6 @@ // RUN: %clang_cc1 %s -std=c++2c -fsyntax-only -verify +// RUN: %clang_cc1 %s -std=c++2c -fsyntax-only -verify -fexperimental-new-constant-interpreter + struct S0 {}; struct S1 {int a;}; @@ -28,7 +30,8 @@ static_assert(__builtin_structured_binding_size(S1) == 1); static_assert(__builtin_structured_binding_size(SD) == 1); static_assert(__builtin_structured_binding_size(SE1) == 1); // expected-error@-1 {{cannot decompose class type 'SE1': both it and its base class 'S1' have non-static data members}} \ -// expected-error@-1 {{type 'SE1' is not destructurable}} +// expected-error@-1 {{type 'SE1' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(int[0]) == 0); @@ -39,7 +42,6 @@ using vec2 = int __attribute__((__vector_size__(2 * sizeof(int)))); using vec3 = int __attribute__((__vector_size__(3 * sizeof(int)))); static_assert(__builtin_structured_binding_size(vec2) == 2); static_assert(__builtin_structured_binding_size(vec3) == 3); -static_assert(__builtin_structured_binding_size(__builtin_complex(0., 0.)) == 2); static_assert(__builtin_structured_binding_size(decltype(__builtin_complex(0., 0.))) == 2); @@ -47,15 +49,18 @@ int VLASize; // expected-note {{declared here}} static_assert(__builtin_structured_binding_size(int[VLASize]) == 42); // expected-error@-1 {{type 'int[VLASize]' is not destructurable}} \ // expected-warning@-1 {{variable length arrays in C++ are a Clang extension}} \ -// expected-note@-1 {{read of non-const variable 'VLASize' is not allowed in a constant expression}} +// expected-note@-1 {{read of non-const variable 'VLASize' is not allowed in a constant expression}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} struct Incomplete; // expected-note {{forward declaration of 'Incomplete'}} static_assert(__builtin_structured_binding_size(Incomplete) == 1); // expected-error@-1 {{incomplete type 'Incomplete' where a complete type is required}} \ -// expected-error@-1 {{type 'Incomplete' is not destructurable}} +// expected-error@-1 {{type 'Incomplete' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(Incomplete[]) == 1); -// expected-error@-1 {{type 'Incomplete[]' is not destructurable}} +// expected-error@-1 {{type 'Incomplete[]' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(Incomplete[0]) == 0); static_assert(__builtin_structured_binding_size(Incomplete[1]) == 1); static_assert(__builtin_structured_binding_size(Incomplete[42]) == 42); @@ -120,23 +125,12 @@ static_assert(__builtin_structured_binding_size(T1) == 1); static_assert(__builtin_structured_binding_size(T42) == 42); static_assert(__builtin_structured_binding_size(TSizeError) == 42); // expected-error@-1 {{cannot decompose this type; 'std::tuple_size<TSizeError>::value' is not a valid integral constant expression}} \ -// expected-error@-1 {{type 'TSizeError' is not destructurable}} +// expected-error@-1 {{type 'TSizeError' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(!is_destructurable<TSizeError>); } -void test_expr(S1 & s1, S2 && s2, T0 & t0, int i, const S1 & s1c, int arr[2]) { - static_assert(__builtin_structured_binding_size(s1) == 1); - static_assert(__builtin_structured_binding_size(s1c) == 1); - static_assert(__builtin_structured_binding_size(s2) == 2); - static_assert(__builtin_structured_binding_size(t0) == 0); - static_assert(__builtin_structured_binding_size(i)); - // expected-error@-1 {{type 'int' is not destructurable}} - static_assert(__builtin_structured_binding_size(arr) == 1); - // expected-error@-1 {{type 'int *' is not destructurable}} -} - - // Check we can implement std::exec::tag_of_t template <typename T> struct type_identity { >From 34d7408cb4b216882efd7ecf1f54356ae977b975 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 18:11:38 +0100 Subject: [PATCH 09/15] remove extra curlies --- clang/lib/Sema/SemaDeclCXX.cpp | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/clang/lib/Sema/SemaDeclCXX.cpp b/clang/lib/Sema/SemaDeclCXX.cpp index f98c21a873504..01666f15e2737 100644 --- a/clang/lib/Sema/SemaDeclCXX.cpp +++ b/clang/lib/Sema/SemaDeclCXX.cpp @@ -1681,10 +1681,10 @@ std::optional<unsigned> Sema::GetDecompositionElementCount(QualType T, case IsTupleLike::NotTupleLike: break; } + CXXRecordDecl *OrigRD = T->getAsCXXRecordDecl(); - if (!OrigRD || OrigRD->isUnion()) { + if (!OrigRD || OrigRD->isUnion()) return std::nullopt; - } if (RequireCompleteType(Loc, T, diag::err_incomplete_type)) return std::nullopt; >From d7250a7334f2a3430ec8b16495d80785077e756f Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 18:41:07 +0100 Subject: [PATCH 10/15] Add tests for cvref --- clang/lib/Sema/SemaDeclCXX.cpp | 6 ++++++ clang/test/SemaCXX/builtin-structured-binding-size.cpp | 10 ++++++++++ 2 files changed, 16 insertions(+) diff --git a/clang/lib/Sema/SemaDeclCXX.cpp b/clang/lib/Sema/SemaDeclCXX.cpp index 01666f15e2737..fd4e06305ffaa 100644 --- a/clang/lib/Sema/SemaDeclCXX.cpp +++ b/clang/lib/Sema/SemaDeclCXX.cpp @@ -1665,6 +1665,12 @@ std::optional<unsigned> Sema::GetDecompositionElementCount(QualType T, SourceLocation Loc) { const ASTContext &Ctx = getASTContext(); assert(!T->isDependentType()); + + Qualifiers Quals; + QualType Unqual = Context.getUnqualifiedArrayType(T, Quals); + Quals.removeCVRQualifiers(); + T = Context.getQualifiedType(Unqual, Quals); + if (auto *CAT = Ctx.getAsConstantArrayType(T)) return CAT->getSize().getZExtValue(); if (auto *VT = T->getAs<VectorType>()) diff --git a/clang/test/SemaCXX/builtin-structured-binding-size.cpp b/clang/test/SemaCXX/builtin-structured-binding-size.cpp index 54736215e3b58..58f0d2d8d8ff3 100644 --- a/clang/test/SemaCXX/builtin-structured-binding-size.cpp +++ b/clang/test/SemaCXX/builtin-structured-binding-size.cpp @@ -74,7 +74,11 @@ static_assert(__builtin_structured_binding_size(P1) == 0); static_assert(is_destructurable<S0>); +static_assert(is_destructurable<const S0>); +static_assert(is_destructurable<volatile S0>); +static_assert(!is_destructurable<S0&>); static_assert(is_destructurable<S1>); +static_assert(!is_destructurable<S1&>); static_assert(!is_destructurable<SE1>); static_assert(!is_destructurable<int>); static_assert(!is_destructurable<int[]>); @@ -121,6 +125,12 @@ struct tuple_size<TSizeError> { }; static_assert(__builtin_structured_binding_size(T0) == 0); + +static_assert(is_destructurable<const T0>); +static_assert(is_destructurable<volatile T0>); +static_assert(!is_destructurable<T0&>); + + static_assert(__builtin_structured_binding_size(T1) == 1); static_assert(__builtin_structured_binding_size(T42) == 42); static_assert(__builtin_structured_binding_size(TSizeError) == 42); >From b573489aa7efeedb643ad65bc6cc4c83febf3f54 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Mon, 17 Mar 2025 19:39:51 +0100 Subject: [PATCH 11/15] union tests --- clang/test/SemaCXX/builtin-structured-binding-size.cpp | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/clang/test/SemaCXX/builtin-structured-binding-size.cpp b/clang/test/SemaCXX/builtin-structured-binding-size.cpp index 58f0d2d8d8ff3..af1b95f423c05 100644 --- a/clang/test/SemaCXX/builtin-structured-binding-size.cpp +++ b/clang/test/SemaCXX/builtin-structured-binding-size.cpp @@ -14,6 +14,8 @@ struct SE1 : S1 { int b;}; class P1 {int a;}; // #note-private +union U1 {}; +union U2 {int a;}; template <typename T> concept is_destructurable = requires { @@ -33,6 +35,14 @@ static_assert(__builtin_structured_binding_size(SE1) == 1); // expected-error@-1 {{type 'SE1' is not destructurable}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} +static_assert(__builtin_structured_binding_size(U1) == 0); +// expected-error@-1 {{type 'U1' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} +static_assert(__builtin_structured_binding_size(U2) == 0); +// expected-error@-1 {{type 'U2' is not destructurable}} \ +// expected-error@-1 {{static assertion expression is not an integral constant expression}} + + static_assert(__builtin_structured_binding_size(int[0]) == 0); static_assert(__builtin_structured_binding_size(int[1]) == 1); >From a85ef1400486e2778c3d9c9c6b9826ff2feae05e Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Tue, 18 Mar 2025 11:30:00 +0100 Subject: [PATCH 12/15] revert unrelated changes --- clang/lib/Sema/SemaExpr.cpp | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/clang/lib/Sema/SemaExpr.cpp b/clang/lib/Sema/SemaExpr.cpp index 1bfe03c66a977..e19136b394800 100644 --- a/clang/lib/Sema/SemaExpr.cpp +++ b/clang/lib/Sema/SemaExpr.cpp @@ -4685,9 +4685,9 @@ Sema::CreateUnaryExprOrTypeTraitExpr(Expr *E, SourceLocation OpLoc, } else if (ExprKind == UETT_VecStep) { isInvalid = CheckVecStepExpr(E); } else if (ExprKind == UETT_OpenMPRequiredSimdAlign) { - Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); - isInvalid = true; - } else if (E->refersToBitField()) { // C99 6.5.3.4p1. + Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); + isInvalid = true; + } else if (E->refersToBitField()) { // C99 6.5.3.4p1. Diag(E->getExprLoc(), diag::err_sizeof_alignof_typeof_bitfield) << 0; isInvalid = true; } else if (ExprKind == UETT_VectorElements) { >From dac84f1913bd7e4d57d9d7aee508943faf2e4b71 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Tue, 18 Mar 2025 15:00:33 +0100 Subject: [PATCH 13/15] Address Erich's and Aaron's feedback --- clang/docs/LanguageExtensions.rst | 2 +- clang/include/clang/AST/ExprCXX.h | 19 +++------- .../clang/Basic/DiagnosticSemaKinds.td | 2 +- clang/lib/AST/ASTImporter.cpp | 6 +-- clang/lib/AST/ExprCXX.cpp | 37 ++++++------------- clang/lib/Sema/SemaExpr.cpp | 6 +-- clang/lib/Serialization/ASTReaderStmt.cpp | 5 ++- clang/lib/Serialization/ASTWriterStmt.cpp | 5 ++- .../builtin-structured-binding-size.cpp | 16 ++++---- 9 files changed, 40 insertions(+), 58 deletions(-) diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index f8227c5a9bb31..8477817981b0e 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -1922,7 +1922,7 @@ The ``__builtin_structured_binding_size(T)`` type trait returns the *structured binding size* ([dcl.struct.bind]) of type ``T`` This is equivalent to the size of the pack ``p`` in ``auto&& [...p] = declval<T&>();``. -If the argument is not destructurable (ie not a builtin array, builtin SIMD vector, +If the argument cannot be decomposed (ie not a builtin array, builtin SIMD vector, builtin complex, *tuple-like* type or destructurable class type), ``__builtin_structured_binding_size(T)`` is not a valid expression (``__builtin_structured_binding_size`` is SFINAE-friendly). diff --git a/clang/include/clang/AST/ExprCXX.h b/clang/include/clang/AST/ExprCXX.h index e1f82d0ec009e..724ed437f1075 100644 --- a/clang/include/clang/AST/ExprCXX.h +++ b/clang/include/clang/AST/ExprCXX.h @@ -51,6 +51,7 @@ #include <cstdint> #include <memory> #include <optional> +#include <variant> namespace clang { @@ -2772,17 +2773,9 @@ class TypeTraitExpr final /// The location of the closing parenthesis. SourceLocation RParenLoc; - // Note: The TypeSourceInfos for the arguments are allocated after the - // TypeTraitExpr. - - TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, - ArrayRef<TypeSourceInfo *> Args, - SourceLocation RParenLoc, - bool Value); - TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, ArrayRef<TypeSourceInfo *> Args, SourceLocation RParenLoc, - APValue Value); + std::variant<bool, APValue> Value); TypeTraitExpr(EmptyShell Empty) : Expr(TypeTraitExprClass, Empty) {} @@ -2790,6 +2783,10 @@ class TypeTraitExpr final return getNumArgs(); } + size_t numTrailingObjects(OverloadToken<APValue>) const { + return TypeTraitExprBits.IsBooleanTypeTrait ? 0 : 1; + } + public: friend class ASTStmtReader; friend class ASTStmtWriter; @@ -2859,10 +2856,6 @@ class TypeTraitExpr final const_child_range children() const { return const_child_range(const_child_iterator(), const_child_iterator()); } - - unsigned numTrailingObjects(OverloadToken<APValue>) const { - return TypeTraitExprBits.IsBooleanTypeTrait ? 0 : 1; - } }; /// An Embarcadero array type trait, as used in the implementation of diff --git a/clang/include/clang/Basic/DiagnosticSemaKinds.td b/clang/include/clang/Basic/DiagnosticSemaKinds.td index e44fb5ffdf684..97ef898bfee10 100644 --- a/clang/include/clang/Basic/DiagnosticSemaKinds.td +++ b/clang/include/clang/Basic/DiagnosticSemaKinds.td @@ -592,7 +592,7 @@ def err_decomp_decl_std_tuple_size_not_constant : Error< def note_in_binding_decl_init : Note< "in implicit initialization of binding declaration %0">; def err_arg_is_not_destructurable : Error< - "type %0 is not destructurable">; + "type %0 cannot be decomposed">; def err_std_type_trait_not_class_template : Error< "unsupported standard library implementation: " diff --git a/clang/lib/AST/ASTImporter.cpp b/clang/lib/AST/ASTImporter.cpp index 94a368c7292e4..514887a4dccc1 100644 --- a/clang/lib/AST/ASTImporter.cpp +++ b/clang/lib/AST/ASTImporter.cpp @@ -8955,9 +8955,9 @@ ExpectedStmt ASTNodeImporter::VisitTypeTraitExpr(TypeTraitExpr *E) { if (Error Err = ImportContainerChecked(E->getArgs(), ToArgs)) return std::move(Err); - // According to Sema::BuildTypeTrait(), if E is value-dependent, - // Value is always false. - if (E->isValueDependent() || E->isStoredAsBoolean()) { + if (E->isStoredAsBoolean()) { + // According to Sema::BuildTypeTrait(), if E is value-dependent, + // Value is always false. bool ToValue = (E->isValueDependent() ? false : E->getBoolValue()); return TypeTraitExpr::Create(Importer.getToContext(), ToType, ToBeginLoc, E->getTrait(), ToArgs, ToEndLoc, ToValue); diff --git a/clang/lib/AST/ExprCXX.cpp b/clang/lib/AST/ExprCXX.cpp index 0b32ecd215efa..fa13d336a85f5 100644 --- a/clang/lib/AST/ExprCXX.cpp +++ b/clang/lib/AST/ExprCXX.cpp @@ -1854,47 +1854,34 @@ bool MaterializeTemporaryExpr::isUsableInConstantExpressions( TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, ArrayRef<TypeSourceInfo *> Args, - SourceLocation RParenLoc, bool Value) + SourceLocation RParenLoc, + std::variant<bool, APValue> Value) : Expr(TypeTraitExprClass, T, VK_PRValue, OK_Ordinary), Loc(Loc), RParenLoc(RParenLoc) { assert(Kind <= TT_Last && "invalid enum value!"); + TypeTraitExprBits.Kind = Kind; assert(static_cast<unsigned>(Kind) == TypeTraitExprBits.Kind && "TypeTraitExprBits.Kind overflow!"); - TypeTraitExprBits.IsBooleanTypeTrait = true; - TypeTraitExprBits.Value = Value; - TypeTraitExprBits.NumArgs = Args.size(); - assert(Args.size() == TypeTraitExprBits.NumArgs && - "TypeTraitExprBits.NumArgs overflow!"); - auto **ToArgs = getTrailingObjects<TypeSourceInfo *>(); - for (unsigned I = 0, N = Args.size(); I != N; ++I) - ToArgs[I] = Args[I]; - - setDependence(computeDependence(this)); -} + TypeTraitExprBits.IsBooleanTypeTrait = Value.index() == 0; + if (TypeTraitExprBits.IsBooleanTypeTrait) + TypeTraitExprBits.Value = std::get<bool>(Value); + else + *getTrailingObjects<APValue>() = std::get<APValue>(std::move(Value)); -TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, - ArrayRef<TypeSourceInfo *> Args, - SourceLocation RParenLoc, APValue Value) - : Expr(TypeTraitExprClass, T, VK_PRValue, OK_Ordinary), Loc(Loc), - RParenLoc(RParenLoc) { - assert(Kind <= TT_Last && "invalid enum value!"); - TypeTraitExprBits.Kind = Kind; - assert(static_cast<unsigned>(Kind) == TypeTraitExprBits.Kind && - "TypeTraitExprBits.Kind overflow!"); - TypeTraitExprBits.IsBooleanTypeTrait = false; TypeTraitExprBits.NumArgs = Args.size(); assert(Args.size() == TypeTraitExprBits.NumArgs && "TypeTraitExprBits.NumArgs overflow!"); - - *getTrailingObjects<APValue>() = Value; - auto **ToArgs = getTrailingObjects<TypeSourceInfo *>(); for (unsigned I = 0, N = Args.size(); I != N; ++I) ToArgs[I] = Args[I]; setDependence(computeDependence(this)); + + assert((TypeTraitExprBits.IsBooleanTypeTrait || isValueDependent() || + getAPValue().isInt() || getAPValue().isAbsent()) && + "Only int values are supported by clang"); } TypeTraitExpr *TypeTraitExpr::Create(const ASTContext &C, QualType T, diff --git a/clang/lib/Sema/SemaExpr.cpp b/clang/lib/Sema/SemaExpr.cpp index e19136b394800..1bfe03c66a977 100644 --- a/clang/lib/Sema/SemaExpr.cpp +++ b/clang/lib/Sema/SemaExpr.cpp @@ -4685,9 +4685,9 @@ Sema::CreateUnaryExprOrTypeTraitExpr(Expr *E, SourceLocation OpLoc, } else if (ExprKind == UETT_VecStep) { isInvalid = CheckVecStepExpr(E); } else if (ExprKind == UETT_OpenMPRequiredSimdAlign) { - Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); - isInvalid = true; - } else if (E->refersToBitField()) { // C99 6.5.3.4p1. + Diag(E->getExprLoc(), diag::err_openmp_default_simd_align_expr); + isInvalid = true; + } else if (E->refersToBitField()) { // C99 6.5.3.4p1. Diag(E->getExprLoc(), diag::err_sizeof_alignof_typeof_bitfield) << 0; isInvalid = true; } else if (ExprKind == UETT_VectorElements) { diff --git a/clang/lib/Serialization/ASTReaderStmt.cpp b/clang/lib/Serialization/ASTReaderStmt.cpp index ebd813f185e1e..8dceca6ff3dbf 100644 --- a/clang/lib/Serialization/ASTReaderStmt.cpp +++ b/clang/lib/Serialization/ASTReaderStmt.cpp @@ -2138,9 +2138,10 @@ void ASTStmtReader::VisitTypeTraitExpr(TypeTraitExpr *E) { E->TypeTraitExprBits.IsBooleanTypeTrait = Record.readInt(); E->TypeTraitExprBits.NumArgs = Record.readInt(); E->TypeTraitExprBits.Kind = Record.readInt(); - E->TypeTraitExprBits.Value = Record.readInt(); - if (!E->TypeTraitExprBits.IsBooleanTypeTrait) + if (E->TypeTraitExprBits.IsBooleanTypeTrait) + E->TypeTraitExprBits.Value = Record.readInt(); + else *E->getTrailingObjects<APValue>() = Record.readAPValue(); SourceRange Range = readSourceRange(); diff --git a/clang/lib/Serialization/ASTWriterStmt.cpp b/clang/lib/Serialization/ASTWriterStmt.cpp index bd588dd371ff7..037eb13b1dc52 100644 --- a/clang/lib/Serialization/ASTWriterStmt.cpp +++ b/clang/lib/Serialization/ASTWriterStmt.cpp @@ -2143,9 +2143,10 @@ void ASTStmtWriter::VisitTypeTraitExpr(TypeTraitExpr *E) { Record.push_back(E->TypeTraitExprBits.IsBooleanTypeTrait); Record.push_back(E->TypeTraitExprBits.NumArgs); Record.push_back(E->TypeTraitExprBits.Kind); // FIXME: Stable encoding - Record.push_back(E->TypeTraitExprBits.Value); - if (!E->TypeTraitExprBits.IsBooleanTypeTrait) + if (E->TypeTraitExprBits.IsBooleanTypeTrait) + Record.push_back(E->TypeTraitExprBits.Value); + else Record.AddAPValue(E->getAPValue()); Record.AddSourceRange(E->getSourceRange()); diff --git a/clang/test/SemaCXX/builtin-structured-binding-size.cpp b/clang/test/SemaCXX/builtin-structured-binding-size.cpp index af1b95f423c05..f778759922226 100644 --- a/clang/test/SemaCXX/builtin-structured-binding-size.cpp +++ b/clang/test/SemaCXX/builtin-structured-binding-size.cpp @@ -32,14 +32,14 @@ static_assert(__builtin_structured_binding_size(S1) == 1); static_assert(__builtin_structured_binding_size(SD) == 1); static_assert(__builtin_structured_binding_size(SE1) == 1); // expected-error@-1 {{cannot decompose class type 'SE1': both it and its base class 'S1' have non-static data members}} \ -// expected-error@-1 {{type 'SE1' is not destructurable}} \ +// expected-error@-1 {{type 'SE1' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(U1) == 0); -// expected-error@-1 {{type 'U1' is not destructurable}} \ +// expected-error@-1 {{type 'U1' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(U2) == 0); -// expected-error@-1 {{type 'U2' is not destructurable}} \ +// expected-error@-1 {{type 'U2' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} @@ -57,7 +57,7 @@ static_assert(__builtin_structured_binding_size(decltype(__builtin_complex(0., 0 int VLASize; // expected-note {{declared here}} static_assert(__builtin_structured_binding_size(int[VLASize]) == 42); -// expected-error@-1 {{type 'int[VLASize]' is not destructurable}} \ +// expected-error@-1 {{type 'int[VLASize]' cannot be decomposed}} \ // expected-warning@-1 {{variable length arrays in C++ are a Clang extension}} \ // expected-note@-1 {{read of non-const variable 'VLASize' is not allowed in a constant expression}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} @@ -66,10 +66,10 @@ static_assert(__builtin_structured_binding_size(int[VLASize]) == 42); struct Incomplete; // expected-note {{forward declaration of 'Incomplete'}} static_assert(__builtin_structured_binding_size(Incomplete) == 1); // expected-error@-1 {{incomplete type 'Incomplete' where a complete type is required}} \ -// expected-error@-1 {{type 'Incomplete' is not destructurable}} \ +// expected-error@-1 {{type 'Incomplete' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(Incomplete[]) == 1); -// expected-error@-1 {{type 'Incomplete[]' is not destructurable}} \ +// expected-error@-1 {{type 'Incomplete[]' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(__builtin_structured_binding_size(Incomplete[0]) == 0); static_assert(__builtin_structured_binding_size(Incomplete[1]) == 1); @@ -145,7 +145,7 @@ static_assert(__builtin_structured_binding_size(T1) == 1); static_assert(__builtin_structured_binding_size(T42) == 42); static_assert(__builtin_structured_binding_size(TSizeError) == 42); // expected-error@-1 {{cannot decompose this type; 'std::tuple_size<TSizeError>::value' is not a valid integral constant expression}} \ -// expected-error@-1 {{type 'TSizeError' is not destructurable}} \ +// expected-error@-1 {{type 'TSizeError' cannot be decomposed}} \ // expected-error@-1 {{static assertion expression is not an integral constant expression}} static_assert(!is_destructurable<TSizeError>); } @@ -179,4 +179,4 @@ static_assert(__is_same_as(tag_of_t<S1>, int)); static_assert(__is_same_as(tag_of_t<int>, int)); // error // expected-error@-1 {{constraints not satisfied for alias template 'tag_of_t' [with T = int]}} -// expected-note@#tag-of-constr {{because substituted constraint expression is ill-formed: type 'int' is not destructurable}} +// expected-note@#tag-of-constr {{because substituted constraint expression is ill-formed: type 'int' cannot be decomposed}} >From ab36891e79023a9cce18392f200959053226bce6 Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Tue, 18 Mar 2025 15:02:10 +0100 Subject: [PATCH 14/15] remove extra new line --- clang/docs/LanguageExtensions.rst | 1 - 1 file changed, 1 deletion(-) diff --git a/clang/docs/LanguageExtensions.rst b/clang/docs/LanguageExtensions.rst index 8477817981b0e..950aacaabfd13 100644 --- a/clang/docs/LanguageExtensions.rst +++ b/clang/docs/LanguageExtensions.rst @@ -434,7 +434,6 @@ __datasizeof ``__datasizeof`` behaves like ``sizeof``, except that it returns the size of the type ignoring tail padding. - _BitInt, _ExtInt ---------------- >From 19541ed04f510be5443dfd4ff0d68c846933748e Mon Sep 17 00:00:00 2001 From: Corentin Jabot <corentinja...@gmail.com> Date: Tue, 18 Mar 2025 15:10:10 +0100 Subject: [PATCH 15/15] use holds_alternative --- clang/lib/AST/ExprCXX.cpp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/clang/lib/AST/ExprCXX.cpp b/clang/lib/AST/ExprCXX.cpp index fa13d336a85f5..c2cf4ffe506c6 100644 --- a/clang/lib/AST/ExprCXX.cpp +++ b/clang/lib/AST/ExprCXX.cpp @@ -1864,7 +1864,7 @@ TypeTraitExpr::TypeTraitExpr(QualType T, SourceLocation Loc, TypeTrait Kind, assert(static_cast<unsigned>(Kind) == TypeTraitExprBits.Kind && "TypeTraitExprBits.Kind overflow!"); - TypeTraitExprBits.IsBooleanTypeTrait = Value.index() == 0; + TypeTraitExprBits.IsBooleanTypeTrait = std::holds_alternative<bool>(Value); if (TypeTraitExprBits.IsBooleanTypeTrait) TypeTraitExprBits.Value = std::get<bool>(Value); else _______________________________________________ cfe-commits mailing list cfe-commits@lists.llvm.org https://lists.llvm.org/cgi-bin/mailman/listinfo/cfe-commits