For Better or for Worse, the Overload

You know what’s stuck on my mind? Ever since writing my last post, it’s been the word “better.” It came up when we were talking about overload resolution and implicit conversion sequences. I explained a necessary special case of it—something about how adding const in a reference-binding is preferred against—and then strategically shut up about the rest.

void run(int (**f)());                // #1
void run(int (*const *f)() noexcept); // #2
int foo() noexcept;

int (*p)() noexcept = &foo;
run(&p); // ???

But it’s so tantalizing, isn’t it? Which one will it choose? How can we reason about this? I can see it in your eyes, sore but eager. You yearn for conversion. Well, I wasn’t going to— I— well… Alright, since you’re so insistent. Just for you. Shall we?

∗  ∗  ∗

Let’s start small and work our way up. An implicit conversion sequence is a standard conversion sequence, possibly followed by a user-defined conversion and another standard conversion sequence in the case of a class type.1 A user-defined conversion is something like T::operator S(), which defines how to convert a T into an S. These are easy: they work exactly how we tell them to. So, it evidently suffices to understand standard conversion sequences.

Definition 1

A standard conversion sequence is a sequence of zero or one conversions from each of the following categories, in order:

  1. Lvalue-to-rvalue, array-to-pointer, or function-to-pointer conversions:
    • Lvalue-to-rvalue: converts a glvalue of non-function, non-array type to a prvalue. Not particularly relevant to overload resolution, and kind of sophisticated, so we’ll mostly forget about this.
    • Array-to-pointer: converts an expression of type “array of NN T” or “array of unknown bound of T” to a prvalue of type “pointer to T,” applying temporary materialization conversion if the expression was a prvalue (note that GCC has a bug and won’t do this; temporary materialization is defined later).
    • Function-to-pointer: converts an lvalue function of type T to a prvalue of type “pointer to T.”
  2. Integral/floating-point/boolean/pointer/pointer-to-member conversions and promotions:
    • There are a bunch of rules for converting between various integral and floating-point types that are necessary but, frankly, menial and uninteresting, so we’ll omit these too. The pointer/pointer-to-member conversions are probably things you already know.
  3. Function pointer conversion: converts a prvalue of type “pointer to noexcept function” to a prvalue of type “pointer to function.”
  4. Qualification conversion: unifies constness of two types somehow. Oh boy. It can’t be that bad, right? Right?

Surprise! This post is actually about qualification conversions

OK— OK. Uh. Hear me out.

In C++, const and volatile are often called cv-qualifiers, so called because they qualify types to form cv-qualified types. The cv-qualified versions of a cv-unqualified type T are const T, volatile T, and const volatile T. We could also consider types T which have cv-qualifiers nested inside—for example, const int** const (“const pointer to pointer to const int”) could be written alternatively as X in the following series of type aliases:

using U = const int;
using V = U*;
using W = V*;
using X = const W;

Now, a mathematically inclined reader may choose to write “const pointer to pointer to const int” as

cv0 P0 cv1 P1 cv2 Ucv_0~P_0~cv_1~P_1~cv_2~\mathtt{U}

where cv0={const}cv_0=\{\mathtt{const}\}, cv1=cv_1=\emptyset, cv2={const}cv_2=\{\mathtt{const}\}, P0=P1=“pointer to”P_0=P_1=\text{``pointer to''}, and U=int\mathtt{U}=\mathtt{int}. More generally, we could write any type T\mathtt{T} (not necessarily uniquely) as

cv0 P0 cv1 P1  cvn1 Pn1 cvn Ucv_0~P_0~cv_1~P_1~\ldots~cv_{n-1}~P_{n-1}~cv_n~\mathtt{U}

for some n0n\ge 0 and some type U\mathtt{U}; each PiP_i is either “pointer to,” “array of NiN_i,” or “array of unknown size of.” For simplicity, let’s assume each PiP_i will always be “pointer to.”

Notice that, for determining whether one type can be qualification-converted into another type (e.g., trying to convert int* to const int*), we can always drop cv0cv_0 from consideration altogether—in particular, at the top level, we can always initialize a const T from a T and vice versa, and likewise we can always convert from one to the other. So, let’s forget about cv0cv_0.

Since we don’t care as much about any of the PiP_i or U\mathtt{U}—these are the “non-const-y” parts, and we’ll deal with them separately—let’s write this even more compactly as the nn-tuple (cv1,cv2,,cvn)(cv_1,cv_2,\ldots,cv_n). The longest possible such tuple is called cv-qualification signature of T\mathtt{T}.

We’re almost there. I’m trying really hard to make the C++ standard more palatable here, so bear with me. Two types T1\mathtt{T1} and T2\mathtt{T2} are called similar if they have cv-decompositions of equal size such that each of their respective PiP_i’s are either (1) the same, or (2) one is “array of NiN_i” and the other is “array of unknown size of”; and, moreover, their U\mathtt{U}’s should agree. Basically, if the “not-const-y” parts of their cv-decompositions mostly agree, they’re called “similar.”

