1*760c2415Smrg // Written in the D programming language.
2*760c2415Smrg 
3*760c2415Smrg /**
4*760c2415Smrg This module implements a
5*760c2415Smrg $(HTTP erdani.org/publications/cuj-04-2002.html,discriminated union)
6*760c2415Smrg type (a.k.a.
7*760c2415Smrg $(HTTP en.wikipedia.org/wiki/Tagged_union,tagged union),
8*760c2415Smrg $(HTTP en.wikipedia.org/wiki/Algebraic_data_type,algebraic type)).
9*760c2415Smrg Such types are useful
10*760c2415Smrg for type-uniform binary interfaces, interfacing with scripting
11*760c2415Smrg languages, and comfortable exploratory programming.
12*760c2415Smrg 
13*760c2415Smrg A $(LREF Variant) object can hold a value of any type, with very few
14*760c2415Smrg restrictions (such as `shared` types and noncopyable types). Setting the value
15*760c2415Smrg is as immediate as assigning to the `Variant` object. To read back the value of
16*760c2415Smrg the appropriate type `T`, use the $(LREF get!T) call. To query whether a
17*760c2415Smrg `Variant` currently holds a value of type `T`, use $(LREF peek!T). To fetch the
18*760c2415Smrg exact type currently held, call $(LREF type), which returns the `TypeInfo` of
19*760c2415Smrg the current value.
20*760c2415Smrg 
21*760c2415Smrg In addition to $(LREF Variant), this module also defines the $(LREF Algebraic)
22*760c2415Smrg type constructor. Unlike `Variant`, `Algebraic` only allows a finite set of
23*760c2415Smrg types, which are specified in the instantiation (e.g. $(D Algebraic!(int,
24*760c2415Smrg string)) may only hold an `int` or a `string`).
25*760c2415Smrg 
26*760c2415Smrg Credits: Reviewed by Brad Roberts. Daniel Keep provided a detailed code review
27*760c2415Smrg prompting the following improvements: (1) better support for arrays; (2) support
28*760c2415Smrg for associative arrays; (3) friendlier behavior towards the garbage collector.
29*760c2415Smrg Copyright: Copyright Andrei Alexandrescu 2007 - 2015.
30*760c2415Smrg License:   $(HTTP www.boost.org/LICENSE_1_0.txt, Boost License 1.0).
31*760c2415Smrg Authors:   $(HTTP erdani.org, Andrei Alexandrescu)
32*760c2415Smrg Source:    $(PHOBOSSRC std/_variant.d)
33*760c2415Smrg */
34*760c2415Smrg module std.variant;
35*760c2415Smrg 
36*760c2415Smrg import std.meta, std.traits, std.typecons;
37*760c2415Smrg 
38*760c2415Smrg ///
39*760c2415Smrg @system unittest
40*760c2415Smrg {
41*760c2415Smrg     Variant a; // Must assign before use, otherwise exception ensues
42*760c2415Smrg     // Initialize with an integer; make the type int
43*760c2415Smrg     Variant b = 42;
44*760c2415Smrg     assert(b.type == typeid(int));
45*760c2415Smrg     // Peek at the value
46*760c2415Smrg     assert(b.peek!(int) !is null && *b.peek!(int) == 42);
47*760c2415Smrg     // Automatically convert per language rules
48*760c2415Smrg     auto x = b.get!(real);
49*760c2415Smrg 
50*760c2415Smrg     // Assign any other type, including other variants
51*760c2415Smrg     a = b;
52*760c2415Smrg     a = 3.14;
53*760c2415Smrg     assert(a.type == typeid(double));
54*760c2415Smrg     // Implicit conversions work just as with built-in types
55*760c2415Smrg     assert(a < b);
56*760c2415Smrg     // Check for convertibility
57*760c2415Smrg     assert(!a.convertsTo!(int)); // double not convertible to int
58*760c2415Smrg     // Strings and all other arrays are supported
59*760c2415Smrg     a = "now I'm a string";
60*760c2415Smrg     assert(a == "now I'm a string");
61*760c2415Smrg 
62*760c2415Smrg     // can also assign arrays
63*760c2415Smrg     a = new int[42];
64*760c2415Smrg     assert(a.length == 42);
65*760c2415Smrg     a[5] = 7;
66*760c2415Smrg     assert(a[5] == 7);
67*760c2415Smrg 
68*760c2415Smrg     // Can also assign class values
69*760c2415Smrg     class Foo {}
70*760c2415Smrg     auto foo = new Foo;
71*760c2415Smrg     a = foo;
72*760c2415Smrg     assert(*a.peek!(Foo) == foo); // and full type information is preserved
73*760c2415Smrg }
74*760c2415Smrg 
75*760c2415Smrg /++
76*760c2415Smrg     Gives the $(D sizeof) the largest type given.
77*760c2415Smrg   +/
maxSize(T...)78*760c2415Smrg template maxSize(T...)
79*760c2415Smrg {
80*760c2415Smrg     static if (T.length == 1)
81*760c2415Smrg     {
82*760c2415Smrg         enum size_t maxSize = T[0].sizeof;
83*760c2415Smrg     }
84*760c2415Smrg     else
85*760c2415Smrg     {
86*760c2415Smrg         import std.algorithm.comparison : max;
87*760c2415Smrg         enum size_t maxSize = max(T[0].sizeof, maxSize!(T[1 .. $]));
88*760c2415Smrg     }
89*760c2415Smrg }
90*760c2415Smrg 
91*760c2415Smrg ///
92*760c2415Smrg @safe unittest
93*760c2415Smrg {
94*760c2415Smrg     static assert(maxSize!(int, long) == 8);
95*760c2415Smrg     static assert(maxSize!(bool, byte) == 1);
96*760c2415Smrg 
97*760c2415Smrg     struct Cat { int a, b, c; }
98*760c2415Smrg     static assert(maxSize!(bool, Cat) == 12);
99*760c2415Smrg }
100*760c2415Smrg 
101*760c2415Smrg struct This;
102*760c2415Smrg 
103*760c2415Smrg private alias This2Variant(V, T...) = AliasSeq!(ReplaceType!(This, V, T));
104*760c2415Smrg 
105*760c2415Smrg /**
106*760c2415Smrg  * Back-end type seldom used directly by user
107*760c2415Smrg  * code. Two commonly-used types using $(D VariantN) are:
108*760c2415Smrg  *
109*760c2415Smrg  * $(OL $(LI $(LREF Algebraic): A closed discriminated union with a
110*760c2415Smrg  * limited type universe (e.g., $(D Algebraic!(int, double,
111*760c2415Smrg  * string)) only accepts these three types and rejects anything
112*760c2415Smrg  * else).) $(LI $(LREF Variant): An open discriminated union allowing an
113*760c2415Smrg  * unbounded set of types. If any of the types in the $(D Variant)
114*760c2415Smrg  * are larger than the largest built-in type, they will automatically
115*760c2415Smrg  * be boxed. This means that even large types will only be the size
116*760c2415Smrg  * of a pointer within the $(D Variant), but this also implies some
117*760c2415Smrg  * overhead. $(D Variant) can accommodate all primitive types and
118*760c2415Smrg  * all user-defined types.))
119*760c2415Smrg  *
120*760c2415Smrg  * Both $(D Algebraic) and $(D Variant) share $(D
121*760c2415Smrg  * VariantN)'s interface. (See their respective documentations below.)
122*760c2415Smrg  *
123*760c2415Smrg  * $(D VariantN) is a discriminated union type parameterized
124*760c2415Smrg  * with the largest size of the types stored ($(D maxDataSize))
125*760c2415Smrg  * and with the list of allowed types ($(D AllowedTypes)). If
126*760c2415Smrg  * the list is empty, then any type up of size up to $(D
127*760c2415Smrg  * maxDataSize) (rounded up for alignment) can be stored in a
128*760c2415Smrg  * $(D VariantN) object without being boxed (types larger
129*760c2415Smrg  * than this will be boxed).
130*760c2415Smrg  *
131*760c2415Smrg  */
VariantN(size_t maxDataSize,AllowedTypesParam...)132*760c2415Smrg struct VariantN(size_t maxDataSize, AllowedTypesParam...)
133*760c2415Smrg {
134*760c2415Smrg     /**
135*760c2415Smrg     The list of allowed types. If empty, any type is allowed.
136*760c2415Smrg     */
137*760c2415Smrg     alias AllowedTypes = This2Variant!(VariantN, AllowedTypesParam);
138*760c2415Smrg 
139*760c2415Smrg private:
140*760c2415Smrg     // Compute the largest practical size from maxDataSize
141*760c2415Smrg     struct SizeChecker
142*760c2415Smrg     {
143*760c2415Smrg         int function() fptr;
144*760c2415Smrg         ubyte[maxDataSize] data;
145*760c2415Smrg     }
146*760c2415Smrg     enum size = SizeChecker.sizeof - (int function()).sizeof;
147*760c2415Smrg 
148*760c2415Smrg     /** Tells whether a type $(D T) is statically _allowed for
149*760c2415Smrg      * storage inside a $(D VariantN) object by looking
150*760c2415Smrg      * $(D T) up in $(D AllowedTypes).
151*760c2415Smrg      */
152*760c2415Smrg     public template allowed(T)
153*760c2415Smrg     {
154*760c2415Smrg         enum bool allowed
155*760c2415Smrg             = is(T == VariantN)
156*760c2415Smrg             ||
157*760c2415Smrg             //T.sizeof <= size &&
158*760c2415Smrg             (AllowedTypes.length == 0 || staticIndexOf!(T, AllowedTypes) >= 0);
159*760c2415Smrg     }
160*760c2415Smrg 
161*760c2415Smrg     // Each internal operation is encoded with an identifier. See
162*760c2415Smrg     // the "handler" function below.
163*760c2415Smrg     enum OpID { getTypeInfo, get, compare, equals, testConversion, toString,
164*760c2415Smrg             index, indexAssign, catAssign, copyOut, length,
165*760c2415Smrg             apply, postblit, destruct }
166*760c2415Smrg 
167*760c2415Smrg     // state
168*760c2415Smrg     ptrdiff_t function(OpID selector, ubyte[size]* store, void* data) fptr
169*760c2415Smrg         = &handler!(void);
170*760c2415Smrg     union
171*760c2415Smrg     {
172*760c2415Smrg         ubyte[size] store;
173*760c2415Smrg         // conservatively mark the region as pointers
174*760c2415Smrg         static if (size >= (void*).sizeof)
175*760c2415Smrg             void*[size / (void*).sizeof] p;
176*760c2415Smrg     }
177*760c2415Smrg 
178*760c2415Smrg     // internals
179*760c2415Smrg     // Handler for an uninitialized value
180*760c2415Smrg     static ptrdiff_t handler(A : void)(OpID selector, ubyte[size]*, void* parm)
181*760c2415Smrg     {
182*760c2415Smrg         switch (selector)
183*760c2415Smrg         {
184*760c2415Smrg         case OpID.getTypeInfo:
185*760c2415Smrg             *cast(TypeInfo *) parm = typeid(A);
186*760c2415Smrg             break;
187*760c2415Smrg         case OpID.copyOut:
188*760c2415Smrg             auto target = cast(VariantN *) parm;
189*760c2415Smrg             target.fptr = &handler!(A);
190*760c2415Smrg             // no need to copy the data (it's garbage)
191*760c2415Smrg             break;
192*760c2415Smrg         case OpID.compare:
193*760c2415Smrg         case OpID.equals:
194*760c2415Smrg             auto rhs = cast(const VariantN *) parm;
195*760c2415Smrg             return rhs.peek!(A)
196*760c2415Smrg                 ? 0 // all uninitialized are equal
197*760c2415Smrg                 : ptrdiff_t.min; // uninitialized variant is not comparable otherwise
198*760c2415Smrg         case OpID.toString:
199*760c2415Smrg             string * target = cast(string*) parm;
200*760c2415Smrg             *target = "<Uninitialized VariantN>";
201*760c2415Smrg             break;
202*760c2415Smrg         case OpID.postblit:
203*760c2415Smrg         case OpID.destruct:
204*760c2415Smrg             break;
205*760c2415Smrg         case OpID.get:
206*760c2415Smrg         case OpID.testConversion:
207*760c2415Smrg         case OpID.index:
208*760c2415Smrg         case OpID.indexAssign:
209*760c2415Smrg         case OpID.catAssign:
210*760c2415Smrg         case OpID.length:
211*760c2415Smrg             throw new VariantException(
212*760c2415Smrg                 "Attempt to use an uninitialized VariantN");
213*760c2415Smrg         default: assert(false, "Invalid OpID");
214*760c2415Smrg         }
215*760c2415Smrg         return 0;
216*760c2415Smrg     }
217*760c2415Smrg 
218*760c2415Smrg     // Handler for all of a type's operations
219*760c2415Smrg     static ptrdiff_t handler(A)(OpID selector, ubyte[size]* pStore, void* parm)
220*760c2415Smrg     {
221*760c2415Smrg         import std.conv : to;
222*760c2415Smrg         static A* getPtr(void* untyped)
223*760c2415Smrg         {
224*760c2415Smrg             if (untyped)
225*760c2415Smrg             {
226*760c2415Smrg                 static if (A.sizeof <= size)
227*760c2415Smrg                     return cast(A*) untyped;
228*760c2415Smrg                 else
229*760c2415Smrg                     return *cast(A**) untyped;
230*760c2415Smrg             }
231*760c2415Smrg             return null;
232*760c2415Smrg         }
233*760c2415Smrg 
234*760c2415Smrg         static ptrdiff_t compare(A* rhsPA, A* zis, OpID selector)
235*760c2415Smrg         {
236*760c2415Smrg             static if (is(typeof(*rhsPA == *zis)))
237*760c2415Smrg             {
238*760c2415Smrg                 if (*rhsPA == *zis)
239*760c2415Smrg                 {
240*760c2415Smrg                     return 0;
241*760c2415Smrg                 }
242*760c2415Smrg                 static if (is(typeof(*zis < *rhsPA)))
243*760c2415Smrg                 {
244*760c2415Smrg                     // Many types (such as any using the default Object opCmp)
245*760c2415Smrg                     // will throw on an invalid opCmp, so do it only
246*760c2415Smrg                     // if the caller requests it.
247*760c2415Smrg                     if (selector == OpID.compare)
248*760c2415Smrg                         return *zis < *rhsPA ? -1 : 1;
249*760c2415Smrg                     else
250*760c2415Smrg                         return ptrdiff_t.min;
251*760c2415Smrg                 }
252*760c2415Smrg                 else
253*760c2415Smrg                 {
254*760c2415Smrg                     // Not equal, and type does not support ordering
255*760c2415Smrg                     // comparisons.
256*760c2415Smrg                     return ptrdiff_t.min;
257*760c2415Smrg                 }
258*760c2415Smrg             }
259*760c2415Smrg             else
260*760c2415Smrg             {
261*760c2415Smrg                 // Type does not support comparisons at all.
262*760c2415Smrg                 return ptrdiff_t.min;
263*760c2415Smrg             }
264*760c2415Smrg         }
265*760c2415Smrg 
266*760c2415Smrg         auto zis = getPtr(pStore);
267*760c2415Smrg         // Input: TypeInfo object
268*760c2415Smrg         // Output: target points to a copy of *me, if me was not null
269*760c2415Smrg         // Returns: true iff the A can be converted to the type represented
270*760c2415Smrg         // by the incoming TypeInfo
271*760c2415Smrg         static bool tryPutting(A* src, TypeInfo targetType, void* target)
272*760c2415Smrg         {
273*760c2415Smrg             alias UA = Unqual!A;
274*760c2415Smrg             alias MutaTypes = AliasSeq!(UA, ImplicitConversionTargets!UA);
275*760c2415Smrg             alias ConstTypes = staticMap!(ConstOf, MutaTypes);
276*760c2415Smrg             alias SharedTypes = staticMap!(SharedOf, MutaTypes);
277*760c2415Smrg             alias SharedConstTypes = staticMap!(SharedConstOf, MutaTypes);
278*760c2415Smrg             alias ImmuTypes  = staticMap!(ImmutableOf, MutaTypes);
279*760c2415Smrg 
280*760c2415Smrg             static if (is(A == immutable))
281*760c2415Smrg                 alias AllTypes = AliasSeq!(ImmuTypes, ConstTypes, SharedConstTypes);
282*760c2415Smrg             else static if (is(A == shared))
283*760c2415Smrg             {
284*760c2415Smrg                 static if (is(A == const))
285*760c2415Smrg                     alias AllTypes = SharedConstTypes;
286*760c2415Smrg                 else
287*760c2415Smrg                     alias AllTypes = AliasSeq!(SharedTypes, SharedConstTypes);
288*760c2415Smrg             }
289*760c2415Smrg             else
290*760c2415Smrg             {
291*760c2415Smrg                 static if (is(A == const))
292*760c2415Smrg                     alias AllTypes = ConstTypes;
293*760c2415Smrg                 else
294*760c2415Smrg                     alias AllTypes = AliasSeq!(MutaTypes, ConstTypes);
295*760c2415Smrg             }
296*760c2415Smrg 
297*760c2415Smrg             foreach (T ; AllTypes)
298*760c2415Smrg             {
299*760c2415Smrg                 if (targetType != typeid(T))
300*760c2415Smrg                     continue;
301*760c2415Smrg 
302*760c2415Smrg                 static if (is(typeof(*cast(T*) target = *src)) ||
303*760c2415Smrg                            is(T ==        const(U), U) ||
304*760c2415Smrg                            is(T ==       shared(U), U) ||
305*760c2415Smrg                            is(T == shared const(U), U) ||
306*760c2415Smrg                            is(T ==    immutable(U), U))
307*760c2415Smrg                 {
308*760c2415Smrg                     import std.conv : emplaceRef;
309*760c2415Smrg 
310*760c2415Smrg                     auto zat = cast(T*) target;
311*760c2415Smrg                     if (src)
312*760c2415Smrg                     {
313*760c2415Smrg                         static if (T.sizeof > 0)
314*760c2415Smrg                             assert(target, "target must be non-null");
315*760c2415Smrg 
316*760c2415Smrg                         emplaceRef(*cast(Unqual!T*) zat, *cast(UA*) src);
317*760c2415Smrg                     }
318*760c2415Smrg                 }
319*760c2415Smrg                 else
320*760c2415Smrg                 {
321*760c2415Smrg                     // type T is not constructible from A
322*760c2415Smrg                     if (src)
323*760c2415Smrg                         assert(false, A.stringof);
324*760c2415Smrg                 }
325*760c2415Smrg                 return true;
326*760c2415Smrg             }
327*760c2415Smrg             return false;
328*760c2415Smrg         }
329*760c2415Smrg 
330*760c2415Smrg         switch (selector)
331*760c2415Smrg         {
332*760c2415Smrg         case OpID.getTypeInfo:
333*760c2415Smrg             *cast(TypeInfo *) parm = typeid(A);
334*760c2415Smrg             break;
335*760c2415Smrg         case OpID.copyOut:
336*760c2415Smrg             auto target = cast(VariantN *) parm;
337*760c2415Smrg             assert(target);
338*760c2415Smrg 
339*760c2415Smrg             static if (target.size < A.sizeof)
340*760c2415Smrg             {
341*760c2415Smrg                 if (target.type.tsize < A.sizeof)
342*760c2415Smrg                     *cast(A**)&target.store = new A;
343*760c2415Smrg             }
344*760c2415Smrg             tryPutting(zis, typeid(A), cast(void*) getPtr(&target.store))
345*760c2415Smrg                 || assert(false);
346*760c2415Smrg             target.fptr = &handler!(A);
347*760c2415Smrg             break;
348*760c2415Smrg         case OpID.get:
349*760c2415Smrg             auto t = * cast(Tuple!(TypeInfo, void*)*) parm;
350*760c2415Smrg             return !tryPutting(zis, t[0], t[1]);
351*760c2415Smrg         case OpID.testConversion:
352*760c2415Smrg             return !tryPutting(null, *cast(TypeInfo*) parm, null);
353*760c2415Smrg         case OpID.compare:
354*760c2415Smrg         case OpID.equals:
355*760c2415Smrg             auto rhsP = cast(VariantN *) parm;
356*760c2415Smrg             auto rhsType = rhsP.type;
357*760c2415Smrg             // Are we the same?
358*760c2415Smrg             if (rhsType == typeid(A))
359*760c2415Smrg             {
360*760c2415Smrg                 // cool! Same type!
361*760c2415Smrg                 auto rhsPA = getPtr(&rhsP.store);
362*760c2415Smrg                 return compare(rhsPA, zis, selector);
363*760c2415Smrg             }
364*760c2415Smrg             else if (rhsType == typeid(void))
365*760c2415Smrg             {
366*760c2415Smrg                 // No support for ordering comparisons with
367*760c2415Smrg                 // uninitialized vars
368*760c2415Smrg                 return ptrdiff_t.min;
369*760c2415Smrg             }
370*760c2415Smrg             VariantN temp;
371*760c2415Smrg             // Do I convert to rhs?
372*760c2415Smrg             if (tryPutting(zis, rhsType, &temp.store))
373*760c2415Smrg             {
374*760c2415Smrg                 // cool, I do; temp's store contains my data in rhs's type!
375*760c2415Smrg                 // also fix up its fptr
376*760c2415Smrg                 temp.fptr = rhsP.fptr;
377*760c2415Smrg                 // now lhsWithRhsType is a full-blown VariantN of rhs's type
378*760c2415Smrg                 if (selector == OpID.compare)
379*760c2415Smrg                     return temp.opCmp(*rhsP);
380*760c2415Smrg                 else
381*760c2415Smrg                     return temp.opEquals(*rhsP) ? 0 : 1;
382*760c2415Smrg             }
383*760c2415Smrg             // Does rhs convert to zis?
384*760c2415Smrg             auto t = tuple(typeid(A), &temp.store);
385*760c2415Smrg             if (rhsP.fptr(OpID.get, &rhsP.store, &t) == 0)
386*760c2415Smrg             {
387*760c2415Smrg                 // cool! Now temp has rhs in my type!
388*760c2415Smrg                 auto rhsPA = getPtr(&temp.store);
389*760c2415Smrg                 return compare(rhsPA, zis, selector);
390*760c2415Smrg             }
391*760c2415Smrg             return ptrdiff_t.min; // dunno
392*760c2415Smrg         case OpID.toString:
393*760c2415Smrg             auto target = cast(string*) parm;
394*760c2415Smrg             static if (is(typeof(to!(string)(*zis))))
395*760c2415Smrg             {
396*760c2415Smrg                 *target = to!(string)(*zis);
397*760c2415Smrg                 break;
398*760c2415Smrg             }
399*760c2415Smrg             // TODO: The following test evaluates to true for shared objects.
400*760c2415Smrg             //       Use __traits for now until this is sorted out.
401*760c2415Smrg             // else static if (is(typeof((*zis).toString)))
402*760c2415Smrg             else static if (__traits(compiles, {(*zis).toString();}))
403*760c2415Smrg             {
404*760c2415Smrg                 *target = (*zis).toString();
405*760c2415Smrg                 break;
406*760c2415Smrg             }
407*760c2415Smrg             else
408*760c2415Smrg             {
409*760c2415Smrg                 throw new VariantException(typeid(A), typeid(string));
410*760c2415Smrg             }
411*760c2415Smrg 
412*760c2415Smrg         case OpID.index:
413*760c2415Smrg             auto result = cast(Variant*) parm;
414*760c2415Smrg             static if (isArray!(A) && !is(Unqual!(typeof(A.init[0])) == void))
415*760c2415Smrg             {
416*760c2415Smrg                 // array type; input and output are the same VariantN
417*760c2415Smrg                 size_t index = result.convertsTo!(int)
418*760c2415Smrg                     ? result.get!(int) : result.get!(size_t);
419*760c2415Smrg                 *result = (*zis)[index];
420*760c2415Smrg                 break;
421*760c2415Smrg             }
422*760c2415Smrg             else static if (isAssociativeArray!(A))
423*760c2415Smrg             {
424*760c2415Smrg                 *result = (*zis)[result.get!(typeof(A.init.keys[0]))];
425*760c2415Smrg                 break;
426*760c2415Smrg             }
427*760c2415Smrg             else
428*760c2415Smrg             {
429*760c2415Smrg                 throw new VariantException(typeid(A), result[0].type);
430*760c2415Smrg             }
431*760c2415Smrg 
432*760c2415Smrg         case OpID.indexAssign:
433*760c2415Smrg             // array type; result comes first, index comes second
434*760c2415Smrg             auto args = cast(Variant*) parm;
435*760c2415Smrg             static if (isArray!(A) && is(typeof((*zis)[0] = (*zis)[0])))
436*760c2415Smrg             {
437*760c2415Smrg                 size_t index = args[1].convertsTo!(int)
438*760c2415Smrg                     ? args[1].get!(int) : args[1].get!(size_t);
439*760c2415Smrg                 (*zis)[index] = args[0].get!(typeof((*zis)[0]));
440*760c2415Smrg                 break;
441*760c2415Smrg             }
442*760c2415Smrg             else static if (isAssociativeArray!(A))
443*760c2415Smrg             {
444*760c2415Smrg                 (*zis)[args[1].get!(typeof(A.init.keys[0]))]
445*760c2415Smrg                     = args[0].get!(typeof(A.init.values[0]));
446*760c2415Smrg                 break;
447*760c2415Smrg             }
448*760c2415Smrg             else
449*760c2415Smrg             {
450*760c2415Smrg                 throw new VariantException(typeid(A), args[0].type);
451*760c2415Smrg             }
452*760c2415Smrg 
453*760c2415Smrg         case OpID.catAssign:
454*760c2415Smrg             static if (!is(Unqual!(typeof((*zis)[0])) == void) && is(typeof((*zis)[0])) && is(typeof((*zis) ~= *zis)))
455*760c2415Smrg             {
456*760c2415Smrg                 // array type; parm is the element to append
457*760c2415Smrg                 auto arg = cast(Variant*) parm;
458*760c2415Smrg                 alias E = typeof((*zis)[0]);
459*760c2415Smrg                 if (arg[0].convertsTo!(E))
460*760c2415Smrg                 {
461*760c2415Smrg                     // append one element to the array
462*760c2415Smrg                     (*zis) ~= [ arg[0].get!(E) ];
463*760c2415Smrg                 }
464*760c2415Smrg                 else
465*760c2415Smrg                 {
466*760c2415Smrg                     // append a whole array to the array
467*760c2415Smrg                     (*zis) ~= arg[0].get!(A);
468*760c2415Smrg                 }
469*760c2415Smrg                 break;
470*760c2415Smrg             }
471*760c2415Smrg             else
472*760c2415Smrg             {
473*760c2415Smrg                 throw new VariantException(typeid(A), typeid(void[]));
474*760c2415Smrg             }
475*760c2415Smrg 
476*760c2415Smrg         case OpID.length:
477*760c2415Smrg             static if (isArray!(A) || isAssociativeArray!(A))
478*760c2415Smrg             {
479*760c2415Smrg                 return zis.length;
480*760c2415Smrg             }
481*760c2415Smrg             else
482*760c2415Smrg             {
483*760c2415Smrg                 throw new VariantException(typeid(A), typeid(void[]));
484*760c2415Smrg             }
485*760c2415Smrg 
486*760c2415Smrg         case OpID.apply:
487*760c2415Smrg             static if (!isFunctionPointer!A && !isDelegate!A)
488*760c2415Smrg             {
489*760c2415Smrg                 import std.conv : text;
490*760c2415Smrg                 import std.exception : enforce;
491*760c2415Smrg                 enforce(0, text("Cannot apply `()' to a value of type `",
492*760c2415Smrg                                 A.stringof, "'."));
493*760c2415Smrg             }
494*760c2415Smrg             else
495*760c2415Smrg             {
496*760c2415Smrg                 import std.conv : text;
497*760c2415Smrg                 import std.exception : enforce;
498*760c2415Smrg                 alias ParamTypes = Parameters!A;
499*760c2415Smrg                 auto p = cast(Variant*) parm;
500*760c2415Smrg                 auto argCount = p.get!size_t;
501*760c2415Smrg                 // To assign the tuple we need to use the unqualified version,
502*760c2415Smrg                 // otherwise we run into issues such as with const values.
503*760c2415Smrg                 // We still get the actual type from the Variant though
504*760c2415Smrg                 // to ensure that we retain const correctness.
505*760c2415Smrg                 Tuple!(staticMap!(Unqual, ParamTypes)) t;
506*760c2415Smrg                 enforce(t.length == argCount,
507*760c2415Smrg                         text("Argument count mismatch: ",
508*760c2415Smrg                              A.stringof, " expects ", t.length,
509*760c2415Smrg                              " argument(s), not ", argCount, "."));
510*760c2415Smrg                 auto variantArgs = p[1 .. argCount + 1];
511*760c2415Smrg                 foreach (i, T; ParamTypes)
512*760c2415Smrg                 {
513*760c2415Smrg                     t[i] = cast() variantArgs[i].get!T;
514*760c2415Smrg                 }
515*760c2415Smrg 
516*760c2415Smrg                 auto args = cast(Tuple!(ParamTypes))t;
517*760c2415Smrg                 static if (is(ReturnType!A == void))
518*760c2415Smrg                 {
519*760c2415Smrg                     (*zis)(args.expand);
520*760c2415Smrg                     *p = Variant.init; // void returns uninitialized Variant.
521*760c2415Smrg                 }
522*760c2415Smrg                 else
523*760c2415Smrg                 {
524*760c2415Smrg                     *p = (*zis)(args.expand);
525*760c2415Smrg                 }
526*760c2415Smrg             }
527*760c2415Smrg             break;
528*760c2415Smrg 
529*760c2415Smrg         case OpID.postblit:
530*760c2415Smrg             static if (hasElaborateCopyConstructor!A)
531*760c2415Smrg             {
532*760c2415Smrg                 typeid(A).postblit(zis);
533*760c2415Smrg             }
534*760c2415Smrg             break;
535*760c2415Smrg 
536*760c2415Smrg         case OpID.destruct:
537*760c2415Smrg             static if (hasElaborateDestructor!A)
538*760c2415Smrg             {
539*760c2415Smrg                 typeid(A).destroy(zis);
540*760c2415Smrg             }
541*760c2415Smrg             break;
542*760c2415Smrg 
543*760c2415Smrg         default: assert(false);
544*760c2415Smrg         }
545*760c2415Smrg         return 0;
546*760c2415Smrg     }
547*760c2415Smrg 
548*760c2415Smrg     enum doUnittest = is(VariantN == Variant);
549*760c2415Smrg 
550*760c2415Smrg public:
551*760c2415Smrg     /** Constructs a $(D VariantN) value given an argument of a
552*760c2415Smrg      * generic type. Statically rejects disallowed types.
553*760c2415Smrg      */
554*760c2415Smrg 
555*760c2415Smrg     this(T)(T value)
556*760c2415Smrg     {
557*760c2415Smrg         static assert(allowed!(T), "Cannot store a " ~ T.stringof
558*760c2415Smrg             ~ " in a " ~ VariantN.stringof);
559*760c2415Smrg         opAssign(value);
560*760c2415Smrg     }
561*760c2415Smrg 
562*760c2415Smrg     /// Allows assignment from a subset algebraic type
563*760c2415Smrg     this(T : VariantN!(tsize, Types), size_t tsize, Types...)(T value)
564*760c2415Smrg         if (!is(T : VariantN) && Types.length > 0 && allSatisfy!(allowed, Types))
565*760c2415Smrg     {
566*760c2415Smrg         opAssign(value);
567*760c2415Smrg     }
568*760c2415Smrg 
569*760c2415Smrg     static if (!AllowedTypes.length || anySatisfy!(hasElaborateCopyConstructor, AllowedTypes))
570*760c2415Smrg     {
571*760c2415Smrg         this(this)
572*760c2415Smrg         {
573*760c2415Smrg             fptr(OpID.postblit, &store, null);
574*760c2415Smrg         }
575*760c2415Smrg     }
576*760c2415Smrg 
577*760c2415Smrg     static if (!AllowedTypes.length || anySatisfy!(hasElaborateDestructor, AllowedTypes))
578*760c2415Smrg     {
579*760c2415Smrg         ~this()
580*760c2415Smrg         {
581*760c2415Smrg             fptr(OpID.destruct, &store, null);
582*760c2415Smrg         }
583*760c2415Smrg     }
584*760c2415Smrg 
585*760c2415Smrg     /** Assigns a $(D VariantN) from a generic
586*760c2415Smrg      * argument. Statically rejects disallowed types. */
587*760c2415Smrg 
588*760c2415Smrg     VariantN opAssign(T)(T rhs)
589*760c2415Smrg     {
590*760c2415Smrg         //writeln(typeid(rhs));
591*760c2415Smrg         static assert(allowed!(T), "Cannot store a " ~ T.stringof
592*760c2415Smrg             ~ " in a " ~ VariantN.stringof ~ ". Valid types are "
593*760c2415Smrg                 ~ AllowedTypes.stringof);
594*760c2415Smrg 
595*760c2415Smrg         static if (is(T : VariantN))
596*760c2415Smrg         {
597*760c2415Smrg             rhs.fptr(OpID.copyOut, &rhs.store, &this);
598*760c2415Smrg         }
599*760c2415Smrg         else static if (is(T : const(VariantN)))
600*760c2415Smrg         {
601*760c2415Smrg             static assert(false,
602*760c2415Smrg                     "Assigning Variant objects from const Variant"~
603*760c2415Smrg                     " objects is currently not supported.");
604*760c2415Smrg         }
605*760c2415Smrg         else
606*760c2415Smrg         {
607*760c2415Smrg             static if (!AllowedTypes.length || anySatisfy!(hasElaborateDestructor, AllowedTypes))
608*760c2415Smrg             {
609*760c2415Smrg                 // Assignment should destruct previous value
610*760c2415Smrg                 fptr(OpID.destruct, &store, null);
611*760c2415Smrg             }
612*760c2415Smrg 
613*760c2415Smrg             static if (T.sizeof <= size)
614*760c2415Smrg             {
615*760c2415Smrg                 import core.stdc.string : memcpy;
616*760c2415Smrg                 // If T is a class we're only copying the reference, so it
617*760c2415Smrg                 // should be safe to cast away shared so the memcpy will work.
618*760c2415Smrg                 //
619*760c2415Smrg                 // TODO: If a shared class has an atomic reference then using
620*760c2415Smrg                 //       an atomic load may be more correct.  Just make sure
621*760c2415Smrg                 //       to use the fastest approach for the load op.
622*760c2415Smrg                 static if (is(T == class) && is(T == shared))
623*760c2415Smrg                     memcpy(&store, cast(const(void*)) &rhs, rhs.sizeof);
624*760c2415Smrg                 else
625*760c2415Smrg                     memcpy(&store, &rhs, rhs.sizeof);
626*760c2415Smrg                 static if (hasElaborateCopyConstructor!T)
627*760c2415Smrg                 {
628*760c2415Smrg                     typeid(T).postblit(&store);
629*760c2415Smrg                 }
630*760c2415Smrg             }
631*760c2415Smrg             else
632*760c2415Smrg             {
633*760c2415Smrg                 import core.stdc.string : memcpy;
634*760c2415Smrg                 static if (__traits(compiles, {new T(T.init);}))
635*760c2415Smrg                 {
636*760c2415Smrg                     auto p = new T(rhs);
637*760c2415Smrg                 }
638*760c2415Smrg                 else
639*760c2415Smrg                 {
640*760c2415Smrg                     auto p = new T;
641*760c2415Smrg                     *p = rhs;
642*760c2415Smrg                 }
643*760c2415Smrg                 memcpy(&store, &p, p.sizeof);
644*760c2415Smrg             }
645*760c2415Smrg             fptr = &handler!(T);
646*760c2415Smrg         }
647*760c2415Smrg         return this;
648*760c2415Smrg     }
649*760c2415Smrg 
650*760c2415Smrg     // Allow assignment from another variant which is a subset of this one
651*760c2415Smrg     VariantN opAssign(T : VariantN!(tsize, Types), size_t tsize, Types...)(T rhs)
652*760c2415Smrg         if (!is(T : VariantN) && Types.length > 0 && allSatisfy!(allowed, Types))
653*760c2415Smrg     {
654*760c2415Smrg         // discover which type rhs is actually storing
655*760c2415Smrg         foreach (V; T.AllowedTypes)
656*760c2415Smrg             if (rhs.type == typeid(V))
657*760c2415Smrg                 return this = rhs.get!V;
658*760c2415Smrg         assert(0, T.AllowedTypes.stringof);
659*760c2415Smrg     }
660*760c2415Smrg 
661*760c2415Smrg 
662*760c2415Smrg     Variant opCall(P...)(auto ref P params)
663*760c2415Smrg     {
664*760c2415Smrg         Variant[P.length + 1] pack;
665*760c2415Smrg         pack[0] = P.length;
666*760c2415Smrg         foreach (i, _; params)
667*760c2415Smrg         {
668*760c2415Smrg             pack[i + 1] = params[i];
669*760c2415Smrg         }
670*760c2415Smrg         fptr(OpID.apply, &store, &pack);
671*760c2415Smrg         return pack[0];
672*760c2415Smrg     }
673*760c2415Smrg 
674*760c2415Smrg     /** Returns true if and only if the $(D VariantN) object
675*760c2415Smrg      * holds a valid value (has been initialized with, or assigned
676*760c2415Smrg      * from, a valid value).
677*760c2415Smrg      */
678*760c2415Smrg     @property bool hasValue() const pure nothrow
679*760c2415Smrg     {
680*760c2415Smrg         // @@@BUG@@@ in compiler, the cast shouldn't be needed
681*760c2415Smrg         return cast(typeof(&handler!(void))) fptr != &handler!(void);
682*760c2415Smrg     }
683*760c2415Smrg 
684*760c2415Smrg     ///
685*760c2415Smrg     static if (doUnittest)
686*760c2415Smrg     @system unittest
687*760c2415Smrg     {
688*760c2415Smrg         Variant a;
689*760c2415Smrg         assert(!a.hasValue);
690*760c2415Smrg         Variant b;
691*760c2415Smrg         a = b;
692*760c2415Smrg         assert(!a.hasValue); // still no value
693*760c2415Smrg         a = 5;
694*760c2415Smrg         assert(a.hasValue);
695*760c2415Smrg     }
696*760c2415Smrg 
697*760c2415Smrg     /**
698*760c2415Smrg      * If the $(D VariantN) object holds a value of the
699*760c2415Smrg      * $(I exact) type $(D T), returns a pointer to that
700*760c2415Smrg      * value. Otherwise, returns $(D null). In cases
701*760c2415Smrg      * where $(D T) is statically disallowed, $(D
702*760c2415Smrg      * peek) will not compile.
703*760c2415Smrg      */
704*760c2415Smrg     @property inout(T)* peek(T)() inout
705*760c2415Smrg     {
706*760c2415Smrg         static if (!is(T == void))
707*760c2415Smrg             static assert(allowed!(T), "Cannot store a " ~ T.stringof
708*760c2415Smrg                     ~ " in a " ~ VariantN.stringof);
709*760c2415Smrg         if (type != typeid(T))
710*760c2415Smrg             return null;
711*760c2415Smrg         static if (T.sizeof <= size)
712*760c2415Smrg             return cast(inout T*)&store;
713*760c2415Smrg         else
714*760c2415Smrg             return *cast(inout T**)&store;
715*760c2415Smrg     }
716*760c2415Smrg 
717*760c2415Smrg     ///
718*760c2415Smrg     static if (doUnittest)
719*760c2415Smrg     @system unittest
720*760c2415Smrg     {
721*760c2415Smrg         Variant a = 5;
722*760c2415Smrg         auto b = a.peek!(int);
723*760c2415Smrg         assert(b !is null);
724*760c2415Smrg         *b = 6;
725*760c2415Smrg         assert(a == 6);
726*760c2415Smrg     }
727*760c2415Smrg 
728*760c2415Smrg     /**
729*760c2415Smrg      * Returns the $(D typeid) of the currently held value.
730*760c2415Smrg      */
731*760c2415Smrg 
732*760c2415Smrg     @property TypeInfo type() const nothrow @trusted
733*760c2415Smrg     {
734*760c2415Smrg         scope(failure) assert(0);
735*760c2415Smrg 
736*760c2415Smrg         TypeInfo result;
737*760c2415Smrg         fptr(OpID.getTypeInfo, null, &result);
738*760c2415Smrg         return result;
739*760c2415Smrg     }
740*760c2415Smrg 
741*760c2415Smrg     /**
742*760c2415Smrg      * Returns $(D true) if and only if the $(D VariantN)
743*760c2415Smrg      * object holds an object implicitly convertible to type `T`.
744*760c2415Smrg      * Implicit convertibility is defined as per
745*760c2415Smrg      * $(REF_ALTTEXT ImplicitConversionTargets, ImplicitConversionTargets, std,traits).
746*760c2415Smrg      */
747*760c2415Smrg 
748*760c2415Smrg     @property bool convertsTo(T)() const
749*760c2415Smrg     {
750*760c2415Smrg         TypeInfo info = typeid(T);
751*760c2415Smrg         return fptr(OpID.testConversion, null, &info) == 0;
752*760c2415Smrg     }
753*760c2415Smrg 
754*760c2415Smrg     /**
755*760c2415Smrg     Returns the value stored in the `VariantN` object, either by specifying the
756*760c2415Smrg     needed type or the index in the list of allowed types. The latter overload
757*760c2415Smrg     only applies to bounded variants (e.g. $(LREF Algebraic)).
758*760c2415Smrg 
759*760c2415Smrg     Params:
760*760c2415Smrg     T = The requested type. The currently stored value must implicitly convert
761*760c2415Smrg     to the requested type, in fact `DecayStaticToDynamicArray!T`. If an
762*760c2415Smrg     implicit conversion is not possible, throws a `VariantException`.
763*760c2415Smrg     index = The index of the type among `AllowedTypesParam`, zero-based.
764*760c2415Smrg      */
765*760c2415Smrg     @property inout(T) get(T)() inout
766*760c2415Smrg     {
767*760c2415Smrg         inout(T) result = void;
768*760c2415Smrg         static if (is(T == shared))
769*760c2415Smrg             alias R = shared Unqual!T;
770*760c2415Smrg         else
771*760c2415Smrg             alias R = Unqual!T;
772*760c2415Smrg         auto buf = tuple(typeid(T), cast(R*)&result);
773*760c2415Smrg 
774*760c2415Smrg         if (fptr(OpID.get, cast(ubyte[size]*) &store, &buf))
775*760c2415Smrg         {
776*760c2415Smrg             throw new VariantException(type, typeid(T));
777*760c2415Smrg         }
778*760c2415Smrg         return result;
779*760c2415Smrg     }
780*760c2415Smrg 
781*760c2415Smrg     /// Ditto
782*760c2415Smrg     @property auto get(uint index)() inout
783*760c2415Smrg     if (index < AllowedTypes.length)
784*760c2415Smrg     {
785*760c2415Smrg         foreach (i, T; AllowedTypes)
786*760c2415Smrg         {
787*760c2415Smrg             static if (index == i) return get!T;
788*760c2415Smrg         }
789*760c2415Smrg         assert(0);
790*760c2415Smrg     }
791*760c2415Smrg 
792*760c2415Smrg     /**
793*760c2415Smrg      * Returns the value stored in the $(D VariantN) object,
794*760c2415Smrg      * explicitly converted (coerced) to the requested type $(D
795*760c2415Smrg      * T). If $(D T) is a string type, the value is formatted as
796*760c2415Smrg      * a string. If the $(D VariantN) object is a string, a
797*760c2415Smrg      * parse of the string to type $(D T) is attempted. If a
798*760c2415Smrg      * conversion is not possible, throws a $(D
799*760c2415Smrg      * VariantException).
800*760c2415Smrg      */
801*760c2415Smrg 
802*760c2415Smrg     @property T coerce(T)()
803*760c2415Smrg     {
804*760c2415Smrg         import std.conv : to, text;
805*760c2415Smrg         static if (isNumeric!T || isBoolean!T)
806*760c2415Smrg         {
807*760c2415Smrg             if (convertsTo!real)
808*760c2415Smrg             {
809*760c2415Smrg                 // maybe optimize this fella; handle ints separately
810*760c2415Smrg                 return to!T(get!real);
811*760c2415Smrg             }
812*760c2415Smrg             else if (convertsTo!(const(char)[]))
813*760c2415Smrg             {
814*760c2415Smrg                 return to!T(get!(const(char)[]));
815*760c2415Smrg             }
816*760c2415Smrg             // I'm not sure why this doesn't convert to const(char),
817*760c2415Smrg             // but apparently it doesn't (probably a deeper bug).
818*760c2415Smrg             //
819*760c2415Smrg             // Until that is fixed, this quick addition keeps a common
820*760c2415Smrg             // function working. "10".coerce!int ought to work.
821*760c2415Smrg             else if (convertsTo!(immutable(char)[]))
822*760c2415Smrg             {
823*760c2415Smrg                 return to!T(get!(immutable(char)[]));
824*760c2415Smrg             }
825*760c2415Smrg             else
826*760c2415Smrg             {
827*760c2415Smrg                 import std.exception : enforce;
828*760c2415Smrg                 enforce(false, text("Type ", type, " does not convert to ",
829*760c2415Smrg                                 typeid(T)));
830*760c2415Smrg                 assert(0);
831*760c2415Smrg             }
832*760c2415Smrg         }
833*760c2415Smrg         else static if (is(T : Object))
834*760c2415Smrg         {
835*760c2415Smrg             return to!(T)(get!(Object));
836*760c2415Smrg         }
837*760c2415Smrg         else static if (isSomeString!(T))
838*760c2415Smrg         {
839*760c2415Smrg             return to!(T)(toString());
840*760c2415Smrg         }
841*760c2415Smrg         else
842*760c2415Smrg         {
843*760c2415Smrg             // Fix for bug 1649
844*760c2415Smrg             static assert(false, "unsupported type for coercion");
845*760c2415Smrg         }
846*760c2415Smrg     }
847*760c2415Smrg 
848*760c2415Smrg     /**
849*760c2415Smrg      * Formats the stored value as a string.
850*760c2415Smrg      */
851*760c2415Smrg 
852*760c2415Smrg     string toString()
853*760c2415Smrg     {
854*760c2415Smrg         string result;
855*760c2415Smrg         fptr(OpID.toString, &store, &result) == 0 || assert(false);
856*760c2415Smrg         return result;
857*760c2415Smrg     }
858*760c2415Smrg 
859*760c2415Smrg     /**
860*760c2415Smrg      * Comparison for equality used by the "==" and "!="  operators.
861*760c2415Smrg      */
862*760c2415Smrg 
863*760c2415Smrg     // returns 1 if the two are equal
864*760c2415Smrg     bool opEquals(T)(auto ref T rhs) const
865*760c2415Smrg     if (allowed!T || is(Unqual!T == VariantN))
866*760c2415Smrg     {
867*760c2415Smrg         static if (is(Unqual!T == VariantN))
868*760c2415Smrg             alias temp = rhs;
869*760c2415Smrg         else
870*760c2415Smrg             auto temp = VariantN(rhs);
871*760c2415Smrg         return !fptr(OpID.equals, cast(ubyte[size]*) &store,
872*760c2415Smrg                      cast(void*) &temp);
873*760c2415Smrg     }
874*760c2415Smrg 
875*760c2415Smrg     // workaround for bug 10567 fix
876*760c2415Smrg     int opCmp(ref const VariantN rhs) const
877*760c2415Smrg     {
878*760c2415Smrg         return (cast() this).opCmp!(VariantN)(cast() rhs);
879*760c2415Smrg     }
880*760c2415Smrg 
881*760c2415Smrg     /**
882*760c2415Smrg      * Ordering comparison used by the "<", "<=", ">", and ">="
883*760c2415Smrg      * operators. In case comparison is not sensible between the held
884*760c2415Smrg      * value and $(D rhs), an exception is thrown.
885*760c2415Smrg      */
886*760c2415Smrg 
887*760c2415Smrg     int opCmp(T)(T rhs)
888*760c2415Smrg     if (allowed!T)  // includes T == VariantN
889*760c2415Smrg     {
890*760c2415Smrg         static if (is(T == VariantN))
891*760c2415Smrg             alias temp = rhs;
892*760c2415Smrg         else
893*760c2415Smrg             auto temp = VariantN(rhs);
894*760c2415Smrg         auto result = fptr(OpID.compare, &store, &temp);
895*760c2415Smrg         if (result == ptrdiff_t.min)
896*760c2415Smrg         {
897*760c2415Smrg             throw new VariantException(type, temp.type);
898*760c2415Smrg         }
899*760c2415Smrg 
900*760c2415Smrg         assert(result >= -1 && result <= 1);  // Should be true for opCmp.
901*760c2415Smrg         return cast(int) result;
902*760c2415Smrg     }
903*760c2415Smrg 
904*760c2415Smrg     /**
905*760c2415Smrg      * Computes the hash of the held value.
906*760c2415Smrg      */
907*760c2415Smrg 
908*760c2415Smrg     size_t toHash() const nothrow @safe
909*760c2415Smrg     {
910*760c2415Smrg         return type.getHash(&store);
911*760c2415Smrg     }
912*760c2415Smrg 
913*760c2415Smrg     private VariantN opArithmetic(T, string op)(T other)
914*760c2415Smrg     {
915*760c2415Smrg         static if (isInstanceOf!(.VariantN, T))
916*760c2415Smrg         {
917*760c2415Smrg             string tryUseType(string tp)
918*760c2415Smrg             {
919*760c2415Smrg                 import std.format : format;
920*760c2415Smrg                 return q{
921*760c2415Smrg                     static if (allowed!%1$s && T.allowed!%1$s)
922*760c2415Smrg                         if (convertsTo!%1$s && other.convertsTo!%1$s)
923*760c2415Smrg                             return VariantN(get!%1$s %2$s other.get!%1$s);
924*760c2415Smrg                 }.format(tp, op);
925*760c2415Smrg             }
926*760c2415Smrg 
927*760c2415Smrg             mixin(tryUseType("uint"));
928*760c2415Smrg             mixin(tryUseType("int"));
929*760c2415Smrg             mixin(tryUseType("ulong"));
930*760c2415Smrg             mixin(tryUseType("long"));
931*760c2415Smrg             mixin(tryUseType("float"));
932*760c2415Smrg             mixin(tryUseType("double"));
933*760c2415Smrg             mixin(tryUseType("real"));
934*760c2415Smrg         }
935*760c2415Smrg         else
936*760c2415Smrg         {
937*760c2415Smrg             static if (allowed!T)
938*760c2415Smrg                 if (auto pv = peek!T) return VariantN(mixin("*pv " ~ op ~ " other"));
939*760c2415Smrg             static if (allowed!uint && is(typeof(T.max) : uint) && isUnsigned!T)
940*760c2415Smrg                 if (convertsTo!uint) return VariantN(mixin("get!(uint) " ~ op ~ " other"));
941*760c2415Smrg             static if (allowed!int && is(typeof(T.max) : int) && !isUnsigned!T)
942*760c2415Smrg                 if (convertsTo!int) return VariantN(mixin("get!(int) " ~ op ~ " other"));
943*760c2415Smrg             static if (allowed!ulong && is(typeof(T.max) : ulong) && isUnsigned!T)
944*760c2415Smrg                 if (convertsTo!ulong) return VariantN(mixin("get!(ulong) " ~ op ~ " other"));
945*760c2415Smrg             static if (allowed!long && is(typeof(T.max) : long) && !isUnsigned!T)
946*760c2415Smrg                 if (convertsTo!long) return VariantN(mixin("get!(long) " ~ op ~ " other"));
947*760c2415Smrg             static if (allowed!float && is(T : float))
948*760c2415Smrg                 if (convertsTo!float) return VariantN(mixin("get!(float) " ~ op ~ " other"));
949*760c2415Smrg             static if (allowed!double && is(T : double))
950*760c2415Smrg                 if (convertsTo!double) return VariantN(mixin("get!(double) " ~ op ~ " other"));
951*760c2415Smrg             static if (allowed!real && is (T : real))
952*760c2415Smrg                 if (convertsTo!real) return VariantN(mixin("get!(real) " ~ op ~ " other"));
953*760c2415Smrg         }
954*760c2415Smrg 
955*760c2415Smrg         throw new VariantException("No possible match found for VariantN "~op~" "~T.stringof);
956*760c2415Smrg     }
957*760c2415Smrg 
958*760c2415Smrg     private VariantN opLogic(T, string op)(T other)
959*760c2415Smrg     {
960*760c2415Smrg         VariantN result;
961*760c2415Smrg         static if (is(T == VariantN))
962*760c2415Smrg         {
963*760c2415Smrg             if (convertsTo!(uint) && other.convertsTo!(uint))
964*760c2415Smrg                 result = mixin("get!(uint) " ~ op ~ " other.get!(uint)");
965*760c2415Smrg             else if (convertsTo!(int) && other.convertsTo!(int))
966*760c2415Smrg                 result = mixin("get!(int) " ~ op ~ " other.get!(int)");
967*760c2415Smrg             else if (convertsTo!(ulong) && other.convertsTo!(ulong))
968*760c2415Smrg                 result = mixin("get!(ulong) " ~ op ~ " other.get!(ulong)");
969*760c2415Smrg             else
970*760c2415Smrg                 result = mixin("get!(long) " ~ op ~ " other.get!(long)");
971*760c2415Smrg         }
972*760c2415Smrg         else
973*760c2415Smrg         {
974*760c2415Smrg             if (is(typeof(T.max) : uint) && T.min == 0 && convertsTo!(uint))
975*760c2415Smrg                 result = mixin("get!(uint) " ~ op ~ " other");
976*760c2415Smrg             else if (is(typeof(T.max) : int) && T.min < 0 && convertsTo!(int))
977*760c2415Smrg                 result = mixin("get!(int) " ~ op ~ " other");
978*760c2415Smrg             else if (is(typeof(T.max) : ulong) && T.min == 0
979*760c2415Smrg                      && convertsTo!(ulong))
980*760c2415Smrg                 result = mixin("get!(ulong) " ~ op ~ " other");
981*760c2415Smrg             else
982*760c2415Smrg                 result = mixin("get!(long) " ~ op ~ " other");
983*760c2415Smrg         }
984*760c2415Smrg         return result;
985*760c2415Smrg     }
986*760c2415Smrg 
987*760c2415Smrg     /**
988*760c2415Smrg      * Arithmetic between $(D VariantN) objects and numeric
989*760c2415Smrg      * values. All arithmetic operations return a $(D VariantN)
990*760c2415Smrg      * object typed depending on the types of both values
991*760c2415Smrg      * involved. The conversion rules mimic D's built-in rules for
992*760c2415Smrg      * arithmetic conversions.
993*760c2415Smrg      */
994*760c2415Smrg 
995*760c2415Smrg     // Adapted from http://www.prowiki.org/wiki4d/wiki.cgi?DanielKeep/Variant
996*760c2415Smrg     // arithmetic
997*760c2415Smrg     VariantN opAdd(T)(T rhs) { return opArithmetic!(T, "+")(rhs); }
998*760c2415Smrg     ///ditto
999*760c2415Smrg     VariantN opSub(T)(T rhs) { return opArithmetic!(T, "-")(rhs); }
1000*760c2415Smrg 
1001*760c2415Smrg     // Commenteed all _r versions for now because of ambiguities
1002*760c2415Smrg     // arising when two Variants are used
1003*760c2415Smrg 
1004*760c2415Smrg     // ///ditto
1005*760c2415Smrg     // VariantN opSub_r(T)(T lhs)
1006*760c2415Smrg     // {
1007*760c2415Smrg     //     return VariantN(lhs).opArithmetic!(VariantN, "-")(this);
1008*760c2415Smrg     // }
1009*760c2415Smrg     ///ditto
1010*760c2415Smrg     VariantN opMul(T)(T rhs) { return opArithmetic!(T, "*")(rhs); }
1011*760c2415Smrg     ///ditto
1012*760c2415Smrg     VariantN opDiv(T)(T rhs) { return opArithmetic!(T, "/")(rhs); }
1013*760c2415Smrg     // ///ditto
1014*760c2415Smrg     // VariantN opDiv_r(T)(T lhs)
1015*760c2415Smrg     // {
1016*760c2415Smrg     //     return VariantN(lhs).opArithmetic!(VariantN, "/")(this);
1017*760c2415Smrg     // }
1018*760c2415Smrg     ///ditto
1019*760c2415Smrg     VariantN opMod(T)(T rhs) { return opArithmetic!(T, "%")(rhs); }
1020*760c2415Smrg     // ///ditto
1021*760c2415Smrg     // VariantN opMod_r(T)(T lhs)
1022*760c2415Smrg     // {
1023*760c2415Smrg     //     return VariantN(lhs).opArithmetic!(VariantN, "%")(this);
1024*760c2415Smrg     // }
1025*760c2415Smrg     ///ditto
1026*760c2415Smrg     VariantN opAnd(T)(T rhs) { return opLogic!(T, "&")(rhs); }
1027*760c2415Smrg     ///ditto
1028*760c2415Smrg     VariantN opOr(T)(T rhs) { return opLogic!(T, "|")(rhs); }
1029*760c2415Smrg     ///ditto
1030*760c2415Smrg     VariantN opXor(T)(T rhs) { return opLogic!(T, "^")(rhs); }
1031*760c2415Smrg     ///ditto
1032*760c2415Smrg     VariantN opShl(T)(T rhs) { return opLogic!(T, "<<")(rhs); }
1033*760c2415Smrg     // ///ditto
1034*760c2415Smrg     // VariantN opShl_r(T)(T lhs)
1035*760c2415Smrg     // {
1036*760c2415Smrg     //     return VariantN(lhs).opLogic!(VariantN, "<<")(this);
1037*760c2415Smrg     // }
1038*760c2415Smrg     ///ditto
1039*760c2415Smrg     VariantN opShr(T)(T rhs) { return opLogic!(T, ">>")(rhs); }
1040*760c2415Smrg     // ///ditto
1041*760c2415Smrg     // VariantN opShr_r(T)(T lhs)
1042*760c2415Smrg     // {
1043*760c2415Smrg     //     return VariantN(lhs).opLogic!(VariantN, ">>")(this);
1044*760c2415Smrg     // }
1045*760c2415Smrg     ///ditto
1046*760c2415Smrg     VariantN opUShr(T)(T rhs) { return opLogic!(T, ">>>")(rhs); }
1047*760c2415Smrg     // ///ditto
1048*760c2415Smrg     // VariantN opUShr_r(T)(T lhs)
1049*760c2415Smrg     // {
1050*760c2415Smrg     //     return VariantN(lhs).opLogic!(VariantN, ">>>")(this);
1051*760c2415Smrg     // }
1052*760c2415Smrg     ///ditto
1053*760c2415Smrg     VariantN opCat(T)(T rhs)
1054*760c2415Smrg     {
1055*760c2415Smrg         auto temp = this;
1056*760c2415Smrg         temp ~= rhs;
1057*760c2415Smrg         return temp;
1058*760c2415Smrg     }
1059*760c2415Smrg     // ///ditto
1060*760c2415Smrg     // VariantN opCat_r(T)(T rhs)
1061*760c2415Smrg     // {
1062*760c2415Smrg     //     VariantN temp = rhs;
1063*760c2415Smrg     //     temp ~= this;
1064*760c2415Smrg     //     return temp;
1065*760c2415Smrg     // }
1066*760c2415Smrg 
1067*760c2415Smrg     ///ditto
1068*760c2415Smrg     VariantN opAddAssign(T)(T rhs)  { return this = this + rhs; }
1069*760c2415Smrg     ///ditto
1070*760c2415Smrg     VariantN opSubAssign(T)(T rhs)  { return this = this - rhs; }
1071*760c2415Smrg     ///ditto
1072*760c2415Smrg     VariantN opMulAssign(T)(T rhs)  { return this = this * rhs; }
1073*760c2415Smrg     ///ditto
1074*760c2415Smrg     VariantN opDivAssign(T)(T rhs)  { return this = this / rhs; }
1075*760c2415Smrg     ///ditto
1076*760c2415Smrg     VariantN opModAssign(T)(T rhs)  { return this = this % rhs; }
1077*760c2415Smrg     ///ditto
1078*760c2415Smrg     VariantN opAndAssign(T)(T rhs)  { return this = this & rhs; }
1079*760c2415Smrg     ///ditto
1080*760c2415Smrg     VariantN opOrAssign(T)(T rhs)   { return this = this | rhs; }
1081*760c2415Smrg     ///ditto
1082*760c2415Smrg     VariantN opXorAssign(T)(T rhs)  { return this = this ^ rhs; }
1083*760c2415Smrg     ///ditto
1084*760c2415Smrg     VariantN opShlAssign(T)(T rhs)  { return this = this << rhs; }
1085*760c2415Smrg     ///ditto
1086*760c2415Smrg     VariantN opShrAssign(T)(T rhs)  { return this = this >> rhs; }
1087*760c2415Smrg     ///ditto
1088*760c2415Smrg     VariantN opUShrAssign(T)(T rhs) { return this = this >>> rhs; }
1089*760c2415Smrg     ///ditto
1090*760c2415Smrg     VariantN opCatAssign(T)(T rhs)
1091*760c2415Smrg     {
1092*760c2415Smrg         auto toAppend = Variant(rhs);
1093*760c2415Smrg         fptr(OpID.catAssign, &store, &toAppend) == 0 || assert(false);
1094*760c2415Smrg         return this;
1095*760c2415Smrg     }
1096*760c2415Smrg 
1097*760c2415Smrg     /**
1098*760c2415Smrg      * Array and associative array operations. If a $(D
1099*760c2415Smrg      * VariantN) contains an (associative) array, it can be indexed
1100*760c2415Smrg      * into. Otherwise, an exception is thrown.
1101*760c2415Smrg      */
1102*760c2415Smrg     inout(Variant) opIndex(K)(K i) inout
1103*760c2415Smrg     {
1104*760c2415Smrg         auto result = Variant(i);
1105*760c2415Smrg         fptr(OpID.index, cast(ubyte[size]*) &store, &result) == 0 || assert(false);
1106*760c2415Smrg         return result;
1107*760c2415Smrg     }
1108*760c2415Smrg 
1109*760c2415Smrg     ///
1110*760c2415Smrg     static if (doUnittest)
1111*760c2415Smrg     @system unittest
1112*760c2415Smrg     {
1113*760c2415Smrg         Variant a = new int[10];
1114*760c2415Smrg         a[5] = 42;
1115*760c2415Smrg         assert(a[5] == 42);
1116*760c2415Smrg         a[5] += 8;
1117*760c2415Smrg         assert(a[5] == 50);
1118*760c2415Smrg 
1119*760c2415Smrg         int[int] hash = [ 42:24 ];
1120*760c2415Smrg         a = hash;
1121*760c2415Smrg         assert(a[42] == 24);
1122*760c2415Smrg         a[42] /= 2;
1123*760c2415Smrg         assert(a[42] == 12);
1124*760c2415Smrg     }
1125*760c2415Smrg 
1126*760c2415Smrg     /// ditto
1127*760c2415Smrg     Variant opIndexAssign(T, N)(T value, N i)
1128*760c2415Smrg     {
1129*760c2415Smrg         static if (AllowedTypes.length && !isInstanceOf!(.VariantN, T))
1130*760c2415Smrg         {
1131*760c2415Smrg             enum canAssign(U) = __traits(compiles, (U u){ u[i] = value; });
1132*760c2415Smrg             static assert(anySatisfy!(canAssign, AllowedTypes),
1133*760c2415Smrg                 "Cannot assign " ~ T.stringof ~ " to " ~ VariantN.stringof ~
1134*760c2415Smrg                 " indexed with " ~ N.stringof);
1135*760c2415Smrg         }
1136*760c2415Smrg         Variant[2] args = [ Variant(value), Variant(i) ];
1137*760c2415Smrg         fptr(OpID.indexAssign, &store, &args) == 0 || assert(false);
1138*760c2415Smrg         return args[0];
1139*760c2415Smrg     }
1140*760c2415Smrg 
1141*760c2415Smrg     /// ditto
1142*760c2415Smrg     Variant opIndexOpAssign(string op, T, N)(T value, N i)
1143*760c2415Smrg     {
1144*760c2415Smrg         return opIndexAssign(mixin(`opIndex(i)` ~ op ~ `value`), i);
1145*760c2415Smrg     }
1146*760c2415Smrg 
1147*760c2415Smrg     /** If the $(D VariantN) contains an (associative) array,
1148*760c2415Smrg      * returns the _length of that array. Otherwise, throws an
1149*760c2415Smrg      * exception.
1150*760c2415Smrg      */
1151*760c2415Smrg     @property size_t length()
1152*760c2415Smrg     {
1153*760c2415Smrg         return cast(size_t) fptr(OpID.length, &store, null);
1154*760c2415Smrg     }
1155*760c2415Smrg 
1156*760c2415Smrg     /**
1157*760c2415Smrg        If the $(D VariantN) contains an array, applies $(D dg) to each
1158*760c2415Smrg        element of the array in turn. Otherwise, throws an exception.
1159*760c2415Smrg      */
1160*760c2415Smrg     int opApply(Delegate)(scope Delegate dg) if (is(Delegate == delegate))
1161*760c2415Smrg     {
1162*760c2415Smrg         alias A = Parameters!(Delegate)[0];
1163*760c2415Smrg         if (type == typeid(A[]))
1164*760c2415Smrg         {
1165*760c2415Smrg             auto arr = get!(A[]);
1166*760c2415Smrg             foreach (ref e; arr)
1167*760c2415Smrg             {
1168*760c2415Smrg                 if (dg(e)) return 1;
1169*760c2415Smrg             }
1170*760c2415Smrg         }
1171*760c2415Smrg         else static if (is(A == VariantN))
1172*760c2415Smrg         {
1173*760c2415Smrg             foreach (i; 0 .. length)
1174*760c2415Smrg             {
1175*760c2415Smrg                 // @@@TODO@@@: find a better way to not confuse
1176*760c2415Smrg                 // clients who think they change values stored in the
1177*760c2415Smrg                 // Variant when in fact they are only changing tmp.
1178*760c2415Smrg                 auto tmp = this[i];
1179*760c2415Smrg                 debug scope(exit) assert(tmp == this[i]);
1180*760c2415Smrg                 if (dg(tmp)) return 1;
1181*760c2415Smrg             }
1182*760c2415Smrg         }
1183*760c2415Smrg         else
1184*760c2415Smrg         {
1185*760c2415Smrg             import std.conv : text;
1186*760c2415Smrg             import std.exception : enforce;
1187*760c2415Smrg             enforce(false, text("Variant type ", type,
1188*760c2415Smrg                             " not iterable with values of type ",
1189*760c2415Smrg                             A.stringof));
1190*760c2415Smrg         }
1191*760c2415Smrg         return 0;
1192*760c2415Smrg     }
1193*760c2415Smrg }
1194*760c2415Smrg 
1195*760c2415Smrg @system unittest
1196*760c2415Smrg {
1197*760c2415Smrg     import std.conv : to;
1198*760c2415Smrg     Variant v;
foo()1199*760c2415Smrg     int foo() { return 42; }
1200*760c2415Smrg     v = &foo;
1201*760c2415Smrg     assert(v() == 42);
1202*760c2415Smrg 
bar(string s)1203*760c2415Smrg     static int bar(string s) { return to!int(s); }
1204*760c2415Smrg     v = &bar;
1205*760c2415Smrg     assert(v("43") == 43);
1206*760c2415Smrg }
1207*760c2415Smrg 
1208*760c2415Smrg @system unittest
1209*760c2415Smrg {
1210*760c2415Smrg     int[int] hash = [ 42:24 ];
1211*760c2415Smrg     Variant v = hash;
1212*760c2415Smrg     assert(v[42] == 24);
1213*760c2415Smrg     v[42] = 5;
1214*760c2415Smrg     assert(v[42] == 5);
1215*760c2415Smrg }
1216*760c2415Smrg 
1217*760c2415Smrg // opIndex with static arrays, issue 12771
1218*760c2415Smrg @system unittest
1219*760c2415Smrg {
1220*760c2415Smrg     int[4] elements = [0, 1, 2, 3];
1221*760c2415Smrg     Variant v = elements;
1222*760c2415Smrg     assert(v == elements);
1223*760c2415Smrg     assert(v[2] == 2);
1224*760c2415Smrg     assert(v[3] == 3);
1225*760c2415Smrg     v[2] = 6;
1226*760c2415Smrg     assert(v[2] == 6);
1227*760c2415Smrg     assert(v != elements);
1228*760c2415Smrg }
1229*760c2415Smrg 
1230*760c2415Smrg @system unittest
1231*760c2415Smrg {
1232*760c2415Smrg     import std.exception : assertThrown;
1233*760c2415Smrg     Algebraic!(int[]) v = [2, 2];
1234*760c2415Smrg 
1235*760c2415Smrg     assert(v == [2, 2]);
1236*760c2415Smrg     v[0] = 1;
1237*760c2415Smrg     assert(v[0] == 1);
1238*760c2415Smrg     assert(v != [2, 2]);
1239*760c2415Smrg 
1240*760c2415Smrg     // opIndexAssign from Variant
1241*760c2415Smrg     v[1] = v[0];
1242*760c2415Smrg     assert(v[1] == 1);
1243*760c2415Smrg 
1244*760c2415Smrg     static assert(!__traits(compiles, (v[1] = null)));
1245*760c2415Smrg     assertThrown!VariantException(v[1] = Variant(null));
1246*760c2415Smrg }
1247*760c2415Smrg 
1248*760c2415Smrg //Issue# 8195
1249*760c2415Smrg @system unittest
1250*760c2415Smrg {
1251*760c2415Smrg     struct S
1252*760c2415Smrg     {
1253*760c2415Smrg         int a;
1254*760c2415Smrg         long b;
1255*760c2415Smrg         string c;
1256*760c2415Smrg         real d = 0.0;
1257*760c2415Smrg         bool e;
1258*760c2415Smrg     }
1259*760c2415Smrg 
1260*760c2415Smrg     static assert(S.sizeof >= Variant.sizeof);
1261*760c2415Smrg     alias Types = AliasSeq!(string, int, S);
1262*760c2415Smrg     alias MyVariant = VariantN!(maxSize!Types, Types);
1263*760c2415Smrg 
1264*760c2415Smrg     auto v = MyVariant(S.init);
1265*760c2415Smrg     assert(v == S.init);
1266*760c2415Smrg }
1267*760c2415Smrg 
1268*760c2415Smrg // Issue #10961
1269*760c2415Smrg @system unittest
1270*760c2415Smrg {
1271*760c2415Smrg     // Primarily test that we can assign a void[] to a Variant.
1272*760c2415Smrg     void[] elements = cast(void[])[1, 2, 3];
1273*760c2415Smrg     Variant v = elements;
1274*760c2415Smrg     void[] returned = v.get!(void[]);
1275*760c2415Smrg     assert(returned == elements);
1276*760c2415Smrg }
1277*760c2415Smrg 
1278*760c2415Smrg // Issue #13352
1279*760c2415Smrg @system unittest
1280*760c2415Smrg {
1281*760c2415Smrg     alias TP = Algebraic!(long);
1282*760c2415Smrg     auto a = TP(1L);
1283*760c2415Smrg     auto b = TP(2L);
1284*760c2415Smrg     assert(!TP.allowed!ulong);
1285*760c2415Smrg     assert(a + b == 3L);
1286*760c2415Smrg     assert(a + 2 == 3L);
1287*760c2415Smrg     assert(1 + b == 3L);
1288*760c2415Smrg 
1289*760c2415Smrg     alias TP2 = Algebraic!(long, string);
1290*760c2415Smrg     auto c = TP2(3L);
1291*760c2415Smrg     assert(a + c == 4L);
1292*760c2415Smrg }
1293*760c2415Smrg 
1294*760c2415Smrg // Issue #13354
1295*760c2415Smrg @system unittest
1296*760c2415Smrg {
1297*760c2415Smrg     alias A = Algebraic!(string[]);
1298*760c2415Smrg     A a = ["a", "b"];
1299*760c2415Smrg     assert(a[0] == "a");
1300*760c2415Smrg     assert(a[1] == "b");
1301*760c2415Smrg     a[1] = "c";
1302*760c2415Smrg     assert(a[1] == "c");
1303*760c2415Smrg 
1304*760c2415Smrg     alias AA = Algebraic!(int[string]);
1305*760c2415Smrg     AA aa = ["a": 1, "b": 2];
1306*760c2415Smrg     assert(aa["a"] == 1);
1307*760c2415Smrg     assert(aa["b"] == 2);
1308*760c2415Smrg     aa["b"] = 3;
1309*760c2415Smrg     assert(aa["b"] == 3);
1310*760c2415Smrg }
1311*760c2415Smrg 
1312*760c2415Smrg // Issue #14198
1313*760c2415Smrg @system unittest
1314*760c2415Smrg {
1315*760c2415Smrg     Variant a = true;
1316*760c2415Smrg     assert(a.type == typeid(bool));
1317*760c2415Smrg }
1318*760c2415Smrg 
1319*760c2415Smrg // Issue #14233
1320*760c2415Smrg @system unittest
1321*760c2415Smrg {
1322*760c2415Smrg     alias Atom = Algebraic!(string, This[]);
1323*760c2415Smrg 
1324*760c2415Smrg     Atom[] values = [];
1325*760c2415Smrg     auto a = Atom(values);
1326*760c2415Smrg }
1327*760c2415Smrg 
1328*760c2415Smrg pure nothrow @nogc
1329*760c2415Smrg @system unittest
1330*760c2415Smrg {
1331*760c2415Smrg     Algebraic!(int, double) a;
1332*760c2415Smrg     a = 100;
1333*760c2415Smrg     a = 1.0;
1334*760c2415Smrg }
1335*760c2415Smrg 
1336*760c2415Smrg // Issue 14457
1337*760c2415Smrg @system unittest
1338*760c2415Smrg {
1339*760c2415Smrg     alias A = Algebraic!(int, float, double);
1340*760c2415Smrg     alias B = Algebraic!(int, float);
1341*760c2415Smrg 
1342*760c2415Smrg     A a = 1;
1343*760c2415Smrg     B b = 6f;
1344*760c2415Smrg     a = b;
1345*760c2415Smrg 
1346*760c2415Smrg     assert(a.type == typeid(float));
1347*760c2415Smrg     assert(a.get!float == 6f);
1348*760c2415Smrg }
1349*760c2415Smrg 
1350*760c2415Smrg // Issue 14585
1351*760c2415Smrg @system unittest
1352*760c2415Smrg {
1353*760c2415Smrg     static struct S
1354*760c2415Smrg     {
1355*760c2415Smrg         int x = 42;
~thisS1356*760c2415Smrg         ~this() {assert(x == 42);}
1357*760c2415Smrg     }
1358*760c2415Smrg     Variant(S()).get!S;
1359*760c2415Smrg }
1360*760c2415Smrg 
1361*760c2415Smrg // Issue 14586
1362*760c2415Smrg @system unittest
1363*760c2415Smrg {
1364*760c2415Smrg     const Variant v = new immutable Object;
1365*760c2415Smrg     v.get!(immutable Object);
1366*760c2415Smrg }
1367*760c2415Smrg 
1368*760c2415Smrg @system unittest
1369*760c2415Smrg {
1370*760c2415Smrg     static struct S
1371*760c2415Smrg     {
opCastS1372*760c2415Smrg         T opCast(T)() {assert(false);}
1373*760c2415Smrg     }
1374*760c2415Smrg     Variant v = S();
1375*760c2415Smrg     v.get!S;
1376*760c2415Smrg }
1377*760c2415Smrg 
1378*760c2415Smrg 
1379*760c2415Smrg /**
1380*760c2415Smrg _Algebraic data type restricted to a closed set of possible
1381*760c2415Smrg types. It's an alias for $(LREF VariantN) with an
1382*760c2415Smrg appropriately-constructed maximum size. `Algebraic` is
1383*760c2415Smrg useful when it is desirable to restrict what a discriminated type
1384*760c2415Smrg could hold to the end of defining simpler and more efficient
1385*760c2415Smrg manipulation.
1386*760c2415Smrg 
1387*760c2415Smrg */
Algebraic(T...)1388*760c2415Smrg template Algebraic(T...)
1389*760c2415Smrg {
1390*760c2415Smrg     alias Algebraic = VariantN!(maxSize!T, T);
1391*760c2415Smrg }
1392*760c2415Smrg 
1393*760c2415Smrg ///
1394*760c2415Smrg @system unittest
1395*760c2415Smrg {
1396*760c2415Smrg     auto v = Algebraic!(int, double, string)(5);
1397*760c2415Smrg     assert(v.peek!(int));
1398*760c2415Smrg     v = 3.14;
1399*760c2415Smrg     assert(v.peek!(double));
1400*760c2415Smrg     // auto x = v.peek!(long); // won't compile, type long not allowed
1401*760c2415Smrg     // v = '1'; // won't compile, type char not allowed
1402*760c2415Smrg }
1403*760c2415Smrg 
1404*760c2415Smrg /**
1405*760c2415Smrg $(H4 Self-Referential Types)
1406*760c2415Smrg 
1407*760c2415Smrg A useful and popular use of algebraic data structures is for defining $(LUCKY
1408*760c2415Smrg self-referential data structures), i.e. structures that embed references to
1409*760c2415Smrg values of their own type within.
1410*760c2415Smrg 
1411*760c2415Smrg This is achieved with `Algebraic` by using `This` as a placeholder whenever a
1412*760c2415Smrg reference to the type being defined is needed. The `Algebraic` instantiation
1413*760c2415Smrg will perform $(LINK2 https://en.wikipedia.org/wiki/Name_resolution_(programming_languages)#Alpha_renaming_to_make_name_resolution_trivial,
1414*760c2415Smrg alpha renaming) on its constituent types, replacing `This`
1415*760c2415Smrg with the self-referenced type. The structure of the type involving `This` may
1416*760c2415Smrg be arbitrarily complex.
1417*760c2415Smrg */
1418*760c2415Smrg @system unittest
1419*760c2415Smrg {
1420*760c2415Smrg     import std.typecons : Tuple, tuple;
1421*760c2415Smrg 
1422*760c2415Smrg     // A tree is either a leaf or a branch of two other trees
1423*760c2415Smrg     alias Tree(Leaf) = Algebraic!(Leaf, Tuple!(This*, This*));
1424*760c2415Smrg     Tree!int tree = tuple(new Tree!int(42), new Tree!int(43));
1425*760c2415Smrg     Tree!int* right = tree.get!1[1];
1426*760c2415Smrg     assert(*right == 43);
1427*760c2415Smrg 
1428*760c2415Smrg     // An object is a double, a string, or a hash of objects
1429*760c2415Smrg     alias Obj = Algebraic!(double, string, This[string]);
1430*760c2415Smrg     Obj obj = "hello";
1431*760c2415Smrg     assert(obj.get!1 == "hello");
1432*760c2415Smrg     obj = 42.0;
1433*760c2415Smrg     assert(obj.get!0 == 42);
1434*760c2415Smrg     obj = ["customer": Obj("John"), "paid": Obj(23.95)];
1435*760c2415Smrg     assert(obj.get!2["customer"] == "John");
1436*760c2415Smrg }
1437*760c2415Smrg 
1438*760c2415Smrg /**
1439*760c2415Smrg Alias for $(LREF VariantN) instantiated with the largest size of `creal`,
1440*760c2415Smrg `char[]`, and `void delegate()`. This ensures that `Variant` is large enough
1441*760c2415Smrg to hold all of D's predefined types unboxed, including all numeric types,
1442*760c2415Smrg pointers, delegates, and class references.  You may want to use
1443*760c2415Smrg $(D VariantN) directly with a different maximum size either for
1444*760c2415Smrg storing larger types unboxed, or for saving memory.
1445*760c2415Smrg  */
1446*760c2415Smrg alias Variant = VariantN!(maxSize!(creal, char[], void delegate()));
1447*760c2415Smrg 
1448*760c2415Smrg /**
1449*760c2415Smrg  * Returns an array of variants constructed from $(D args).
1450*760c2415Smrg  *
1451*760c2415Smrg  * This is by design. During construction the $(D Variant) needs
1452*760c2415Smrg  * static type information about the type being held, so as to store a
1453*760c2415Smrg  * pointer to function for fast retrieval.
1454*760c2415Smrg  */
variantArray(T...)1455*760c2415Smrg Variant[] variantArray(T...)(T args)
1456*760c2415Smrg {
1457*760c2415Smrg     Variant[] result;
1458*760c2415Smrg     foreach (arg; args)
1459*760c2415Smrg     {
1460*760c2415Smrg         result ~= Variant(arg);
1461*760c2415Smrg     }
1462*760c2415Smrg     return result;
1463*760c2415Smrg }
1464*760c2415Smrg 
1465*760c2415Smrg ///
1466*760c2415Smrg @system unittest
1467*760c2415Smrg {
1468*760c2415Smrg     auto a = variantArray(1, 3.14, "Hi!");
1469*760c2415Smrg     assert(a[1] == 3.14);
1470*760c2415Smrg     auto b = Variant(a); // variant array as variant
1471*760c2415Smrg     assert(b[1] == 3.14);
1472*760c2415Smrg }
1473*760c2415Smrg 
1474*760c2415Smrg /**
1475*760c2415Smrg  * Thrown in three cases:
1476*760c2415Smrg  *
1477*760c2415Smrg  * $(OL $(LI An uninitialized `Variant` is used in any way except
1478*760c2415Smrg  * assignment and $(D hasValue);) $(LI A $(D get) or
1479*760c2415Smrg  * $(D coerce) is attempted with an incompatible target type;)
1480*760c2415Smrg  * $(LI A comparison between $(D Variant) objects of
1481*760c2415Smrg  * incompatible types is attempted.))
1482*760c2415Smrg  *
1483*760c2415Smrg  */
1484*760c2415Smrg 
1485*760c2415Smrg // @@@ BUG IN COMPILER. THE 'STATIC' BELOW SHOULD NOT COMPILE
1486*760c2415Smrg static class VariantException : Exception
1487*760c2415Smrg {
1488*760c2415Smrg     /// The source type in the conversion or comparison
1489*760c2415Smrg     TypeInfo source;
1490*760c2415Smrg     /// The target type in the conversion or comparison
1491*760c2415Smrg     TypeInfo target;
this(string s)1492*760c2415Smrg     this(string s)
1493*760c2415Smrg     {
1494*760c2415Smrg         super(s);
1495*760c2415Smrg     }
this(TypeInfo source,TypeInfo target)1496*760c2415Smrg     this(TypeInfo source, TypeInfo target)
1497*760c2415Smrg     {
1498*760c2415Smrg         super("Variant: attempting to use incompatible types "
1499*760c2415Smrg                             ~ source.toString()
1500*760c2415Smrg                             ~ " and " ~ target.toString());
1501*760c2415Smrg         this.source = source;
1502*760c2415Smrg         this.target = target;
1503*760c2415Smrg     }
1504*760c2415Smrg }
1505*760c2415Smrg 
1506*760c2415Smrg @system unittest
1507*760c2415Smrg {
1508*760c2415Smrg     alias W1 = This2Variant!(char, int, This[int]);
1509*760c2415Smrg     alias W2 = AliasSeq!(int, char[int]);
1510*760c2415Smrg     static assert(is(W1 == W2));
1511*760c2415Smrg 
1512*760c2415Smrg     alias var_t = Algebraic!(void, string);
1513*760c2415Smrg     var_t foo = "quux";
1514*760c2415Smrg }
1515*760c2415Smrg 
1516*760c2415Smrg @system unittest
1517*760c2415Smrg {
1518*760c2415Smrg      alias A = Algebraic!(real, This[], This[int], This[This]);
1519*760c2415Smrg      A v1, v2, v3;
1520*760c2415Smrg      v2 = 5.0L;
1521*760c2415Smrg      v3 = 42.0L;
1522*760c2415Smrg      //v1 = [ v2 ][];
1523*760c2415Smrg       auto v = v1.peek!(A[]);
1524*760c2415Smrg      //writeln(v[0]);
1525*760c2415Smrg      v1 = [ 9 : v3 ];
1526*760c2415Smrg      //writeln(v1);
1527*760c2415Smrg      v1 = [ v3 : v3 ];
1528*760c2415Smrg      //writeln(v1);
1529*760c2415Smrg }
1530*760c2415Smrg 
1531*760c2415Smrg @system unittest
1532*760c2415Smrg {
1533*760c2415Smrg     import std.conv : ConvException;
1534*760c2415Smrg     import std.exception : assertThrown, collectException;
1535*760c2415Smrg     // try it with an oddly small size
1536*760c2415Smrg     VariantN!(1) test;
1537*760c2415Smrg     assert(test.size > 1);
1538*760c2415Smrg 
1539*760c2415Smrg     // variantArray tests
1540*760c2415Smrg     auto heterogeneous = variantArray(1, 4.5, "hi");
1541*760c2415Smrg     assert(heterogeneous.length == 3);
1542*760c2415Smrg     auto variantArrayAsVariant = Variant(heterogeneous);
1543*760c2415Smrg     assert(variantArrayAsVariant[0] == 1);
1544*760c2415Smrg     assert(variantArrayAsVariant.length == 3);
1545*760c2415Smrg 
1546*760c2415Smrg     // array tests
1547*760c2415Smrg     auto arr = Variant([1.2].dup);
1548*760c2415Smrg     auto e = arr[0];
1549*760c2415Smrg     assert(e == 1.2);
1550*760c2415Smrg     arr[0] = 2.0;
1551*760c2415Smrg     assert(arr[0] == 2);
1552*760c2415Smrg     arr ~= 4.5;
1553*760c2415Smrg     assert(arr[1] == 4.5);
1554*760c2415Smrg 
1555*760c2415Smrg     // general tests
1556*760c2415Smrg     Variant a;
1557*760c2415Smrg     auto b = Variant(5);
1558*760c2415Smrg     assert(!b.peek!(real) && b.peek!(int));
1559*760c2415Smrg     // assign
1560*760c2415Smrg     a = *b.peek!(int);
1561*760c2415Smrg     // comparison
1562*760c2415Smrg     assert(a == b, a.type.toString() ~ " " ~ b.type.toString());
1563*760c2415Smrg     auto c = Variant("this is a string");
1564*760c2415Smrg     assert(a != c);
1565*760c2415Smrg     // comparison via implicit conversions
1566*760c2415Smrg     a = 42; b = 42.0; assert(a == b);
1567*760c2415Smrg 
1568*760c2415Smrg     // try failing conversions
1569*760c2415Smrg     bool failed = false;
1570*760c2415Smrg     try
1571*760c2415Smrg     {
1572*760c2415Smrg         auto d = c.get!(int);
1573*760c2415Smrg     }
catch(Exception e)1574*760c2415Smrg     catch (Exception e)
1575*760c2415Smrg     {
1576*760c2415Smrg         //writeln(stderr, e.toString);
1577*760c2415Smrg         failed = true;
1578*760c2415Smrg     }
1579*760c2415Smrg     assert(failed); // :o)
1580*760c2415Smrg 
1581*760c2415Smrg     // toString tests
1582*760c2415Smrg     a = Variant(42); assert(a.toString() == "42");
1583*760c2415Smrg     a = Variant(42.22); assert(a.toString() == "42.22");
1584*760c2415Smrg 
1585*760c2415Smrg     // coerce tests
1586*760c2415Smrg     a = Variant(42.22); assert(a.coerce!(int) == 42);
1587*760c2415Smrg     a = cast(short) 5; assert(a.coerce!(double) == 5);
1588*760c2415Smrg     a = Variant("10"); assert(a.coerce!int == 10);
1589*760c2415Smrg 
1590*760c2415Smrg     a = Variant(1);
1591*760c2415Smrg     assert(a.coerce!bool);
1592*760c2415Smrg     a = Variant(0);
1593*760c2415Smrg     assert(!a.coerce!bool);
1594*760c2415Smrg 
1595*760c2415Smrg     a = Variant(1.0);
1596*760c2415Smrg     assert(a.coerce!bool);
1597*760c2415Smrg     a = Variant(0.0);
1598*760c2415Smrg     assert(!a.coerce!bool);
1599*760c2415Smrg     a = Variant(float.init);
1600*760c2415Smrg     assertThrown!ConvException(a.coerce!bool);
1601*760c2415Smrg 
1602*760c2415Smrg     a = Variant("true");
1603*760c2415Smrg     assert(a.coerce!bool);
1604*760c2415Smrg     a = Variant("false");
1605*760c2415Smrg     assert(!a.coerce!bool);
1606*760c2415Smrg     a = Variant("");
1607*760c2415Smrg     assertThrown!ConvException(a.coerce!bool);
1608*760c2415Smrg 
1609*760c2415Smrg     // Object tests
1610*760c2415Smrg     class B1 {}
1611*760c2415Smrg     class B2 : B1 {}
1612*760c2415Smrg     a = new B2;
1613*760c2415Smrg     assert(a.coerce!(B1) !is null);
1614*760c2415Smrg     a = new B1;
1615*760c2415Smrg     assert(collectException(a.coerce!(B2) is null));
1616*760c2415Smrg     a = cast(Object) new B2; // lose static type info; should still work
1617*760c2415Smrg     assert(a.coerce!(B2) !is null);
1618*760c2415Smrg 
1619*760c2415Smrg //     struct Big { int a[45]; }
1620*760c2415Smrg //     a = Big.init;
1621*760c2415Smrg 
1622*760c2415Smrg     // hash
1623*760c2415Smrg     assert(a.toHash() != 0);
1624*760c2415Smrg }
1625*760c2415Smrg 
1626*760c2415Smrg // tests adapted from
1627*760c2415Smrg // http://www.dsource.org/projects/tango/browser/trunk/tango/core/Variant.d?rev=2601
1628*760c2415Smrg @system unittest
1629*760c2415Smrg {
1630*760c2415Smrg     Variant v;
1631*760c2415Smrg 
1632*760c2415Smrg     assert(!v.hasValue);
1633*760c2415Smrg     v = 42;
1634*760c2415Smrg     assert( v.peek!(int) );
1635*760c2415Smrg     assert( v.convertsTo!(long) );
1636*760c2415Smrg     assert( v.get!(int) == 42 );
1637*760c2415Smrg     assert( v.get!(long) == 42L );
1638*760c2415Smrg     assert( v.get!(ulong) == 42uL );
1639*760c2415Smrg 
1640*760c2415Smrg     v = "Hello, World!";
1641*760c2415Smrg     assert( v.peek!(string) );
1642*760c2415Smrg 
1643*760c2415Smrg     assert( v.get!(string) == "Hello, World!" );
1644*760c2415Smrg     assert(!is(char[] : wchar[]));
1645*760c2415Smrg     assert( !v.convertsTo!(wchar[]) );
1646*760c2415Smrg     assert( v.get!(string) == "Hello, World!" );
1647*760c2415Smrg 
1648*760c2415Smrg     // Literal arrays are dynamically-typed
1649*760c2415Smrg     v = cast(int[4]) [1,2,3,4];
1650*760c2415Smrg     assert( v.peek!(int[4]) );
1651*760c2415Smrg     assert( v.get!(int[4]) == [1,2,3,4] );
1652*760c2415Smrg 
1653*760c2415Smrg     {
1654*760c2415Smrg          v = [1,2,3,4,5];
1655*760c2415Smrg          assert( v.peek!(int[]) );
1656*760c2415Smrg          assert( v.get!(int[]) == [1,2,3,4,5] );
1657*760c2415Smrg     }
1658*760c2415Smrg 
1659*760c2415Smrg     v = 3.1413;
1660*760c2415Smrg     assert( v.peek!(double) );
1661*760c2415Smrg     assert( v.convertsTo!(real) );
1662*760c2415Smrg     //@@@ BUG IN COMPILER: DOUBLE SHOULD NOT IMPLICITLY CONVERT TO FLOAT
1663*760c2415Smrg     assert( !v.convertsTo!(float) );
1664*760c2415Smrg     assert( *v.peek!(double) == 3.1413 );
1665*760c2415Smrg 
1666*760c2415Smrg     auto u = Variant(v);
1667*760c2415Smrg     assert( u.peek!(double) );
1668*760c2415Smrg     assert( *u.peek!(double) == 3.1413 );
1669*760c2415Smrg 
1670*760c2415Smrg     // operators
1671*760c2415Smrg     v = 38;
1672*760c2415Smrg     assert( v + 4 == 42 );
1673*760c2415Smrg     assert( 4 + v == 42 );
1674*760c2415Smrg     assert( v - 4 == 34 );
1675*760c2415Smrg     assert( Variant(4) - v == -34 );
1676*760c2415Smrg     assert( v * 2 == 76 );
1677*760c2415Smrg     assert( 2 * v == 76 );
1678*760c2415Smrg     assert( v / 2 == 19 );
1679*760c2415Smrg     assert( Variant(2) / v == 0 );
1680*760c2415Smrg     assert( v % 2 == 0 );
1681*760c2415Smrg     assert( Variant(2) % v == 2 );
1682*760c2415Smrg     assert( (v & 6) == 6 );
1683*760c2415Smrg     assert( (6 & v) == 6 );
1684*760c2415Smrg     assert( (v | 9) == 47 );
1685*760c2415Smrg     assert( (9 | v) == 47 );
1686*760c2415Smrg     assert( (v ^ 5) == 35 );
1687*760c2415Smrg     assert( (5 ^ v) == 35 );
1688*760c2415Smrg     assert( v << 1 == 76 );
1689*760c2415Smrg     assert( Variant(1) << Variant(2) == 4 );
1690*760c2415Smrg     assert( v >> 1 == 19 );
1691*760c2415Smrg     assert( Variant(4) >> Variant(2) == 1 );
1692*760c2415Smrg     assert( Variant("abc") ~ "def" == "abcdef" );
1693*760c2415Smrg     assert( Variant("abc") ~ Variant("def") == "abcdef" );
1694*760c2415Smrg 
1695*760c2415Smrg     v = 38;
1696*760c2415Smrg     v += 4;
1697*760c2415Smrg     assert( v == 42 );
1698*760c2415Smrg     v = 38; v -= 4; assert( v == 34 );
1699*760c2415Smrg     v = 38; v *= 2; assert( v == 76 );
1700*760c2415Smrg     v = 38; v /= 2; assert( v == 19 );
1701*760c2415Smrg     v = 38; v %= 2; assert( v == 0 );
1702*760c2415Smrg     v = 38; v &= 6; assert( v == 6 );
1703*760c2415Smrg     v = 38; v |= 9; assert( v == 47 );
1704*760c2415Smrg     v = 38; v ^= 5; assert( v == 35 );
1705*760c2415Smrg     v = 38; v <<= 1; assert( v == 76 );
1706*760c2415Smrg     v = 38; v >>= 1; assert( v == 19 );
1707*760c2415Smrg     v = 38; v += 1;  assert( v < 40 );
1708*760c2415Smrg 
1709*760c2415Smrg     v = "abc";
1710*760c2415Smrg     v ~= "def";
1711*760c2415Smrg     assert( v == "abcdef", *v.peek!(char[]) );
1712*760c2415Smrg     assert( Variant(0) < Variant(42) );
1713*760c2415Smrg     assert( Variant(42) > Variant(0) );
1714*760c2415Smrg     assert( Variant(42) > Variant(0.1) );
1715*760c2415Smrg     assert( Variant(42.1) > Variant(1) );
1716*760c2415Smrg     assert( Variant(21) == Variant(21) );
1717*760c2415Smrg     assert( Variant(0) != Variant(42) );
1718*760c2415Smrg     assert( Variant("bar") == Variant("bar") );
1719*760c2415Smrg     assert( Variant("foo") != Variant("bar") );
1720*760c2415Smrg 
1721*760c2415Smrg     {
1722*760c2415Smrg         auto v1 = Variant(42);
1723*760c2415Smrg         auto v2 = Variant("foo");
1724*760c2415Smrg         auto v3 = Variant(1+2.0i);
1725*760c2415Smrg 
1726*760c2415Smrg         int[Variant] hash;
1727*760c2415Smrg         hash[v1] = 0;
1728*760c2415Smrg         hash[v2] = 1;
1729*760c2415Smrg         hash[v3] = 2;
1730*760c2415Smrg 
1731*760c2415Smrg         assert( hash[v1] == 0 );
1732*760c2415Smrg         assert( hash[v2] == 1 );
1733*760c2415Smrg         assert( hash[v3] == 2 );
1734*760c2415Smrg     }
1735*760c2415Smrg 
1736*760c2415Smrg     {
1737*760c2415Smrg         int[char[]] hash;
1738*760c2415Smrg         hash["a"] = 1;
1739*760c2415Smrg         hash["b"] = 2;
1740*760c2415Smrg         hash["c"] = 3;
1741*760c2415Smrg         Variant vhash = hash;
1742*760c2415Smrg 
1743*760c2415Smrg         assert( vhash.get!(int[char[]])["a"] == 1 );
1744*760c2415Smrg         assert( vhash.get!(int[char[]])["b"] == 2 );
1745*760c2415Smrg         assert( vhash.get!(int[char[]])["c"] == 3 );
1746*760c2415Smrg     }
1747*760c2415Smrg }
1748*760c2415Smrg 
1749*760c2415Smrg @system unittest
1750*760c2415Smrg {
1751*760c2415Smrg     // check comparisons incompatible with AllowedTypes
1752*760c2415Smrg     Algebraic!int v = 2;
1753*760c2415Smrg 
1754*760c2415Smrg     assert(v == 2);
1755*760c2415Smrg     assert(v < 3);
1756*760c2415Smrg     static assert(!__traits(compiles, {v == long.max;}));
1757*760c2415Smrg     static assert(!__traits(compiles, {v == null;}));
1758*760c2415Smrg     static assert(!__traits(compiles, {v < long.max;}));
1759*760c2415Smrg     static assert(!__traits(compiles, {v > null;}));
1760*760c2415Smrg }
1761*760c2415Smrg 
1762*760c2415Smrg @system unittest
1763*760c2415Smrg {
1764*760c2415Smrg     // bug 1558
1765*760c2415Smrg     Variant va=1;
1766*760c2415Smrg     Variant vb=-2;
1767*760c2415Smrg     assert((va+vb).get!(int) == -1);
1768*760c2415Smrg     assert((va-vb).get!(int) == 3);
1769*760c2415Smrg }
1770*760c2415Smrg 
1771*760c2415Smrg @system unittest
1772*760c2415Smrg {
1773*760c2415Smrg     Variant a;
1774*760c2415Smrg     a=5;
1775*760c2415Smrg     Variant b;
1776*760c2415Smrg     b=a;
1777*760c2415Smrg     Variant[] c;
1778*760c2415Smrg     c = variantArray(1, 2, 3.0, "hello", 4);
1779*760c2415Smrg     assert(c[3] == "hello");
1780*760c2415Smrg }
1781*760c2415Smrg 
1782*760c2415Smrg @system unittest
1783*760c2415Smrg {
1784*760c2415Smrg     Variant v = 5;
1785*760c2415Smrg     assert(!__traits(compiles, v.coerce!(bool delegate())));
1786*760c2415Smrg }
1787*760c2415Smrg 
1788*760c2415Smrg 
1789*760c2415Smrg @system unittest
1790*760c2415Smrg {
1791*760c2415Smrg     struct Huge {
1792*760c2415Smrg         real a, b, c, d, e, f, g;
1793*760c2415Smrg     }
1794*760c2415Smrg 
1795*760c2415Smrg     Huge huge;
1796*760c2415Smrg     huge.e = 42;
1797*760c2415Smrg     Variant v;
1798*760c2415Smrg     v = huge;  // Compile time error.
1799*760c2415Smrg     assert(v.get!(Huge).e == 42);
1800*760c2415Smrg }
1801*760c2415Smrg 
1802*760c2415Smrg @system unittest
1803*760c2415Smrg {
1804*760c2415Smrg     const x = Variant(42);
1805*760c2415Smrg     auto y1 = x.get!(const int);
1806*760c2415Smrg     // @@@BUG@@@
1807*760c2415Smrg     //auto y2 = x.get!(immutable int)();
1808*760c2415Smrg }
1809*760c2415Smrg 
1810*760c2415Smrg // test iteration
1811*760c2415Smrg @system unittest
1812*760c2415Smrg {
1813*760c2415Smrg     auto v = Variant([ 1, 2, 3, 4 ][]);
1814*760c2415Smrg     auto j = 0;
foreach(int i;v)1815*760c2415Smrg     foreach (int i; v)
1816*760c2415Smrg     {
1817*760c2415Smrg         assert(i == ++j);
1818*760c2415Smrg     }
1819*760c2415Smrg     assert(j == 4);
1820*760c2415Smrg }
1821*760c2415Smrg 
1822*760c2415Smrg // test convertibility
1823*760c2415Smrg @system unittest
1824*760c2415Smrg {
1825*760c2415Smrg     auto v = Variant("abc".dup);
1826*760c2415Smrg     assert(v.convertsTo!(char[]));
1827*760c2415Smrg }
1828*760c2415Smrg 
1829*760c2415Smrg // http://d.puremagic.com/issues/show_bug.cgi?id=5424
1830*760c2415Smrg @system unittest
1831*760c2415Smrg {
1832*760c2415Smrg     interface A {
1833*760c2415Smrg         void func1();
1834*760c2415Smrg     }
1835*760c2415Smrg     static class AC: A {
func1()1836*760c2415Smrg         void func1() {
1837*760c2415Smrg         }
1838*760c2415Smrg     }
1839*760c2415Smrg 
1840*760c2415Smrg     A a = new AC();
1841*760c2415Smrg     a.func1();
1842*760c2415Smrg     Variant b = Variant(a);
1843*760c2415Smrg }
1844*760c2415Smrg 
1845*760c2415Smrg @system unittest
1846*760c2415Smrg {
1847*760c2415Smrg     // bug 7070
1848*760c2415Smrg     Variant v;
1849*760c2415Smrg     v = null;
1850*760c2415Smrg }
1851*760c2415Smrg 
1852*760c2415Smrg // Class and interface opEquals, issue 12157
1853*760c2415Smrg @system unittest
1854*760c2415Smrg {
1855*760c2415Smrg     class Foo { }
1856*760c2415Smrg 
1857*760c2415Smrg     class DerivedFoo : Foo { }
1858*760c2415Smrg 
1859*760c2415Smrg     Foo f1 = new Foo();
1860*760c2415Smrg     Foo f2 = new DerivedFoo();
1861*760c2415Smrg 
1862*760c2415Smrg     Variant v1 = f1, v2 = f2;
1863*760c2415Smrg     assert(v1 == f1);
1864*760c2415Smrg     assert(v1 != new Foo());
1865*760c2415Smrg     assert(v1 != f2);
1866*760c2415Smrg     assert(v2 != v1);
1867*760c2415Smrg     assert(v2 == f2);
1868*760c2415Smrg }
1869*760c2415Smrg 
1870*760c2415Smrg // Const parameters with opCall, issue 11361.
1871*760c2415Smrg @system unittest
1872*760c2415Smrg {
t1(string c)1873*760c2415Smrg     static string t1(string c) {
1874*760c2415Smrg         return c ~ "a";
1875*760c2415Smrg     }
1876*760c2415Smrg 
t2(const (char)[]p)1877*760c2415Smrg     static const(char)[] t2(const(char)[] p) {
1878*760c2415Smrg         return p ~ "b";
1879*760c2415Smrg     }
1880*760c2415Smrg 
t3(int p)1881*760c2415Smrg     static char[] t3(int p) {
1882*760c2415Smrg         import std.conv : text;
1883*760c2415Smrg         return p.text.dup;
1884*760c2415Smrg     }
1885*760c2415Smrg 
1886*760c2415Smrg     Variant v1 = &t1;
1887*760c2415Smrg     Variant v2 = &t2;
1888*760c2415Smrg     Variant v3 = &t3;
1889*760c2415Smrg 
1890*760c2415Smrg     assert(v1("abc") == "abca");
1891*760c2415Smrg     assert(v1("abc").type == typeid(string));
1892*760c2415Smrg     assert(v2("abc") == "abcb");
1893*760c2415Smrg 
1894*760c2415Smrg     assert(v2(cast(char[])("abc".dup)) == "abcb");
1895*760c2415Smrg     assert(v2("abc").type == typeid(const(char)[]));
1896*760c2415Smrg 
1897*760c2415Smrg     assert(v3(4) == ['4']);
1898*760c2415Smrg     assert(v3(4).type == typeid(char[]));
1899*760c2415Smrg }
1900*760c2415Smrg 
1901*760c2415Smrg // issue 12071
1902*760c2415Smrg @system unittest
1903*760c2415Smrg {
1904*760c2415Smrg     static struct Structure { int data; }
1905*760c2415Smrg     alias VariantTest = Algebraic!(Structure delegate() pure nothrow @nogc @safe);
1906*760c2415Smrg 
1907*760c2415Smrg     bool called = false;
example()1908*760c2415Smrg     Structure example() pure nothrow @nogc @safe
1909*760c2415Smrg     {
1910*760c2415Smrg         called = true;
1911*760c2415Smrg         return Structure.init;
1912*760c2415Smrg     }
1913*760c2415Smrg     auto m = VariantTest(&example);
1914*760c2415Smrg     m();
1915*760c2415Smrg     assert(called);
1916*760c2415Smrg }
1917*760c2415Smrg 
1918*760c2415Smrg // Ordering comparisons of incompatible types, e.g. issue 7990.
1919*760c2415Smrg @system unittest
1920*760c2415Smrg {
1921*760c2415Smrg     import std.exception : assertThrown;
1922*760c2415Smrg     assertThrown!VariantException(Variant(3) < "a");
1923*760c2415Smrg     assertThrown!VariantException("a" < Variant(3));
1924*760c2415Smrg     assertThrown!VariantException(Variant(3) < Variant("a"));
1925*760c2415Smrg 
1926*760c2415Smrg     assertThrown!VariantException(Variant.init < Variant(3));
1927*760c2415Smrg     assertThrown!VariantException(Variant(3) < Variant.init);
1928*760c2415Smrg }
1929*760c2415Smrg 
1930*760c2415Smrg // Handling of unordered types, e.g. issue 9043.
1931*760c2415Smrg @system unittest
1932*760c2415Smrg {
1933*760c2415Smrg     import std.exception : assertThrown;
1934*760c2415Smrg     static struct A { int a; }
1935*760c2415Smrg 
1936*760c2415Smrg     assert(Variant(A(3)) != A(4));
1937*760c2415Smrg 
1938*760c2415Smrg     assertThrown!VariantException(Variant(A(3)) < A(4));
1939*760c2415Smrg     assertThrown!VariantException(A(3) < Variant(A(4)));
1940*760c2415Smrg     assertThrown!VariantException(Variant(A(3)) < Variant(A(4)));
1941*760c2415Smrg }
1942*760c2415Smrg 
1943*760c2415Smrg // Handling of empty types and arrays, e.g. issue 10958
1944*760c2415Smrg @system unittest
1945*760c2415Smrg {
1946*760c2415Smrg     class EmptyClass { }
1947*760c2415Smrg     struct EmptyStruct { }
1948*760c2415Smrg     alias EmptyArray = void[0];
1949*760c2415Smrg     alias Alg = Algebraic!(EmptyClass, EmptyStruct, EmptyArray);
1950*760c2415Smrg 
testEmpty(T)1951*760c2415Smrg     Variant testEmpty(T)()
1952*760c2415Smrg     {
1953*760c2415Smrg         T inst;
1954*760c2415Smrg         Variant v = inst;
1955*760c2415Smrg         assert(v.get!T == inst);
1956*760c2415Smrg         assert(v.peek!T !is null);
1957*760c2415Smrg         assert(*v.peek!T == inst);
1958*760c2415Smrg         Alg alg = inst;
1959*760c2415Smrg         assert(alg.get!T == inst);
1960*760c2415Smrg         return v;
1961*760c2415Smrg     }
1962*760c2415Smrg 
1963*760c2415Smrg     testEmpty!EmptyClass();
1964*760c2415Smrg     testEmpty!EmptyStruct();
1965*760c2415Smrg     testEmpty!EmptyArray();
1966*760c2415Smrg 
1967*760c2415Smrg     // EmptyClass/EmptyStruct sizeof is 1, so we have this to test just size 0.
1968*760c2415Smrg     EmptyArray arr = EmptyArray.init;
1969*760c2415Smrg     Algebraic!(EmptyArray) a = arr;
1970*760c2415Smrg     assert(a.length == 0);
1971*760c2415Smrg     assert(a.get!EmptyArray == arr);
1972*760c2415Smrg }
1973*760c2415Smrg 
1974*760c2415Smrg // Handling of void function pointers / delegates, e.g. issue 11360
1975*760c2415Smrg @system unittest
1976*760c2415Smrg {
t1()1977*760c2415Smrg     static void t1() { }
1978*760c2415Smrg     Variant v = &t1;
1979*760c2415Smrg     assert(v() == Variant.init);
1980*760c2415Smrg 
t2()1981*760c2415Smrg     static int t2() { return 3; }
1982*760c2415Smrg     Variant v2 = &t2;
1983*760c2415Smrg     assert(v2() == 3);
1984*760c2415Smrg }
1985*760c2415Smrg 
1986*760c2415Smrg // Using peek for large structs, issue 8580
1987*760c2415Smrg @system unittest
1988*760c2415Smrg {
TestStruct(bool pad)1989*760c2415Smrg     struct TestStruct(bool pad)
1990*760c2415Smrg     {
1991*760c2415Smrg         int val1;
1992*760c2415Smrg         static if (pad)
1993*760c2415Smrg             ubyte[Variant.size] padding;
1994*760c2415Smrg         int val2;
1995*760c2415Smrg     }
1996*760c2415Smrg 
testPeekWith(T)1997*760c2415Smrg     void testPeekWith(T)()
1998*760c2415Smrg     {
1999*760c2415Smrg         T inst;
2000*760c2415Smrg         inst.val1 = 3;
2001*760c2415Smrg         inst.val2 = 4;
2002*760c2415Smrg         Variant v = inst;
2003*760c2415Smrg         T* original = v.peek!T;
2004*760c2415Smrg         assert(original.val1 == 3);
2005*760c2415Smrg         assert(original.val2 == 4);
2006*760c2415Smrg         original.val1 = 6;
2007*760c2415Smrg         original.val2 = 8;
2008*760c2415Smrg         T modified = v.get!T;
2009*760c2415Smrg         assert(modified.val1 == 6);
2010*760c2415Smrg         assert(modified.val2 == 8);
2011*760c2415Smrg     }
2012*760c2415Smrg 
2013*760c2415Smrg     testPeekWith!(TestStruct!false)();
2014*760c2415Smrg     testPeekWith!(TestStruct!true)();
2015*760c2415Smrg }
2016*760c2415Smrg 
2017*760c2415Smrg /**
2018*760c2415Smrg  * Applies a delegate or function to the given $(LREF Algebraic) depending on the held type,
2019*760c2415Smrg  * ensuring that all types are handled by the visiting functions.
2020*760c2415Smrg  *
2021*760c2415Smrg  * The delegate or function having the currently held value as parameter is called
2022*760c2415Smrg  * with $(D variant)'s current value. Visiting handlers are passed
2023*760c2415Smrg  * in the template parameter list.
2024*760c2415Smrg  * It is statically ensured that all held types of
2025*760c2415Smrg  * $(D variant) are handled across all handlers.
2026*760c2415Smrg  * $(D visit) allows delegates and static functions to be passed
2027*760c2415Smrg  * as parameters.
2028*760c2415Smrg  *
2029*760c2415Smrg  * If a function with an untyped parameter is specified, this function is called
2030*760c2415Smrg  * when the variant contains a type that does not match any other function.
2031*760c2415Smrg  * This can be used to apply the same function across multiple possible types.
2032*760c2415Smrg  * Exactly one generic function is allowed.
2033*760c2415Smrg  *
2034*760c2415Smrg  * If a function without parameters is specified, this function is called
2035*760c2415Smrg  * when `variant` doesn't hold a value. Exactly one parameter-less function
2036*760c2415Smrg  * is allowed.
2037*760c2415Smrg  *
2038*760c2415Smrg  * Duplicate overloads matching the same type in one of the visitors are disallowed.
2039*760c2415Smrg  *
2040*760c2415Smrg  * Returns: The return type of visit is deduced from the visiting functions and must be
2041*760c2415Smrg  * the same across all overloads.
2042*760c2415Smrg  * Throws: $(LREF VariantException) if `variant` doesn't hold a value and no
2043*760c2415Smrg  * parameter-less fallback function is specified.
2044*760c2415Smrg  */
2045*760c2415Smrg template visit(Handlers...)
2046*760c2415Smrg if (Handlers.length > 0)
2047*760c2415Smrg {
2048*760c2415Smrg     ///
2049*760c2415Smrg     auto visit(VariantType)(VariantType variant)
2050*760c2415Smrg         if (isAlgebraic!VariantType)
2051*760c2415Smrg     {
2052*760c2415Smrg         return visitImpl!(true, VariantType, Handlers)(variant);
2053*760c2415Smrg     }
2054*760c2415Smrg }
2055*760c2415Smrg 
2056*760c2415Smrg ///
2057*760c2415Smrg @system unittest
2058*760c2415Smrg {
2059*760c2415Smrg     Algebraic!(int, string) variant;
2060*760c2415Smrg 
2061*760c2415Smrg     variant = 10;
2062*760c2415Smrg     assert(variant.visit!((string s) => cast(int) s.length,
2063*760c2415Smrg                           (int i)    => i)()
2064*760c2415Smrg                           == 10);
2065*760c2415Smrg     variant = "string";
2066*760c2415Smrg     assert(variant.visit!((int i) => i,
2067*760c2415Smrg                           (string s) => cast(int) s.length)()
2068*760c2415Smrg                           == 6);
2069*760c2415Smrg 
2070*760c2415Smrg     // Error function usage
2071*760c2415Smrg     Algebraic!(int, string) emptyVar;
2072*760c2415Smrg     auto rslt = emptyVar.visit!((string s) => cast(int) s.length,
2073*760c2415Smrg                           (int i)    => i,
2074*760c2415Smrg                           () => -1)();
2075*760c2415Smrg     assert(rslt == -1);
2076*760c2415Smrg 
2077*760c2415Smrg     // Generic function usage
2078*760c2415Smrg     Algebraic!(int, float, real) number = 2;
2079*760c2415Smrg     assert(number.visit!(x => x += 1) == 3);
2080*760c2415Smrg 
2081*760c2415Smrg     // Generic function for int/float with separate behavior for string
2082*760c2415Smrg     Algebraic!(int, float, string) something = 2;
2083*760c2415Smrg     assert(something.visit!((string s) => s.length, x => x) == 2); // generic
2084*760c2415Smrg     something = "asdf";
2085*760c2415Smrg     assert(something.visit!((string s) => s.length, x => x) == 4); // string
2086*760c2415Smrg 
2087*760c2415Smrg     // Generic handler and empty handler
2088*760c2415Smrg     Algebraic!(int, float, real) empty2;
2089*760c2415Smrg     assert(empty2.visit!(x => x + 1, () => -1) == -1);
2090*760c2415Smrg }
2091*760c2415Smrg 
2092*760c2415Smrg @system unittest
2093*760c2415Smrg {
2094*760c2415Smrg     Algebraic!(size_t, string) variant;
2095*760c2415Smrg 
2096*760c2415Smrg     // not all handled check
2097*760c2415Smrg     static assert(!__traits(compiles, variant.visit!((size_t i){ })() ));
2098*760c2415Smrg 
2099*760c2415Smrg     variant = cast(size_t) 10;
2100*760c2415Smrg     auto which = 0;
2101*760c2415Smrg     variant.visit!( (string s) => which = 1,
2102*760c2415Smrg                     (size_t i) => which = 0
2103*760c2415Smrg                     )();
2104*760c2415Smrg 
2105*760c2415Smrg     // integer overload was called
2106*760c2415Smrg     assert(which == 0);
2107*760c2415Smrg 
2108*760c2415Smrg     // mustn't compile as generic Variant not supported
2109*760c2415Smrg     Variant v;
2110*760c2415Smrg     static assert(!__traits(compiles, v.visit!((string s) => which = 1,
2111*760c2415Smrg                                                (size_t i) => which = 0
2112*760c2415Smrg                                                 )()
2113*760c2415Smrg                                                 ));
2114*760c2415Smrg 
func(string s)2115*760c2415Smrg     static size_t func(string s) {
2116*760c2415Smrg         return s.length;
2117*760c2415Smrg     }
2118*760c2415Smrg 
2119*760c2415Smrg     variant = "test";
2120*760c2415Smrg     assert( 4 == variant.visit!(func,
2121*760c2415Smrg                                 (size_t i) => i
2122*760c2415Smrg                                 )());
2123*760c2415Smrg 
2124*760c2415Smrg     Algebraic!(int, float, string) variant2 = 5.0f;
2125*760c2415Smrg     // Shouldn' t compile as float not handled by visitor.
2126*760c2415Smrg     static assert(!__traits(compiles, variant2.visit!(
2127*760c2415Smrg                         (int _) {},
2128*760c2415Smrg                         (string _) {})()));
2129*760c2415Smrg 
2130*760c2415Smrg     Algebraic!(size_t, string, float) variant3;
2131*760c2415Smrg     variant3 = 10.0f;
2132*760c2415Smrg     auto floatVisited = false;
2133*760c2415Smrg 
2134*760c2415Smrg     assert(variant3.visit!(
2135*760c2415Smrg                  (float f) { floatVisited = true; return cast(size_t) f; },
2136*760c2415Smrg                  func,
2137*760c2415Smrg                  (size_t i) { return i; }
2138*760c2415Smrg                  )() == 10);
2139*760c2415Smrg     assert(floatVisited == true);
2140*760c2415Smrg 
2141*760c2415Smrg     Algebraic!(float, string) variant4;
2142*760c2415Smrg 
2143*760c2415Smrg     assert(variant4.visit!(func, (float f) => cast(size_t) f, () => size_t.max)() == size_t.max);
2144*760c2415Smrg 
2145*760c2415Smrg     // double error func check
2146*760c2415Smrg     static assert(!__traits(compiles,
2147*760c2415Smrg                             visit!(() => size_t.max, func, (float f) => cast(size_t) f, () => size_t.max)(variant4))
2148*760c2415Smrg                  );
2149*760c2415Smrg }
2150*760c2415Smrg 
2151*760c2415Smrg // disallow providing multiple generic handlers to visit
2152*760c2415Smrg // disallow a generic handler that does not apply to all types
2153*760c2415Smrg @system unittest
2154*760c2415Smrg {
2155*760c2415Smrg     Algebraic!(int, float) number = 2;
2156*760c2415Smrg     // ok, x + 1 valid for int and float
2157*760c2415Smrg     static assert( __traits(compiles, number.visit!(x => x + 1)));
2158*760c2415Smrg     // bad, two generic handlers
2159*760c2415Smrg     static assert(!__traits(compiles, number.visit!(x => x + 1, x => x + 2)));
2160*760c2415Smrg     // bad, x ~ "a" does not apply to int or float
2161*760c2415Smrg     static assert(!__traits(compiles, number.visit!(x => x ~ "a")));
2162*760c2415Smrg     // bad, x ~ "a" does not apply to int or float
2163*760c2415Smrg     static assert(!__traits(compiles, number.visit!(x => x + 1, x => x ~ "a")));
2164*760c2415Smrg 
2165*760c2415Smrg     Algebraic!(int, string) maybenumber = 2;
2166*760c2415Smrg     // ok, x ~ "a" valid for string, x + 1 valid for int, only 1 generic
2167*760c2415Smrg     static assert( __traits(compiles, number.visit!((string x) => x ~ "a", x => x + 1)));
2168*760c2415Smrg     // bad, x ~ "a" valid for string but not int
2169*760c2415Smrg     static assert(!__traits(compiles, number.visit!(x => x ~ "a")));
2170*760c2415Smrg     // bad, two generics, each only applies in one case
2171*760c2415Smrg     static assert(!__traits(compiles, number.visit!(x => x + 1, x => x ~ "a")));
2172*760c2415Smrg }
2173*760c2415Smrg 
2174*760c2415Smrg /**
2175*760c2415Smrg  * Behaves as $(LREF visit) but doesn't enforce that all types are handled
2176*760c2415Smrg  * by the visiting functions.
2177*760c2415Smrg  *
2178*760c2415Smrg  * If a parameter-less function is specified it is called when
2179*760c2415Smrg  * either $(D variant) doesn't hold a value or holds a type
2180*760c2415Smrg  * which isn't handled by the visiting functions.
2181*760c2415Smrg  *
2182*760c2415Smrg  * Returns: The return type of tryVisit is deduced from the visiting functions and must be
2183*760c2415Smrg  * the same across all overloads.
2184*760c2415Smrg  * Throws: $(LREF VariantException) if `variant` doesn't hold a value or
2185*760c2415Smrg  * `variant` holds a value which isn't handled by the visiting functions,
2186*760c2415Smrg  * when no parameter-less fallback function is specified.
2187*760c2415Smrg  */
2188*760c2415Smrg template tryVisit(Handlers...)
2189*760c2415Smrg if (Handlers.length > 0)
2190*760c2415Smrg {
2191*760c2415Smrg     ///
2192*760c2415Smrg     auto tryVisit(VariantType)(VariantType variant)
2193*760c2415Smrg         if (isAlgebraic!VariantType)
2194*760c2415Smrg     {
2195*760c2415Smrg         return visitImpl!(false, VariantType, Handlers)(variant);
2196*760c2415Smrg     }
2197*760c2415Smrg }
2198*760c2415Smrg 
2199*760c2415Smrg ///
2200*760c2415Smrg @system unittest
2201*760c2415Smrg {
2202*760c2415Smrg     Algebraic!(int, string) variant;
2203*760c2415Smrg 
2204*760c2415Smrg     variant = 10;
2205*760c2415Smrg     auto which = -1;
2206*760c2415Smrg     variant.tryVisit!((int i) { which = 0; })();
2207*760c2415Smrg     assert(which == 0);
2208*760c2415Smrg 
2209*760c2415Smrg     // Error function usage
2210*760c2415Smrg     variant = "test";
2211*760c2415Smrg     variant.tryVisit!((int i) { which = 0; },
2212*760c2415Smrg                       ()      { which = -100; })();
2213*760c2415Smrg     assert(which == -100);
2214*760c2415Smrg }
2215*760c2415Smrg 
2216*760c2415Smrg @system unittest
2217*760c2415Smrg {
2218*760c2415Smrg     import std.exception : assertThrown;
2219*760c2415Smrg     Algebraic!(int, string) variant;
2220*760c2415Smrg 
2221*760c2415Smrg     variant = 10;
2222*760c2415Smrg     auto which = -1;
2223*760c2415Smrg     variant.tryVisit!((int i){ which = 0; })();
2224*760c2415Smrg 
2225*760c2415Smrg     assert(which == 0);
2226*760c2415Smrg 
2227*760c2415Smrg     variant = "test";
2228*760c2415Smrg 
2229*760c2415Smrg     assertThrown!VariantException(variant.tryVisit!((int i) { which = 0; })());
2230*760c2415Smrg 
errorfunc()2231*760c2415Smrg     void errorfunc()
2232*760c2415Smrg     {
2233*760c2415Smrg         which = -1;
2234*760c2415Smrg     }
2235*760c2415Smrg 
2236*760c2415Smrg     variant.tryVisit!((int i) { which = 0; }, errorfunc)();
2237*760c2415Smrg 
2238*760c2415Smrg     assert(which == -1);
2239*760c2415Smrg }
2240*760c2415Smrg 
isAlgebraic(Type)2241*760c2415Smrg private template isAlgebraic(Type)
2242*760c2415Smrg {
2243*760c2415Smrg     static if (is(Type _ == VariantN!T, T...))
2244*760c2415Smrg         enum isAlgebraic = T.length >= 2; // T[0] == maxDataSize, T[1..$] == AllowedTypesParam
2245*760c2415Smrg     else
2246*760c2415Smrg         enum isAlgebraic = false;
2247*760c2415Smrg }
2248*760c2415Smrg 
2249*760c2415Smrg @system unittest
2250*760c2415Smrg {
2251*760c2415Smrg     static assert(!isAlgebraic!(Variant));
2252*760c2415Smrg     static assert( isAlgebraic!(Algebraic!(string)));
2253*760c2415Smrg     static assert( isAlgebraic!(Algebraic!(int, int[])));
2254*760c2415Smrg }
2255*760c2415Smrg 
2256*760c2415Smrg private auto visitImpl(bool Strict, VariantType, Handler...)(VariantType variant)
2257*760c2415Smrg if (isAlgebraic!VariantType && Handler.length > 0)
2258*760c2415Smrg {
2259*760c2415Smrg     alias AllowedTypes = VariantType.AllowedTypes;
2260*760c2415Smrg 
2261*760c2415Smrg 
2262*760c2415Smrg     /**
2263*760c2415Smrg      * Returns: Struct where $(D indices)  is an array which
2264*760c2415Smrg      * contains at the n-th position the index in Handler which takes the
2265*760c2415Smrg      * n-th type of AllowedTypes. If an Handler doesn't match an
2266*760c2415Smrg      * AllowedType, -1 is set. If a function in the delegates doesn't
2267*760c2415Smrg      * have parameters, the field $(D exceptionFuncIdx) is set;
2268*760c2415Smrg      * otherwise it's -1.
2269*760c2415Smrg      */
visitGetOverloadMap()2270*760c2415Smrg     auto visitGetOverloadMap()
2271*760c2415Smrg     {
2272*760c2415Smrg         struct Result {
2273*760c2415Smrg             int[AllowedTypes.length] indices;
2274*760c2415Smrg             int exceptionFuncIdx = -1;
2275*760c2415Smrg             int generalFuncIdx = -1;
2276*760c2415Smrg         }
2277*760c2415Smrg 
2278*760c2415Smrg         Result result;
2279*760c2415Smrg 
2280*760c2415Smrg         foreach (tidx, T; AllowedTypes)
2281*760c2415Smrg         {
2282*760c2415Smrg             bool added = false;
2283*760c2415Smrg             foreach (dgidx, dg; Handler)
2284*760c2415Smrg             {
2285*760c2415Smrg                 // Handle normal function objects
2286*760c2415Smrg                 static if (isSomeFunction!dg)
2287*760c2415Smrg                 {
2288*760c2415Smrg                     alias Params = Parameters!dg;
2289*760c2415Smrg                     static if (Params.length == 0)
2290*760c2415Smrg                     {
2291*760c2415Smrg                         // Just check exception functions in the first
2292*760c2415Smrg                         // inner iteration (over delegates)
2293*760c2415Smrg                         if (tidx > 0)
2294*760c2415Smrg                             continue;
2295*760c2415Smrg                         else
2296*760c2415Smrg                         {
2297*760c2415Smrg                             if (result.exceptionFuncIdx != -1)
2298*760c2415Smrg                                 assert(false, "duplicate parameter-less (error-)function specified");
2299*760c2415Smrg                             result.exceptionFuncIdx = dgidx;
2300*760c2415Smrg                         }
2301*760c2415Smrg                     }
2302*760c2415Smrg                     else static if (is(Params[0] == T) || is(Unqual!(Params[0]) == T))
2303*760c2415Smrg                     {
2304*760c2415Smrg                         if (added)
2305*760c2415Smrg                             assert(false, "duplicate overload specified for type '" ~ T.stringof ~ "'");
2306*760c2415Smrg 
2307*760c2415Smrg                         added = true;
2308*760c2415Smrg                         result.indices[tidx] = dgidx;
2309*760c2415Smrg                     }
2310*760c2415Smrg                 }
2311*760c2415Smrg                 else static if (isSomeFunction!(dg!T))
2312*760c2415Smrg                 {
2313*760c2415Smrg                     assert(result.generalFuncIdx == -1 ||
2314*760c2415Smrg                            result.generalFuncIdx == dgidx,
2315*760c2415Smrg                            "Only one generic visitor function is allowed");
2316*760c2415Smrg                     result.generalFuncIdx = dgidx;
2317*760c2415Smrg                 }
2318*760c2415Smrg                 // Handle composite visitors with opCall overloads
2319*760c2415Smrg                 else
2320*760c2415Smrg                 {
2321*760c2415Smrg                     static assert(false, dg.stringof ~ " is not a function or delegate");
2322*760c2415Smrg                 }
2323*760c2415Smrg             }
2324*760c2415Smrg 
2325*760c2415Smrg             if (!added)
2326*760c2415Smrg                 result.indices[tidx] = -1;
2327*760c2415Smrg         }
2328*760c2415Smrg 
2329*760c2415Smrg         return result;
2330*760c2415Smrg     }
2331*760c2415Smrg 
2332*760c2415Smrg     enum HandlerOverloadMap = visitGetOverloadMap();
2333*760c2415Smrg 
2334*760c2415Smrg     if (!variant.hasValue)
2335*760c2415Smrg     {
2336*760c2415Smrg         // Call the exception function. The HandlerOverloadMap
2337*760c2415Smrg         // will have its exceptionFuncIdx field set to value != -1 if an
2338*760c2415Smrg         // exception function has been specified; otherwise we just through an exception.
2339*760c2415Smrg         static if (HandlerOverloadMap.exceptionFuncIdx != -1)
2340*760c2415Smrg             return Handler[ HandlerOverloadMap.exceptionFuncIdx ]();
2341*760c2415Smrg         else
2342*760c2415Smrg             throw new VariantException("variant must hold a value before being visited.");
2343*760c2415Smrg     }
2344*760c2415Smrg 
foreach(idx,T;AllowedTypes)2345*760c2415Smrg     foreach (idx, T; AllowedTypes)
2346*760c2415Smrg     {
2347*760c2415Smrg         if (auto ptr = variant.peek!T)
2348*760c2415Smrg         {
2349*760c2415Smrg             enum dgIdx = HandlerOverloadMap.indices[idx];
2350*760c2415Smrg 
2351*760c2415Smrg             static if (dgIdx == -1)
2352*760c2415Smrg             {
2353*760c2415Smrg                 static if (HandlerOverloadMap.generalFuncIdx >= 0)
2354*760c2415Smrg                     return Handler[HandlerOverloadMap.generalFuncIdx](*ptr);
2355*760c2415Smrg                 else static if (Strict)
2356*760c2415Smrg                     static assert(false, "overload for type '" ~ T.stringof ~ "' hasn't been specified");
2357*760c2415Smrg                 else static if (HandlerOverloadMap.exceptionFuncIdx != -1)
2358*760c2415Smrg                     return Handler[HandlerOverloadMap.exceptionFuncIdx]();
2359*760c2415Smrg                 else
2360*760c2415Smrg                     throw new VariantException(
2361*760c2415Smrg                         "variant holds value of type '"
2362*760c2415Smrg                         ~ T.stringof ~
2363*760c2415Smrg                         "' but no visitor has been provided"
2364*760c2415Smrg                     );
2365*760c2415Smrg             }
2366*760c2415Smrg             else
2367*760c2415Smrg             {
2368*760c2415Smrg                 return Handler[ dgIdx ](*ptr);
2369*760c2415Smrg             }
2370*760c2415Smrg         }
2371*760c2415Smrg     }
2372*760c2415Smrg 
2373*760c2415Smrg     assert(false);
2374*760c2415Smrg }
2375*760c2415Smrg 
2376*760c2415Smrg @system unittest
2377*760c2415Smrg {
2378*760c2415Smrg     // validate that visit can be called with a const type
2379*760c2415Smrg     struct Foo { int depth; }
2380*760c2415Smrg     struct Bar { int depth; }
2381*760c2415Smrg     alias FooBar = Algebraic!(Foo, Bar);
2382*760c2415Smrg 
depth(in FooBar fb)2383*760c2415Smrg     int depth(in FooBar fb) {
2384*760c2415Smrg         return fb.visit!((Foo foo) => foo.depth,
2385*760c2415Smrg                          (Bar bar) => bar.depth);
2386*760c2415Smrg     }
2387*760c2415Smrg 
2388*760c2415Smrg     FooBar fb = Foo(3);
2389*760c2415Smrg     assert(depth(fb) == 3);
2390*760c2415Smrg }
2391*760c2415Smrg 
2392*760c2415Smrg @system unittest
2393*760c2415Smrg {
2394*760c2415Smrg     // https://issues.dlang.org/show_bug.cgi?id=16383
this()2395*760c2415Smrg     class Foo {this() immutable {}}
2396*760c2415Smrg     alias V = Algebraic!(immutable Foo);
2397*760c2415Smrg 
2398*760c2415Smrg     auto x = V(new immutable Foo).visit!(
2399*760c2415Smrg         (immutable(Foo) _) => 3
2400*760c2415Smrg     );
2401*760c2415Smrg     assert(x == 3);
2402*760c2415Smrg }
2403*760c2415Smrg 
2404*760c2415Smrg @system unittest
2405*760c2415Smrg {
2406*760c2415Smrg     // http://d.puremagic.com/issues/show_bug.cgi?id=5310
2407*760c2415Smrg     const Variant a;
2408*760c2415Smrg     assert(a == a);
2409*760c2415Smrg     Variant b;
2410*760c2415Smrg     assert(a == b);
2411*760c2415Smrg     assert(b == a);
2412*760c2415Smrg }
2413*760c2415Smrg 
2414*760c2415Smrg @system unittest
2415*760c2415Smrg {
2416*760c2415Smrg     const Variant a = [2];
2417*760c2415Smrg     assert(a[0] == 2);
2418*760c2415Smrg }
2419*760c2415Smrg 
2420*760c2415Smrg @system unittest
2421*760c2415Smrg {
2422*760c2415Smrg     // http://d.puremagic.com/issues/show_bug.cgi?id=10017
2423*760c2415Smrg     static struct S
2424*760c2415Smrg     {
2425*760c2415Smrg         ubyte[Variant.size + 1] s;
2426*760c2415Smrg     }
2427*760c2415Smrg 
2428*760c2415Smrg     Variant v1, v2;
2429*760c2415Smrg     v1 = S(); // the payload is allocated on the heap
2430*760c2415Smrg     v2 = v1;  // AssertError: target must be non-null
2431*760c2415Smrg     assert(v1 == v2);
2432*760c2415Smrg }
2433*760c2415Smrg @system unittest
2434*760c2415Smrg {
2435*760c2415Smrg     import std.exception : assertThrown;
2436*760c2415Smrg     // http://d.puremagic.com/issues/show_bug.cgi?id=7069
2437*760c2415Smrg     Variant v;
2438*760c2415Smrg 
2439*760c2415Smrg     int i = 10;
2440*760c2415Smrg     v = i;
2441*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ConstOf))
2442*760c2415Smrg     {
2443*760c2415Smrg         assert(v.get!(qual!int) == 10);
2444*760c2415Smrg         assert(v.get!(qual!float) == 10.0f);
2445*760c2415Smrg     }
2446*760c2415Smrg     foreach (qual; AliasSeq!(ImmutableOf, SharedOf, SharedConstOf))
2447*760c2415Smrg     {
2448*760c2415Smrg         assertThrown!VariantException(v.get!(qual!int));
2449*760c2415Smrg     }
2450*760c2415Smrg 
2451*760c2415Smrg     const(int) ci = 20;
2452*760c2415Smrg     v = ci;
2453*760c2415Smrg     foreach (qual; AliasSeq!(ConstOf))
2454*760c2415Smrg     {
2455*760c2415Smrg         assert(v.get!(qual!int) == 20);
2456*760c2415Smrg         assert(v.get!(qual!float) == 20.0f);
2457*760c2415Smrg     }
2458*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ImmutableOf, SharedOf, SharedConstOf))
2459*760c2415Smrg     {
2460*760c2415Smrg         assertThrown!VariantException(v.get!(qual!int));
2461*760c2415Smrg         assertThrown!VariantException(v.get!(qual!float));
2462*760c2415Smrg     }
2463*760c2415Smrg 
2464*760c2415Smrg     immutable(int) ii = ci;
2465*760c2415Smrg     v = ii;
2466*760c2415Smrg     foreach (qual; AliasSeq!(ImmutableOf, ConstOf, SharedConstOf))
2467*760c2415Smrg     {
2468*760c2415Smrg         assert(v.get!(qual!int) == 20);
2469*760c2415Smrg         assert(v.get!(qual!float) == 20.0f);
2470*760c2415Smrg     }
2471*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, SharedOf))
2472*760c2415Smrg     {
2473*760c2415Smrg         assertThrown!VariantException(v.get!(qual!int));
2474*760c2415Smrg         assertThrown!VariantException(v.get!(qual!float));
2475*760c2415Smrg     }
2476*760c2415Smrg 
2477*760c2415Smrg     int[] ai = [1,2,3];
2478*760c2415Smrg     v = ai;
2479*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ConstOf))
2480*760c2415Smrg     {
2481*760c2415Smrg         assert(v.get!(qual!(int[])) == [1,2,3]);
2482*760c2415Smrg         assert(v.get!(qual!(int)[]) == [1,2,3]);
2483*760c2415Smrg     }
2484*760c2415Smrg     foreach (qual; AliasSeq!(ImmutableOf, SharedOf, SharedConstOf))
2485*760c2415Smrg     {
2486*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int[])));
2487*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int)[]));
2488*760c2415Smrg     }
2489*760c2415Smrg 
2490*760c2415Smrg     const(int[]) cai = [4,5,6];
2491*760c2415Smrg     v = cai;
2492*760c2415Smrg     foreach (qual; AliasSeq!(ConstOf))
2493*760c2415Smrg     {
2494*760c2415Smrg         assert(v.get!(qual!(int[])) == [4,5,6]);
2495*760c2415Smrg         assert(v.get!(qual!(int)[]) == [4,5,6]);
2496*760c2415Smrg     }
2497*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ImmutableOf, SharedOf, SharedConstOf))
2498*760c2415Smrg     {
2499*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int[])));
2500*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int)[]));
2501*760c2415Smrg     }
2502*760c2415Smrg 
2503*760c2415Smrg     immutable(int[]) iai = [7,8,9];
2504*760c2415Smrg     v = iai;
2505*760c2415Smrg     //assert(v.get!(immutable(int[])) == [7,8,9]);   // Bug ??? runtime error
2506*760c2415Smrg     assert(v.get!(immutable(int)[]) == [7,8,9]);
2507*760c2415Smrg     assert(v.get!(const(int[])) == [7,8,9]);
2508*760c2415Smrg     assert(v.get!(const(int)[]) == [7,8,9]);
2509*760c2415Smrg     //assert(v.get!(shared(const(int[]))) == cast(shared const)[7,8,9]);    // Bug ??? runtime error
2510*760c2415Smrg     //assert(v.get!(shared(const(int))[]) == cast(shared const)[7,8,9]);    // Bug ??? runtime error
2511*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf))
2512*760c2415Smrg     {
2513*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int[])));
2514*760c2415Smrg         assertThrown!VariantException(v.get!(qual!(int)[]));
2515*760c2415Smrg     }
2516*760c2415Smrg 
2517*760c2415Smrg     class A {}
2518*760c2415Smrg     class B : A {}
2519*760c2415Smrg     B b = new B();
2520*760c2415Smrg     v = b;
2521*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ConstOf))
2522*760c2415Smrg     {
2523*760c2415Smrg         assert(v.get!(qual!B) is b);
2524*760c2415Smrg         assert(v.get!(qual!A) is b);
2525*760c2415Smrg         assert(v.get!(qual!Object) is b);
2526*760c2415Smrg     }
2527*760c2415Smrg     foreach (qual; AliasSeq!(ImmutableOf, SharedOf, SharedConstOf))
2528*760c2415Smrg     {
2529*760c2415Smrg         assertThrown!VariantException(v.get!(qual!B));
2530*760c2415Smrg         assertThrown!VariantException(v.get!(qual!A));
2531*760c2415Smrg         assertThrown!VariantException(v.get!(qual!Object));
2532*760c2415Smrg     }
2533*760c2415Smrg 
2534*760c2415Smrg     const(B) cb = new B();
2535*760c2415Smrg     v = cb;
2536*760c2415Smrg     foreach (qual; AliasSeq!(ConstOf))
2537*760c2415Smrg     {
2538*760c2415Smrg         assert(v.get!(qual!B) is cb);
2539*760c2415Smrg         assert(v.get!(qual!A) is cb);
2540*760c2415Smrg         assert(v.get!(qual!Object) is cb);
2541*760c2415Smrg     }
2542*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ImmutableOf, SharedOf, SharedConstOf))
2543*760c2415Smrg     {
2544*760c2415Smrg         assertThrown!VariantException(v.get!(qual!B));
2545*760c2415Smrg         assertThrown!VariantException(v.get!(qual!A));
2546*760c2415Smrg         assertThrown!VariantException(v.get!(qual!Object));
2547*760c2415Smrg     }
2548*760c2415Smrg 
2549*760c2415Smrg     immutable(B) ib = new immutable(B)();
2550*760c2415Smrg     v = ib;
2551*760c2415Smrg     foreach (qual; AliasSeq!(ImmutableOf, ConstOf, SharedConstOf))
2552*760c2415Smrg     {
2553*760c2415Smrg         assert(v.get!(qual!B) is ib);
2554*760c2415Smrg         assert(v.get!(qual!A) is ib);
2555*760c2415Smrg         assert(v.get!(qual!Object) is ib);
2556*760c2415Smrg     }
2557*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, SharedOf))
2558*760c2415Smrg     {
2559*760c2415Smrg         assertThrown!VariantException(v.get!(qual!B));
2560*760c2415Smrg         assertThrown!VariantException(v.get!(qual!A));
2561*760c2415Smrg         assertThrown!VariantException(v.get!(qual!Object));
2562*760c2415Smrg     }
2563*760c2415Smrg 
2564*760c2415Smrg     shared(B) sb = new shared B();
2565*760c2415Smrg     v = sb;
2566*760c2415Smrg     foreach (qual; AliasSeq!(SharedOf, SharedConstOf))
2567*760c2415Smrg     {
2568*760c2415Smrg         assert(v.get!(qual!B) is sb);
2569*760c2415Smrg         assert(v.get!(qual!A) is sb);
2570*760c2415Smrg         assert(v.get!(qual!Object) is sb);
2571*760c2415Smrg     }
2572*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ImmutableOf, ConstOf))
2573*760c2415Smrg     {
2574*760c2415Smrg         assertThrown!VariantException(v.get!(qual!B));
2575*760c2415Smrg         assertThrown!VariantException(v.get!(qual!A));
2576*760c2415Smrg         assertThrown!VariantException(v.get!(qual!Object));
2577*760c2415Smrg     }
2578*760c2415Smrg 
2579*760c2415Smrg     shared(const(B)) scb = new shared const B();
2580*760c2415Smrg     v = scb;
2581*760c2415Smrg     foreach (qual; AliasSeq!(SharedConstOf))
2582*760c2415Smrg     {
2583*760c2415Smrg         assert(v.get!(qual!B) is scb);
2584*760c2415Smrg         assert(v.get!(qual!A) is scb);
2585*760c2415Smrg         assert(v.get!(qual!Object) is scb);
2586*760c2415Smrg     }
2587*760c2415Smrg     foreach (qual; AliasSeq!(MutableOf, ConstOf, ImmutableOf, SharedOf))
2588*760c2415Smrg     {
2589*760c2415Smrg         assertThrown!VariantException(v.get!(qual!B));
2590*760c2415Smrg         assertThrown!VariantException(v.get!(qual!A));
2591*760c2415Smrg         assertThrown!VariantException(v.get!(qual!Object));
2592*760c2415Smrg     }
2593*760c2415Smrg }
2594*760c2415Smrg 
2595*760c2415Smrg @system unittest
2596*760c2415Smrg {
2597*760c2415Smrg     static struct DummyScope
2598*760c2415Smrg     {
2599*760c2415Smrg         // https://d.puremagic.com/issues/show_bug.cgi?id=12540
2600*760c2415Smrg         alias Alias12540 = Algebraic!Class12540;
2601*760c2415Smrg 
2602*760c2415Smrg         static class Class12540
2603*760c2415Smrg         {
2604*760c2415Smrg             Alias12540 entity;
2605*760c2415Smrg         }
2606*760c2415Smrg     }
2607*760c2415Smrg }
2608*760c2415Smrg 
2609*760c2415Smrg @system unittest
2610*760c2415Smrg {
2611*760c2415Smrg     // https://issues.dlang.org/show_bug.cgi?id=10194
2612*760c2415Smrg     // Also test for elaborate copying
2613*760c2415Smrg     static struct S
2614*760c2415Smrg     {
2615*760c2415Smrg         @disable this();
2616*760c2415Smrg         this(int dummy)
2617*760c2415Smrg         {
2618*760c2415Smrg             ++cnt;
2619*760c2415Smrg         }
2620*760c2415Smrg 
2621*760c2415Smrg         this(this)
2622*760c2415Smrg         {
2623*760c2415Smrg             ++cnt;
2624*760c2415Smrg         }
2625*760c2415Smrg 
2626*760c2415Smrg         @disable S opAssign();
2627*760c2415Smrg 
2628*760c2415Smrg         ~this()
2629*760c2415Smrg         {
2630*760c2415Smrg             --cnt;
2631*760c2415Smrg             assert(cnt >= 0);
2632*760c2415Smrg         }
2633*760c2415Smrg         static int cnt = 0;
2634*760c2415Smrg     }
2635*760c2415Smrg 
2636*760c2415Smrg     {
2637*760c2415Smrg         Variant v;
2638*760c2415Smrg         {
2639*760c2415Smrg             v = S(0);
2640*760c2415Smrg             assert(S.cnt == 1);
2641*760c2415Smrg         }
2642*760c2415Smrg         assert(S.cnt == 1);
2643*760c2415Smrg 
2644*760c2415Smrg         // assigning a new value should destroy the existing one
2645*760c2415Smrg         v = 0;
2646*760c2415Smrg         assert(S.cnt == 0);
2647*760c2415Smrg 
2648*760c2415Smrg         // destroying the variant should destroy it's current value
2649*760c2415Smrg         v = S(0);
2650*760c2415Smrg         assert(S.cnt == 1);
2651*760c2415Smrg     }
2652*760c2415Smrg     assert(S.cnt == 0);
2653*760c2415Smrg }
2654*760c2415Smrg 
2655*760c2415Smrg @system unittest
2656*760c2415Smrg {
2657*760c2415Smrg     // Bugzilla 13300
2658*760c2415Smrg     static struct S
2659*760c2415Smrg     {
2660*760c2415Smrg         this(this) {}
2661*760c2415Smrg         ~this() {}
2662*760c2415Smrg     }
2663*760c2415Smrg 
2664*760c2415Smrg     static assert( hasElaborateCopyConstructor!(Variant));
2665*760c2415Smrg     static assert(!hasElaborateCopyConstructor!(Algebraic!bool));
2666*760c2415Smrg     static assert( hasElaborateCopyConstructor!(Algebraic!S));
2667*760c2415Smrg     static assert( hasElaborateCopyConstructor!(Algebraic!(bool, S)));
2668*760c2415Smrg 
2669*760c2415Smrg     static assert( hasElaborateDestructor!(Variant));
2670*760c2415Smrg     static assert(!hasElaborateDestructor!(Algebraic!bool));
2671*760c2415Smrg     static assert( hasElaborateDestructor!(Algebraic!S));
2672*760c2415Smrg     static assert( hasElaborateDestructor!(Algebraic!(bool, S)));
2673*760c2415Smrg 
2674*760c2415Smrg     import std.array;
2675*760c2415Smrg     alias Value = Algebraic!bool;
2676*760c2415Smrg 
2677*760c2415Smrg     static struct T
2678*760c2415Smrg     {
2679*760c2415Smrg         Value value;
2680*760c2415Smrg         @disable this();
2681*760c2415Smrg     }
2682*760c2415Smrg     auto a = appender!(T[]);
2683*760c2415Smrg }
2684*760c2415Smrg 
2685*760c2415Smrg @system unittest
2686*760c2415Smrg {
2687*760c2415Smrg     // Bugzilla 13871
2688*760c2415Smrg     alias A = Algebraic!(int, typeof(null));
2689*760c2415Smrg     static struct B { A value; }
2690*760c2415Smrg     alias C = std.variant.Algebraic!B;
2691*760c2415Smrg 
2692*760c2415Smrg     C var;
2693*760c2415Smrg     var = C(B());
2694*760c2415Smrg }
2695*760c2415Smrg 
2696*760c2415Smrg @system unittest
2697*760c2415Smrg {
2698*760c2415Smrg     import std.exception : assertThrown, assertNotThrown;
2699*760c2415Smrg     // Make sure Variant can handle types with opDispatch but no length field.
2700*760c2415Smrg     struct SWithNoLength
2701*760c2415Smrg     {
2702*760c2415Smrg         void opDispatch(string s)() { }
2703*760c2415Smrg     }
2704*760c2415Smrg 
2705*760c2415Smrg     struct SWithLength
2706*760c2415Smrg     {
2707*760c2415Smrg         @property int opDispatch(string s)()
2708*760c2415Smrg         {
2709*760c2415Smrg             // Assume that s == "length"
2710*760c2415Smrg             return 5; // Any value is OK for test.
2711*760c2415Smrg         }
2712*760c2415Smrg     }
2713*760c2415Smrg 
2714*760c2415Smrg     SWithNoLength sWithNoLength;
2715*760c2415Smrg     Variant v = sWithNoLength;
2716*760c2415Smrg     assertThrown!VariantException(v.length);
2717*760c2415Smrg 
2718*760c2415Smrg     SWithLength sWithLength;
2719*760c2415Smrg     v = sWithLength;
2720*760c2415Smrg     assertNotThrown!VariantException(v.get!SWithLength.length);
2721*760c2415Smrg     assertThrown!VariantException(v.length);
2722*760c2415Smrg }
2723*760c2415Smrg 
2724*760c2415Smrg @system unittest
2725*760c2415Smrg {
2726*760c2415Smrg     // Bugzilla 13534
2727*760c2415Smrg     static assert(!__traits(compiles, () @safe {
2728*760c2415Smrg         auto foo() @system { return 3; }
2729*760c2415Smrg         auto v = Variant(&foo);
2730*760c2415Smrg         v(); // foo is called in safe code!?
2731*760c2415Smrg     }));
2732*760c2415Smrg }
2733*760c2415Smrg 
2734*760c2415Smrg @system unittest
2735*760c2415Smrg {
2736*760c2415Smrg     // Bugzilla 15039
2737*760c2415Smrg     import std.typecons;
2738*760c2415Smrg     import std.variant;
2739*760c2415Smrg 
2740*760c2415Smrg     alias IntTypedef = Typedef!int;
2741*760c2415Smrg     alias Obj = Algebraic!(int, IntTypedef, This[]);
2742*760c2415Smrg 
2743*760c2415Smrg     Obj obj = 1;
2744*760c2415Smrg 
2745*760c2415Smrg     obj.visit!(
2746*760c2415Smrg         (int x) {},
2747*760c2415Smrg         (IntTypedef x) {},
2748*760c2415Smrg         (Obj[] x) {},
2749*760c2415Smrg     );
2750*760c2415Smrg }
2751*760c2415Smrg 
2752*760c2415Smrg @system unittest
2753*760c2415Smrg {
2754*760c2415Smrg     // Bugzilla 15791
2755*760c2415Smrg     int n = 3;
2756*760c2415Smrg     struct NS1 { int foo() { return n + 10; } }
2757*760c2415Smrg     struct NS2 { int foo() { return n * 10; } }
2758*760c2415Smrg 
2759*760c2415Smrg     Variant v;
2760*760c2415Smrg     v = NS1();
2761*760c2415Smrg     assert(v.get!NS1.foo() == 13);
2762*760c2415Smrg     v = NS2();
2763*760c2415Smrg     assert(v.get!NS2.foo() == 30);
2764*760c2415Smrg }
2765*760c2415Smrg 
2766*760c2415Smrg @system unittest
2767*760c2415Smrg {
2768*760c2415Smrg     // Bugzilla 15827
2769*760c2415Smrg     static struct Foo15827 { Variant v; this(Foo15827 v) {} }
2770*760c2415Smrg     Variant v = Foo15827.init;
2771*760c2415Smrg }
2772