OK. It’s time. I’m only barely paraphrasing the standard because it’s all I can do at this point—it’s honestly worded pretty tightly. Let T1\mathtt{T1} and T2\mathtt{T2} be two types. Then, their cv-combined type T3\mathtt{T3}, if it exists, is a type similar to T1\mathtt{T1} such that, for each i>0i>0:

  • cvi3=cvi1cvi2cv_i^3=cv_i^1\cup cv_i^2;
  • if either Pi1P_i^1 or Pi2P_i^2 are “array of unknown bound of,” then so is Pi3P_i^3; and,
  • if cvi3cvi1cv_i^3\ne cv_i^1, cvi3cvi2cv_i^3\ne cv_i^2, Pi3Pi1P_i^3\ne P_i^1 or P13Pi2P_1^3\ne P_i^2, then const\mathtt{const} is added to each cvj3cv_j^3 for 0<j<i0<j<i.

This can be thought of as an algorithm for finding the converted type T3\mathtt{T3}. If it ends up finding in the end that T3=T2\mathtt{T3}=\mathtt{T2} (up to top-level cv-qualifiers), then a prvalue of type T1\mathtt{T1} can be successfully converted to a prvalue of type T2\mathtt{T2}.

Hey, that was only a little awful. It’s actually cute if you think about it for a bit. The gist is that, if the cv-qualification signature of T2\mathtt{T2} doesn’t have const\mathtt{const} up to the last point of disagreement with T1\mathtt{T1}, the conversion probably won’t work out.

I learn best when I look at a few examples, so here are two I found to be useful:

// q :: "pointer to pointer to pointer to int"
int*** q{};
// p :: "pointer to const pointer to pointer to int"
int** const* p = q;

This one compiles. The PiP_i’s and UU both match up, so we we’ll only focus on the cv-qualifiers. The cv-qualification signature for int*** is a:=(,,)a := (\emptyset, \emptyset, \emptyset) while, for int** const*, it’s b:=({const},,)b := (\{\mathtt{const}\}, \emptyset, \emptyset). So, we determine the cv-qualification signature cc for the cv-combined type as follows:

  1. Set c1:=a1b1={const}c_1 := a_1\cup b_1=\{\mathtt{const}\}. Although a1b1a_1 \ne b_1, there are no prior sets to change (i.e., i=1i=1), so just move on.
  2. Set c2:=a2b2=c_2 := a_2\cup b_2=\emptyset. Since a2=b2a_2 = b_2, move on.
  3. Set c3:=a3b3=c_3 := a_3\cup b_3=\emptyset. Since a3=b3a_3 = b_3, move on.

Then, c=b=(const,,)c=b=(\mathtt{const}, \emptyset, \emptyset) is the cv-qualification signature for int** const*, matching bb exactly so that the conversion of q to the type of p succeeds.

As you might’ve come to expect by now, the story gets worse when we move one of those stars in p over:

// q :: "pointer to pointer to pointer to int"
int*** q;
// p :: "pointer to pointer const to pointer to int"
int* const** p = q;

This one kept me up at night. It actually does not compile, for a reason that’s easy to miss. Let’s go through it: the cv-qualification signature for int*** is a:=(,,)a := (\emptyset, \emptyset, \emptyset) while, for int** const*, it’s b:=(,{const},)b := (\emptyset, \{\mathtt{const}\}, \emptyset). So, we determine the cv-decomposition cc for the cv-combined type as follows:

  1. Set c1:=a1b1=c_1 := a_1\cup b_1=\emptyset. Since a1=b1a_1 = b_1, move on.
  2. Set c2:=a2b2={const}c_2 := a_2\cup b_2=\{\mathtt{const}\}. Since a2b2a_2\ne b_2, set c1:=c1{const}={const}c_1:=c_1\cup\{\mathtt{const}\}=\{\mathtt{const}\}.
  3. Set c3:=a3b3=c_3 := a_3\cup b_3=\emptyset. Since a3=b3a_3 = b_3, move on.

Then, c=({const},{const},)bc=(\{\mathtt{const}\}, \{\mathtt{const}\}, \emptyset)\ne b, so the conversion fails and we get a compiler error which doesn’t illuminate very much about this process. Great.

What were we talking about again? Oh.

Right. I guess you might want to re-skim the beginning of this post to refresh yourself on the rest of the standard conversion stuff. Before we move on, I’ll add one kind of implicit conversion I didn’t mention that you’re probably already aware of. Temporary materialization is a conversion applied to a prvalue which initializes the prvalue-designated object and produces an xvalue denoting it. This is a cute way of extending the lifetime of a temporary: it happens in cases like the array-to-pointer conversion mentioned earlier, binding a reference to a prvalue, and so on. In general, this only extends the lifetime of the temporary until the evaluation of the originating statement is complete; one of the few exceptions to this is for reference binding:

void foo(int* arr);
using U = int[4];

foo(U{1,2,3,4}); // OK
int* ptr = U{1,2,3,4}; // dangling pointer...
const U& ref = U{1,2,3,4}; // OK

With that rotten cherry on top, let’s zoom back out to overload resolution.

Toward a Better “Better”

While we have an idea of how to convert between types, overload resolution involves converting between many possible types—for each overload—and deciding which conversions are “better.” Recall the definitions given in the previous post:

Definition 2

In overload resolution for an expression f(E1, ..., En), a candidate function FF is called viable if:

  • the number of arguments given “matches” the number of parameters to FF;
  • its constraints (i.e., C++20 concepts/constraints) are satisfied by the expression; and
  • for each argument, there is some implicit conversion sequence that converts it to the type of the corresponding parameter.
Definition 3

Let FF and GG be two viable candidates, and let ICSi(F)\operatorname{ICS}_i(F) represent the (possibly trivial) sequence of implicit conversions that converts the ithi^{\rm th} argument to the type of the ithi^{\rm th} parameter of FF. We say FF is better than GG if, for each ii, ICSi(F)\operatorname{ICS}_i(F) is not worse than ICSi(G)\operatorname{ICS}_i(G), and:

  • There is some jj such that ICSj(F)\operatorname{ICS}_j(F) is a “better” conversion sequence than ICSj(G)\operatorname{ICS}_j(G); or, otherwise,
  • (A list of some other things, omitted for brevity).

There’s that itch. There are so many unanswered questions. For one, we still can’t shake out why one conversion sequence might be better than another; moreover, it’s still not clear why this code shakes out the way it does:

void foo(const int&); // #1
void foo(int&);       // #2

const int x; int y;
foo(4); // #1
foo(x); // #1
foo(y); // #2

We need a rigorous notion of “better.”

Well, here’s a start: let’s say that any standard conversion sequence is always better than a user-defined conversion sequence. Moreover, we’ll say that for two user-defined conversion sequences S1 and S2 which call the same conversion function/non-explicit constructor, S1 is better than S2 if the standard conversion sequence following S1 is better than that following S2 (recall that a (possibly trivial) standard conversion sequence always follows a user-defined conversion, by definition of implicit conversion sequence). That puts user-defined conversion sequences to rest (noting that the term “better” is already itself becoming slightly overloaded), so it remains to rank the standard conversions.

We’re getting there—I can feel it. Let’s kick this off with a table ripped out of [over.ics.scs] in the standard:

[tab:over.ics.scs]
Conversion Rank
None Exact match
Lvalue-to-rvalue
Array-to-pointer
Function-to-pointer
Qualification
Function pointer
Integral promotions Promotion
Floating-point promotion
Integral Conversion
Floating-point
Floating-integral
Pointer
Pointer-to-member
Boolean

As you might imagine, “exact match” is better than “promotion” which is better than “conversion,” and the rank of a conversion sequence is the lowest across the ranks of its constituent conversions. So, if it’s a fight between two conversion sequences, pick the one with the better rank. If they have the same rank, though, it gets a bit more complicated. Let S1 and S2 be standard conversion sequences of the same rank. Then:

  1. If S1 is a proper subsequence of S2, choose S1.
  2. If S1 and S2 are conversions between base/derived class pointers, there are a whole bunch of broadly uninteresting rules about which one’s better that you can probably mostly intuit.
  3. In general, prefer binding rvalue references where possible.2
  4. Prefer having function lvalues bound to lvalue references over rvalue references.3
  5. If S1 and S2 are conversions from T0 to similar types T1 and T2 respectively, differing only in a qualification conversion step, and T1 is qualification-convertible to T2, then S1 is better than S2 (if T1 sits between T0 and T2, it’s “less work” to convert to T1, so we prefer S1).
  6. If references are bound during S1 and S2 and the referred-to types are the same up to top-level cv-qualifiers, prefer the sequence for which the referred-to type is less qualified (i.e., avoid unnecessary cv-qualification in reference binding).

That last rule explains the overload resolution in that earlier example, and it also came up in my last post. Go figure. In any case, we now have standard conversions, hence implicit conversion sequences, and hence overload resolution as a whole. Got all that? No? Fine—this was at least a little dense, so here are some examples:

void foo(const int p); // #1
void foo(int p);       // #2
foo(5); // #1 or #2?
Reveal answer

This one is ill-formed because disambiguation never happens by top-level cv-qualifiers for a non-reference type—any call would be ambiguous, so this “overload” counts as re-definition. It’s not possible to meaningfully disambiguate since we’re passing by value: how should the compiler know whether a const or non-const copy is better than the other?

void run(int (*f)());                // #1
void run(int (*const f)() noexcept); // #2
int foo() noexcept;

run(foo); // #1 or #2?
Reveal answer

This will choose the second overload as the associated implicit conversion sequence is a subset of the first.

  • Candidate 1: function-to-pointer; function pointer; done.
  • Candidate 2: function-to-pointer; done.

Remember that no qualification conversion happens since the only const is the first one. We may as well remove the const. Note that void run(int (const *f)() noexcept) would be ill-formed since function types cannot be cv-qualified.

// f :: "pointer to pointer to `int()`"
void run(int (**f)());                // #1
// g :: "pointer to const pointer to `int() noexcept`"
void run(int (*const *g)() noexcept); // #2
int foo() noexcept;

int (*p)() noexcept = &foo;
// &p :: "pointer to pointer to `int() noexcept`"
run(&p); // #1 or #2?
Reveal answer

Chooses the second overload:

  • Candidate 1: not viable—we can’t do a function pointer conversion at depth beyond “pointer to int() noexcept,” so the best we can do is run qualification conversion, but at that point we’re still off by a noexcept, so the conversion cannot be completed.
  • Candidate 2: qualification conversion; success!
void foo(int*& p);

int arr[3];
foo(arr); // well-formed?
Reveal answer

Ill-formed: array-to-pointer conversion would convert the argument expression arr from an lvalue of type “array of 3 int” to a prvalue of type “pointer to int,” which can’t be bound to the lvalue reference parameter.

// p :: "pointer to pointer to const pointer to int"
void foo(int* const** p);

// a :: "pointer to array of 5 `pointer to int`"
int* (*a)[5]{};
foo(a); // well-formed?
Reveal answer

Ill-formed: the array is not at the top level, so array-to-pointer conversion can’t happen, hence qualification conversion can’t happen.

∗  ∗  ∗

Fuck. It just works. Like a well-oiled machine. I mean, obviously it does—the compilers make it work, after all—but it’s something else to feel how it all works and to be able to reason about it more thoroughly.

…On the other hand, like, that was awful, right? Sure, you can avoid this nonsense by writing sane overloads and not nesting pointers too deeply, but it’s a little terrifying standing back and looking at this grand, winding Rube Goldberg machine that exists just to support ad hoc polymorphism—i.e, name sharing. Conversions, too, I guess, but I think there’s broad agreement right now that implicit conversions are usually something that make it easier to write incorrect code. Was it really worth it? Hard to say. It’s hard not to peer at it, though, in a morbid way, like watching some kind of wounded animal.

A closing note: the standard is very long and dense and scattered and, moreover, I am very stupid, so there’s a non-zero chance something here is wrong. If you’re smarter than me and spot any such instances, send me an email or something. As they say, the easiest way to learn is to be wrong on the internet.

  1. There are also ellipsis conversion sequences, which rank last, but I’m editorializing those away here. 

  2. The actual rule is more complicated than this, but I’m simplifying. 

  3. I just learned that this is a language feature and it’s fucking stupid. Look:

    using U = int();
    void foo(U&&); // #1
    void foo(U&);  // #2
    int bar();
    
    foo(bar); // selects #2 -- OK
    foo(std::move(bar)); // also selects #2 -- ???
    

    There’s a rule in C++ that says, if you have a function f that returns an rvalue reference (say T&&), then the expression f(args) is an xvalue. Today I learned that there’s an exception in this rule—if T is a function type, then it’s an lvalue instead. So you can never actually get an rvalue designating a function. And, like, that makes sense I guess—code isn’t “temporary”—but why allow rvalue references to function types if you’re just going to treat them exactly the same as lvalue references??? 

I, Equality Operator

Couldn’t keep yourself away, eh? Or maybe I couldn’t keep myself away. In any case: I’ve prepared for you a classic tale from everyone’s favourite book: ISO/IEC 14882:2020. It’s a tragedy, of course. All of them are. Now, gather ’round…

∗  ∗  ∗

One of the flagship features that shipped with C++20 a few years ago was an overhaul to comparisons. Gone are the days of writing six different operators (twelve, if you want to reverse the operands) just to do basic ordering and equality comparisons. Now, you only have to implement two—operator== and operator<=> (the “three-way comparison operator,” or more lovingly the “spaceship operator”)—and the benevolent compiler will graciously give you the rest for free.

Basically, operator<=> is a combined operator that tells you whether a given object x is less than, greater than, or equal to another object y (or, in some cases, if they are incomparable). Its return type, for our purposes, will be std::weak_ordering, which has static members less, equivalent, and greater. There are other types that add guarantees or allow for a partial order, but we’ll stick with this for simplicity.

struct T {
    std::weak_ordering operator<=>(const T&) const;
    bool operator==(const T&) const;
};
T t, s;
// the below are all legal:
bool b1 = t == s; // t == s
bool b2 = t != s; // !(t == s)
bool b3 = t <  s; // (t <=> s) == std::weak_ordering::less
bool b4 = t >  s; // (t <=> s) == std::weak_ordering::greater
bool b5 = t <= s; // (t <=> s) == std::weak_ordering::less || (t <=> s) == std::weak_ordering:equivalent
bool b6 = t >= s; // (t <=> s) == std::weak_ordering::greater || (t <=> s) == std::weak_ordering::equivalent

Another complementing feature of this is that operator== and operator<=> support parameter reversal—for example, if you provide bool T::operator==(const S&), you can compare T{} == S{} or S{} == T{} for free. And, if you use the other operators generated from operator== and operator<=>, they’ll also be reversible.

Note that you could choose to implement operator== with a call to operator<=> but, for sufficiently interesting types, this will usually be inefficient and miss possible short-circuits. This is why operator<=> doesn’t give you == for free.

So, enterprising experts we are, we’re going to move all our code to C++20. All of it. Day one. I hear you—it’s a good idea! C++ loves backwards compatibility, after all. Here’s some of the code we’re going to move over:

struct T {
    bool operator==(const T&);
    bool operator!=(const T&);
};

bool b = T{} != T{};

Great stuff. While C++20 affords us the ability to nix our operator!= altogether as mentioned earlier, we’re going to leave things as-is for now since, hypothetically, we didn’t read up about this feature carefully enough beforehand. Here we go, guns blazing, in glorious -std=c++20:

warning: ISO C++20 considers use of overloaded operator '!=' (with operand types 'T' and 'T') to be ambiguous despite there being a unique best viable function with non-reversed arguments [-Wambiguous-reversed-operator]
    bool b = T{} != T{};
             ~~~ ^  ~~~
note: candidate function with non-reversed arguments
    bool operator!=(const T&) { return true; }
         ^
note: ambiguous candidate function with reversed arguments
    bool operator==(const T&) { return true; }
         ^
1 warning generated.

Uh-oh. So, what Clang is telling us is that this technically shouldn’t compile, but it’s for a stupid reason so they’ll compile it for us anyway. How sweet of them! Even sweeter, GCC will compile it without even warning us.

The problem is something like this: when considering an expression like x != y, there are three candidates on the table:

  1. operator!=, the member function we wrote;
  2. operator==, the member function we wrote; and,
  3. operator==, but with the order of its operands reversed.

The latter two are called “rewritten” candidates since they involve rewriting x != y as !(x == y) and !(y == x) respectively. While we won’t get into the gory details of overload resolution—only the morbid and disturbing ones—here are the parts we care about right now:

Definition 1

In overload resolution for an expression f(E1, ..., En), a candidate function FF is called viable if:

  • the number of arguments given “matches” the number of parameters to FF;
  • its constraints (i.e., C++20 concepts/constraints) are satisfied by the expression; and
  • for each provided argument, there is some implicit conversion sequence that converts it to the type of the corresponding parameter of FF.
Definition 2

Let FF and GG be two viable candidates, and let ICSi(F)\operatorname{ICS}_i(F) represent the (possibly trivial) sequence of implicit conversions that converts the ithi^{\rm th} argument to the type of the ithi^{\rm th} parameter of FF. We say FF is better than GG if, for each ii, ICSi(F)\operatorname{ICS}_i(F) is not worse than ICSi(G)\operatorname{ICS}_i(G), and:

  • There is some jj such that ICSj(F)\operatorname{ICS}_j(F) is a “better” conversion sequence than ICSj(G)\operatorname{ICS}_j(G); or, otherwise,
  • (A few other things that we won’t discuss); or, otherwise,
  • GG is a rewritten candidate and FF is not; or, otherwise,
  • FF and GG are both rewritten candidates, but GG is a synthesized candidate with its parameter order reversed while FF is not; or, otherwise,
  • (A few more things that we won’t discuss).

There’s the problem—our operator!= member candidate is better than the non-reversed rewritten operator== candidate, but we can’t say that the operator!= member candidate or reversed rewritten operator== candidate are “better” than each other because the conversion sequences in the parameters for either one aren’t all not worse than the conversion sequences for the other.

In particular, the operator!= member candidate can be thought of as taking an implicit first parameter of type T& (say, *this) and second parameter of type const T&; on the other hand, the reversed rewritten operator== candidate swaps these and takes first parameter of type const T& and second parameter of type T&. The first candidate is better than the second one in the first parameter—what we mean by “better” in this case is, according to [over.ics.rank]/3.2.6, if reference parameter types of two overloads differ only by a top-level const (e.g., const int& and int&), the argument should prefer being bound to the one that’s no more const-qualified than itself. So, the left-hand side of T{} != T{} will prefer the first candidate, but the right-hand side will prefer the second candidate. Overload resolution is at an impasse—no candidate has strictly better conversion sequences than the other, and so the compiler ought to declare ambiguity and bail out.

That’s a problem, isn’t it? Like, obviously we want to use the != that we wrote. Even the compiler agrees with me, telling us that ours is the “unique best viable function.” It’s my understanding that compilers don’t typically make value judgments on the standard.

Well, as usual, I was being a touch dishonest. The (partial) overload resolution mechanism above is only correct per the initial release of C++20, or N4860. This caused a bit of a ruckus and, in the end, some folks on the C++ committee decided to address this retroactively in proposal P2468R2. The net effect of it is that, if a user-provided operator!= is present, the rewritten candidates for operator== won’t be considered for !=, period. So, with a modern compiler, the earlier snippet should compile on C++20. Fantastic! All’s well with the world again.

No—that’s not right. There’s a wrinkle. Let’s scale back that example even further:

struct T {
    bool operator==(const T&);
};

bool b = T{} == T{};

On a modern compiler, this will net us the following under C++20 (and, indeed, under C++23 as well):

warning: ISO C++20 considers use of overloaded operator '==' (with operand types 'T' and 'T') to be ambiguous despite there being a unique best viable function [-Wambiguous-reversed-operator]
    bool b = T{} == T{};
             ~~~ ^  ~~~
note: ambiguity is between a regular call to this operator and a call with the argument order reversed
    bool operator==(const T&) { return true; }
         ^
1 warning generated.

Hmph. It’s the same thing. Can you guess why? I bet you can. You’re so smart. It’s the same problem as earlier, really! Here—when considering an expression like x == y, there are two candidates on the table:

  1. operator==, the member function we wrote; and,
  2. operator==, but with the order of its operands reversed.

It’s the same thing! The const gets flip-flopped around between the two candidates and so the compiler hypothetically becomes incapable of determining which candidate is “better.” OK, look, I hear you yelling at your screen incessantly—stop that, now, it’s disrespectful—yelling that this whole shebang would’ve been avoided altogether had we just const-qualified our operators:

struct T {
    bool operator==(const T&) const;
    bool operator!=(const T&) const;
};

bool b1 = T{} == T{}; // OK
bool b2 = T{} != T{}; // OK

Doing this makes both parameter types the same, so reversing does nothing. And sure, yeah, you have a point. Really, all “morally correct” comparison operators should be const-qualified—of course, if not, your operators will fail some constraints nobody cares about, like std::equality_comparable, but that’s all. Like, come on. Please. I guarantee that your run-of-the-mill Programmer Andy regularly forgets about that and, moreover, I’d wager that you regularly forget about it too. That’s a whole lot of pretty-much-fine code that no longer compiles. Man.

Actually, while we’re at it, here’s a neat corollary: if you provide your own operator!=, it will not have any reversed rewritten candidates, even if you’ve also provided operator==. This is a consequence of P2468R2, i.e., the fix for the earlier problem. And, like… huh? Why? It would be pretty easy to tweak the wording to make it reversible. The standard’s already a million pages—what’s one more? To my understanding, the committee’s reasoning here is that, nowadays, you should only ever write operator<=> and operator== anyway, so it’s not worth giving you the “new” stuff for your “old” code. You can probably already tell I don’t fully buy that. There’s a bunch of existing code that implements the “old” operators, so why not just give it the fancy new stuff? It feels like it undermines the spirit of C++ not to.

Oh well. Better get cracking on that spaceship, I guess.

I Have No Constructor, and I Must Initialize

It has been three days. The room is cold and dark, but your screens are blinding. You feel disoriented as you come in and out of dissociative episodes. Now and again, you laugh, to no accompaniment. Why are you here? Was this your fault?

Your first mistake was to engage—this much is clear.

∗  ∗  ∗

Back when I took a first course in C++ a few years ago, I was taught that, under certain circumstances, the compiler would provide some kind of defaulted constructors in case we don’t provide our own. Curious to know more, my primary concern was with cases like this:

struct T { /* ... */ };

T t;
T s{};
T r{arg1, arg2, ...};

I became interested in the particulars of what this meant. Most of my focus fell on the first two—for the third, I felt satisfied with a hand-wavy explanation of “if T is simple enough, it’ll do component-wise initialization.” The first two are where the danger lies, after all: what if some objects are left uninitialized? The search looked something like what follows.

Primarily, there are two kinds of initialization of concern: default-initialization and value-initialization. The rules given in the standard look roughly like this:

  • For any type T, T t; performs default-initialization on t as follows:
    • If T is a class type and there is a default constructor, run it.
    • If T is an array type, default-initialize each element.
    • Otherwise, do nothing.
  • For any type T, T t{}; performs value-initialization on t as follows:
    • If T is a class type…
      • If there is no default constructor (i.e., if the user has declared any non-default constructors) or if there is a user-provided or deleted default constructor, default-initialize.
      • Otherwise, zero-initialize and then default-initialize.
    • Otherwise, if T is an array type, value-initialize each element.
    • Otherwise, zero-initialize.

You can see each of these in action here:

struct Pair {
    int x, y;
    Pair() : x{0}, y{1} {}
};
struct SimplePair {
    int x, y;
};

int x{}; // value-initialized => zero-initialized
int y; // default-initialized (to garbage)
Pair p; // default-initialized => default-constructed
Pair q{}; // value-initialized => default-initialized => default-constructed
SimplePair r; // default-initialized => default-constructed to garbage (more on this later)

This leaves for discussion the default constructor, i.e., the zero-argument constructor overload. What does the compiler provide us and when? It’s generally common knowledge that, so long as you don’t declare any of your own constructors, the compiler will declare and (possibly) provide its own. But, the devil’s in the details after all—and C++ has a terrifying quantity of details, which bears some implication on the exorcist’s nightmare contained therein.

The Default Constructor

When you don’t declare any constructors, the compiler will declare a default constructor for you: this one is called implicitly-declared. There’s also the almost-identical “defaulted on first declaration” constructor—almost-identical in that they’re mostly interchangeable in the standard, it looks like this:

struct T {
    T() = default;
};

These constructors don’t necessarily do anything by virtue of being implicitly-declared or defaulted on first declaration—after all, they’re only declared so far—but there are knock-on effects which will affect what they do. In particular, if a default constructor is implicitly declared or explicitly defaulted (and not defined as deleted), an implicitly-defined default constructor will be provided by the compiler. In terms of implementation, it’s guaranteed to be equivalent to a constructor with an empty body and empty member initializer list (i.e., T() {}).

So, if we did something like this:

struct T {
    int x;
    T() = default;
};

T t{};
std::cout << t.x << std::endl;

The printed result would be 0. This is because we value-initialize t and, since T has a non-user-provided default constructor, the object is zero-initialized (hence t.x is zero-initialized) then default-initialized (calling the implicitly-defined default constructor, which does nothing).

Naturally, we can also get an implicitly-defined default constructor outside the class as follows:

struct T {
    T();
};
T::T() = default;

Actually, let me augment this to look a little more like the last example:

struct T {
    int x;
    T();
};
T::T() = default;

T t{};
std::cout << t.x << std::endl;

You’d expect the printed result to be 0, right? You poor thing. Alas—it will be garbage. Some things can never be perfect, it seems. Here’s a relevant excerpt from our description of value-initialization:

If there is no default constructor (i.e., if the user has declared any non-default constructors) or if there is a user-provided or deleted default constructor, default-initialize.

A-ha. You see this line?

T::T() = default;

That’s user-provided. By defining the constructor outside the class like this, we are not first-declaring it as defaulted; we are defining it as defaulted. Providing it, if you will. So, the compiler will rightfully opt to simply default-initialize t, hence running the explicitly-defaulted default constructor which does precisely nothing. Great.

Of course, in some situations, it’s impossible for the compiler to provide a sane default constructor—in such cases, it defines the implicitly-declared default constructor as deleted. Here are some of the situations that lead to this:

  • T has a non-static reference member (what would you reasonably default-initialize this to?);
  • T has non-static members or non-abstract base classes which aren’t reasonably default-constructable or destructable (I’m omitting some details here, but you get the idea); or
  • T has any const, non-static, non-const-default-constructible members without default member initializers (if the member is const and won’t get default-initialized to anything useful, our final object would necessarily permanently contain garbage).
    • Aside: for a class type, “const-default-constructible” means default-initialization will invoke a non-inherited user-provided constructor—the idea being that a const object of the type can be sanely initialized by default-initialization.

Remember that that’s all assuming you don’t provide any constructors yourself. If you do, the compiler won’t try to implicitly define a default constructor—not even as deleted. There would be no default constructor at all here.

I’m omitting some details here and eliding discussion of unions altogether, but these are the broad strokes. Basically, if your class has anything that can’t be default-initialized in an at-least-sort-of-potentially-useful way, the compiler will give up and define the implicitly-declared default constructor as deleted. This follows the (often unfortunate) guiding C++ philosophy of being very permissive.

Here’s an example that’s as simple as it gets: the presence of a const int member without a default member initializer (e.g., = 0) defines the implicitly-declared default constructor as deleted, so it won’t compile:

struct A {
    const int x;
};

A a{};

Well, that’s what you’d think if you hadn’t read carefully enough, anyway. As it turns out, this gnarly code is perfectly well-formed and will compile—indeed, a.x will be initialized 0. Why? Because A is an aggregate. And, actually, that’s not value-initialization at all.

Initialization Done Right

Alright, let’s get down to brass tacks. I lied to you. Well, only kind of—all the other examples I gave so far were carefully cooked so that the explanations I gave were still technically right—there was just one incorrect definition, and some very deliberate dancing around a very large elephant in the room.

In fact, when we write something like T t{};, what’s actually being performed first-up is something called list-initialization. Indeed, anything that looks like T t{...}, T t = {...}, or most any other curly-brace-decorated form of initialization, is probably list-initialization. The first two forms here are called direct-list-initialization and copy-list-initialization respectively. Copy-initialization, as a standalone thing, is about initializing an object from another object, usually involving an = in some way; direct-initialization, on the other hand, is about initializing an object from a set of constructor arguments. The practical difference is minimal beyond syntax, so we’ll mostly restrict our discussion to direct-list-initialization.

List-initialization is a bit of a complicated thing but, as it turns out, there’s actually yet another kind of initialization standing between it and the funny-looking const example that got us here. First, a definition:

Definition

An aggregate is either (1) an array or (2) a class which has

  • no user-declared or inherited constructors;
  • no private or protected direct non-static data members;
  • no private or protected direct base classes; and
  • no virtual functions or virtual base classes.

Basically, an aggregate is one kind of “simple” type that we can craft, sitting close behind trivial and standard-layout types. There’s a special kind of list-initialization which exists for aggregates called aggregate initialization. The particulars surrounding this get a little hairy (read: uninteresting) in the standard, but it suffices to say that it’s a souped-up way of copy-initializing each element of the class (or array) with each element of the initializer list, in order. If the number of elements given in the list is less than the number of elements in the aggregate, each remaining element of the aggregate will be initialized with its default member initializer (if it has one) or, assuming it’s not a reference, copy-initialized with an empty initializer list (as in, = {}; this will recursively lead to another round of list-initialization).

So, here’s the glue between list-initialization and aggregate initialization: if list-initialization is performed on an aggregate, aggregate initialization is performed unless the list has only one argument, of type T or of type derived from T, in which case it performs direct-initialization (or copy-initialization). Hence, with an example like this:

struct S {
    int a;
    float b;
    char c;
};

S s{3, 4.0f, 'S'};

…there are no constructor calls to speak of.

Of course, that covers list-initialization for aggregates, but there are a few other cases left. Namely…

  • If T is a non-aggregate class type…
    • If the initializer is empty and T has a default constructor, then value-initialization is performed.
    • Otherwise, consider other constructors according to the usual overload resolution procedure—note that std::initializer_list constructor overloads always get priority here.
  • When the initializer list contains exactly one element, non-class types and references are initialized more or less how you’d expect, so we won’t dwell on them.
  • Finally, otherwise, if the initializer list is empty, value-initialization is performed.

With that, I will correct the subtly wrong definition of value-initialization I gave earlier: for non-aggregate types T, T t{}; performs value-initialization (via list-initialization) on t as follows:

  • If T is a class type…
    • If there is no default constructor or if there is a user-provided or deleted default constructor, default-initialize.
    • Otherwise, zero-initialize and then default-initialize.
  • Otherwise, if T is an array type, value-initialize each element.
  • Otherwise, zero-initialize.

The only addition is the word “non-aggregate.” There are a few wrinkles I’m leaving out (like unions), but they all behave more or less how you’d expect given all of this. Anyway, here’s that gnarly example from earlier again:

struct A {
    const int x;
};

A a{};

A sharp moment of clarity and understanding; the sensation that, if there is a god, it must have spoken to you. You are grateful either way. Here, A is clearly an aggregate, and so list-initialization leads to aggregate initialization which leads to copy-list-initialization of a.x with an empty list, hence value initialization, hence zero initialization. No fuss, no muss. Constructors were never in question to begin with. While we’re feeling so high and mighty, we might even try this:

A b{4};

This performs list-initialization, hence aggregate initialization, hence copy-initialization of b.a with 4. Yes! We might even be so bold as to try this:

A c{4.0f};
// error: narrowing conversion of '4.0e+0f' from 'float' to 'int' [-Wnarrowing]

Fuck. OK, maybe we pushed our luck. I forgot to mention that list-initializing with one element doesn’t allow for narrowing conversions. It’s fine, though. It’s all fine. Here:

A c(4.0f); // N.B. parentheses, not braces

Under C++20, this compiles.

Cry.

Lists But Rounder

You might recall from a first course in C++ that you can kind of mostly use parentheses in the place of braces for the purposes of initialization. Not everywhere, but, like, mostwhere. You were probably told to avoid it for reasons like the most vexing parse: while T t(a, b, c); syntactically represents an invocation of some constructor (not quite; we’ll discuss this later), T t(); syntactically represents a declaration of a function t which takes no parameters and has return type T. Here, you really need to either settle on T t{}; or T t; instead. However, this parenthesized expression-list initializer is often functionally different from braced-init-list initializers. Parenthesized initializers invoke direct-non-list-initialization, which has rules that are similar to but different from direct-list-initialization.

Parenthesized initializers let us perform aggregate initialization on aggregates (both classes and arrays) in basically the same way as with list-initialization, but narrowing conversions are allowed, remaining elements are directly value-initialized (rather than empty-list-initialized), and temporaries bound to references do not have their lifetime extended. Did you catch that last one? Here’s the action replay:

struct T {
    const int& r;
};

T t(42);

That’s right: t.r is a dangling reference. Reading from it is undefined behaviour. What a world. I really can’t imagine why this would be desired behaviour for any programmer ever, but that’s just how things are sometimes.

In any case, parentheses are generally less “regulatory”; they’re often more permissive. Along with those allowances I just mentioned, it also lets us invoke the copy constructor for T in case there’s also a std::initializer_list<T> constructor overload—recall that such overloads take priority in overload resolution, and a braced-init-list of Ts can be interpreted as std::initializer_list<T>.

struct T {
    T(std::initializer_list<T>) {
        std::cout << "list" << std::endl;
    }
    T(const T&) {
        std::cout << "copy" << std::endl;
    }
};

T t{}; // list
T s{t} // list
T r(t); // copy
T q(T{}); // list (no copy!)

That last one might come as a surprise—according to what we’ve seen so far, we would expect the list constructor to be used for T{}, followed by the copy constructor for q(T{}). You may recall something called copy elision—this is essentially that. In particular, direct- and copy-initialization have provisions where, if the initializer is a prvalue of type T, the object gets initialized directly by the expression rather than the temporary materialized by it. This is never explicitly called “elision” by the standard—one might argue that it’s not even an appropriate name for it since C++17—but it’s probably what you know it as anyway.

An aside: from what I can tell, for some reason, this technically only works if non-list-initialization is used, i.e, T q(T{}); but NOT T q{T{}};. Like, there’s just nothing described in the standard about list-initialization that would allow for elision to take place. Both GCC and Clang ignore this and elide anyway in most cases, except if a std::initializer_list<T> constructor overload is defined (like above), in which case GCC uses it instead of eliding—I understand this to be a single corner case where GCC does the right thing. I expect this will be cleared up eventually—see CWG issue 2311.

Anyway, for a parenthesized initializer, if this elision provision doesn’t apply, constructors are considered as you would expect; if there are none and T is an aggregate class, it’ll do per-element copy-initialization as discussed earlier.

One last nugget: elements of parenthesized initialization lists have no guaranteed evaluation order, whereas braced initialization lists evaluate elements strictly from left to right.

∗  ∗  ∗

That should be most of it. I mean, there are special initialization rules for static variables (constant initialization included), but, like, do you really care? In my humble opinion, here’s the key takeaway: just write your own fucking constructors! You see all that nonsense? Almost completely avoidable if you had just written your own fucking constructors. Don’t let the compiler figure it out for you. You’re the one in control here. Or is it that you think you’re being cute? You just added six instances of undefined behaviour to your company’s codebase, and now twenty Russian hackers are fighting to pwn your app first. Are you stupid? What’s the matter with you? What were you thinking? God.