1 /** Array Containers.
2 
3     TODO Split up `Array` into `Array`, `SortedArray`, `SetArray` and reuse
4     logic in `Array` via `alias this` or free functions.
5 
6     TODO Use `std.algorithm.mutation.move` and `std.range.primitives.moveAt`
7 
8     TODO copy assignment, struct Store, Notify andralex of packed array
9 
10     TODO Add `c.insertAfter(r, x)` where `c` is a collection, `r` is a range
11     previously extracted from `c`, and `x` is a value convertible to
12     collection's element type. See also:
13     https://forum.dlang.org/post/n3qq6e$2bis$1@digitalmars.com
14  */
15 module array_ex;
16 
17 // private import std.experimental.allocator.mallocator : Mallocator;
18 
19 // we handle these as pure to make containers using them pure
20 extern(C) pure nothrow @system @nogc
21 {
22     void* malloc(size_t size);
23     void* realloc(void* ptr, size_t size);
24     void free(void* ptr);
25 }
26 
27 enum Ordering
28 {
29     unsorted, // unsorted array
30     sortedValues, // sorted array with possibly duplicate values
31     sortedUniqueSet, // sorted array with unique values
32 }
33 
34 version(unittest)
35 {
36     import std.algorithm.comparison : equal;
37     import std.meta : AliasSeq;
38 }
39 
40 enum IsOrdered(Ordering ordering) = ordering != Ordering.unsorted;
41 
42 static if (__VERSION__ >= 2071)
43 {
44     import std.math : nextPow2;
45 }
46 else
47 {
48 /**
49    Returns $(D s) rounded up to the nearest power of 2.
50    Taken from `roundUpToPowerOf2` in allocator.
51 */
52     auto nextPow2(size_t s)
53     {
54         import std.meta : AliasSeq;
55         assert(s <= (size_t.max >> 1) + 1);
56         --s;
57         static if (size_t.sizeof == 4)
58             alias Shifts = AliasSeq!(1, 2, 4, 8, 16);
59         else
60             alias Shifts = AliasSeq!(1, 2, 4, 8, 16, 32);
61         foreach (i; Shifts)
62         {
63             s |= s >> i;
64         }
65         return s + 1;
66     }
67 }
68 
69 template shouldAddGCRange(T)
70 {
71     import std.traits : isPointer, hasIndirections;
72     enum shouldAddGCRange = isPointer!T || hasIndirections!T || is (T == class);
73 }
74 
75 /// Large array storage.
76 static struct Large(E, bool useGC)
77 {
78     E* ptr;
79     size_t length;
80 
81     static if (useGC)
82     {
83         import core.memory : GC;
84     }
85     else
86     {
87         alias _malloc = malloc;
88         alias _realloc = realloc;
89         alias _free = free;
90     }
91 
92     pure nothrow @trusted:
93 
94     static if (useGC)
95     {
96         this(size_t n)
97         {
98             length = n;
99             ptr = cast(E*)GC.malloc(E.sizeof * length);
100         }
101         void resize(size_t n)
102         {
103             length = n;
104             ptr = cast(E*)GC.realloc(ptr, E.sizeof * length);
105         }
106         void clear()
107         {
108             GC.free(ptr); debug ptr = null;
109         }
110     }
111     else
112     {
113         @nogc:
114         this(size_t n)
115         {
116             length = n;
117             ptr = cast(E*)malloc(E.sizeof * length);
118         }
119         void resize(size_t n)
120         {
121             length = n;
122             ptr = cast(E*)_realloc(ptr, E.sizeof * length);
123         }
124         void clear()
125         {
126             _free(ptr); debug ptr = null;
127         }
128     }
129 }
130 
131 /// Small array storage.
132 alias Small(E, size_t n) = E[n];
133 
134 /// Small-size-optimized (SSO) array store.
135 static struct Store(E, bool useGC = shouldAddGCRange!E)
136 {
137     /** Fixed number elements that fit into small variant storage. */
138     enum smallLength = Large!(E, useGC).sizeof / E.sizeof;
139 
140     /** Maximum number elements that fit into large variant storage. */
141     enum maxLargeLength = size_t.max >> 8;
142 
143     /// Destruct.
144     ~this() nothrow @trusted
145     {
146         if (isLarge) { large.clear; }
147     }
148 
149     /// Get currently length at `ptr`.
150     size_t length() const @trusted pure nothrow @nogc
151     {
152         return isLarge ? large.length : smallLength;
153     }
154 
155     /// Returns: `true` iff is small packed.
156     bool isSmall() const @safe pure nothrow @nogc { return !isLarge; }
157 
158 private:
159 
160     /// Reserve length to `n` elements starting at `ptr`.
161     void reserve(size_t n) pure nothrow @trusted
162     {
163         if (isLarge)        // currently large
164         {
165             if (n > smallLength) // large => large
166             {
167                 large.resize(n);
168             }
169             else                // large => small
170             {
171                 // large => tmp
172                 typeof(small) tmp = void; // temporary storage for small
173                 tmp[0 .. n] = large.ptr[0 .. n]; // large to temporary
174                 tmp[n .. $] = 0; // zero remaining
175 
176                 // empty large
177                 large.clear();
178 
179                 // tmp => small
180                 small[] = tmp[0 .. smallLength];
181 
182                 isLarge = false;
183             }
184         }
185         else                    // currently small
186         {
187             if (n > smallLength) // small => large
188             {
189                 typeof(small) tmp = small; // temporary storage for small
190 
191                 import std.conv : emplace;
192                 emplace(&large, n);
193 
194                 large.ptr[0 .. length] = tmp[0 .. length]; // temporary to large
195 
196                 isLarge = true;                      // tag as large
197             }
198             else {}                // small => small
199         }
200     }
201 
202     /// Get pointer.
203     auto ptr() pure nothrow @nogc
204     {
205         alias ET = ContainerElementType!(typeof(this), E);
206         return isLarge ? cast(ET*)large.ptr : cast(ET*)&small;
207     }
208 
209     /// Get slice.
210     auto ref slice() pure nothrow @nogc
211     {
212         return ptr[0 .. length];
213     }
214 
215     union
216     {
217         Small!(E, smallLength) small; // small variant
218         Large!(E, useGC) large;          // large variant
219     }
220     bool isLarge;               // TODO make part of union as in rcstring.d
221 }
222 
223 /// Test `Store`.
224 static void storeTester(E, bool useGC)()
225 {
226     Store!(E, useGC) si;
227 
228     assert(si.ptr !is null);
229     assert(si.slice.ptr !is null);
230     assert(si.slice.length != 0);
231     assert(si.length == si.smallLength);
232 
233     si.reserve(si.smallLength);     // max small
234     assert(si.length == si.smallLength);
235     assert(si.isSmall);
236 
237     si.reserve(si.smallLength + 1); // small to large
238     assert(si.length == si.smallLength + 1);
239     assert(si.isLarge);
240 
241     si.reserve(si.smallLength * 8); // small to large
242     assert(si.length == si.smallLength * 8);
243     assert(si.isLarge);
244 
245     si.reserve(si.smallLength);     // max small
246     assert(si.length == si.smallLength);
247     assert(si.isSmall);
248 
249     si.reserve(0);
250     assert(si.length == si.smallLength);
251     assert(si.isSmall);
252 
253     si.reserve(si.smallLength + 1);
254     assert(si.length == si.smallLength + 1);
255     assert(si.isLarge);
256 
257     si.reserve(si.smallLength);
258     assert(si.length == si.smallLength);
259     assert(si.isSmall);
260 
261     si.reserve(si.smallLength - 1);
262     assert(si.length == si.smallLength);
263     assert(si.isSmall);
264 }
265 
266 
267 pure nothrow @nogc unittest
268 {
269     foreach (E; AliasSeq!(char, byte, short, int))
270     {
271         storeTester!(E, false);
272     }
273 }
274 
275 pure nothrow unittest
276 {
277     foreach (E; AliasSeq!(char, byte, short, int))
278     {
279         storeTester!(E, true);
280     }
281 }
282 
283 /// Returns: `true` iff C is an `Array`.
284 import std.traits : isInstanceOf;
285 enum isArray(C) = isInstanceOf!(Array, C);
286 
287 /** Small-size-optimized (SSO-packed) array of value types `E`.
288  */
289 struct Array(E,
290              Ordering ordering = Ordering.unsorted,
291              bool useGC = shouldAddGCRange!E,
292              alias less = "a < b") // TODO move out of this definition
293 {
294     import std.range : isInputRange, ElementType;
295     import std.traits : isAssignable, Unqual, isSomeChar;
296     import std.functional : binaryFun;
297     import std.meta : allSatisfy;
298 
299     import core.exception : RangeError;
300 
301     alias ME = Unqual!E; // mutable E
302     enum isString = isSomeChar!E;
303 
304     alias comp = binaryFun!less; //< comparison
305 
306     /// Maximum number of elements that fits in SSO-packed
307     enum smallLength = (_storeLength.sizeof + _length.sizeof) / E.sizeof;
308 
309     /// Returns: `true` iff is SSO-packed.
310     bool isSmall() const @safe pure nothrow @nogc { return length <= smallLength; }
311 
312     static if (useGC)
313     {
314         import core.memory : GC;
315     }
316     else
317     {
318         alias _malloc = malloc;
319         alias _realloc = realloc;
320         alias _free = free;
321     }
322 
323     /// Construct with length `n`.
324     static if (useGC)
325     {
326         this(size_t n) pure @trusted nothrow
327         {
328             _storePtr = cast(E*)GC.malloc(E.sizeof * n);
329             static if (shouldAddGCRange!E) { GC.addRange(ptr, length * E.sizeof); }
330             _length = _storeLength = n;
331             zero;
332         }
333     }
334     else
335     {
336         this(size_t n) pure nothrow @trusted @nogc
337         {
338             _storePtr = cast(E*)_malloc(E.sizeof * n);
339             static if (shouldAddGCRange!E) { GC.addRange(ptr, length * E.sizeof); }
340             _length = _storeLength = n;
341             zero;
342         }
343     }
344 
345     this(this) @disable;       /// TODO activate when internal RC-logic is ready
346 
347     void zero() @("complexity", "O(length)")
348     {
349         ptr[0 .. length] = 0; // NOTE should we zero [0 .. _storeLength] instead?
350     }
351 
352     /** Construct from InputRange `values`.
353         If `values` are sorted `assumeSortedParameter` is true.
354      */
355     this(R)(R values, bool assumeSortedParameter = false) @trusted nothrow @("complexity", "O(n*log(n))")
356         if (isInputRange!R)
357     {
358         // init
359         _storePtr = null;
360         _storeLength = 0;
361 
362         // append new data
363         import std.range : hasLength;
364         static if (hasLength!R)
365         {
366             reserve(values.length); // fast reserve
367             size_t i = 0;
368             foreach (ref value; values)
369             {
370                 ptr[i++] = value;
371             }
372             _length = values.length;
373         }
374         else
375         {
376             size_t i = 0;
377             foreach (ref value; values)
378             {
379                 reserve(i + 1); // slower reserve
380                 ptr[i++] = value;
381             }
382             _length = i;
383         }
384 
385         static if (IsOrdered!ordering)
386         {
387             if (!assumeSortedParameter)
388             {
389                 import std.algorithm.sorting : sort;
390                 sort!comp(ptr[0 .. _length]);
391             }
392         }
393     }
394 
395     /// Reserve room for `n` elements at store `_storePtr`.
396     static if (useGC)
397     {
398         void reserve(size_t n) pure nothrow @trusted
399         {
400             makeReservedLengthAtLeast(n);
401             _storePtr = cast(E*)GC.realloc(_storePtr, E.sizeof * _storeLength);
402             static if (shouldAddGCRange!E) { GC.addRange(ptr, length * E.sizeof); }
403         }
404     }
405     else
406     {
407         void reserve(size_t n) pure nothrow @trusted @nogc
408         {
409             makeReservedLengthAtLeast(n);
410             _storePtr = cast(E*)_realloc(_storePtr, E.sizeof * _storeLength);
411         }
412     }
413 
414     /// Helper for `reserve`.
415     private void makeReservedLengthAtLeast(size_t n) pure nothrow @safe @nogc
416     {
417         if (_storeLength < n) { _storeLength = n.nextPow2; }
418     }
419 
420     /// Pack/Compress storage.
421     static if (useGC)
422     {
423         void compress() pure nothrow @trusted
424         {
425             if (length)
426             {
427                 _storePtr = cast(E*)GC.realloc(_storePtr, E.sizeof * _length);
428             }
429             else
430             {
431                 GC.free(_storePtr); debug _storePtr = null;
432             }
433             _storeLength = _length;
434         }
435     }
436     else
437     {
438         void compress() pure nothrow @trusted @nogc
439         {
440             if (length)
441             {
442                 _storePtr = cast(E*)_realloc(_storePtr, E.sizeof * _storeLength);
443             }
444             else
445             {
446                 _free(_storePtr); debug _storePtr = null;
447             }
448             _storeLength = _length;
449         }
450     }
451     alias pack = compress;
452 
453     /// Destruct.
454     static if (useGC)
455     {
456         ~this() nothrow @trusted
457         {
458             static if (shouldAddGCRange!E) { GC.removeRange(ptr); }
459             GC.free(_storePtr); debug _storePtr = null;
460         }
461     }
462     else
463     {
464         ~this() nothrow @trusted @nogc
465         {
466             static if (shouldAddGCRange!E) { GC.removeRange(ptr); }
467             _free(_storePtr); debug _storePtr = null;
468         }
469     }
470 
471     enum isElementAssignable(U) = isAssignable!(E, U);
472 
473     /** Removal doesn't need to care about ordering. */
474     ContainerElementType!(typeof(this), E) linearPopAtIndex(size_t index) @trusted @("complexity", "O(length)")
475     {
476         if (index >= _length) { throw new RangeError(); }
477         checkEmptyPop;
478         typeof(return) value = ptr[index]; // TODO move construct?
479         // TODO functionize move
480         foreach (const i; 0 .. length - (index + 1)) // each element index that needs to be moved
481         {
482             const si = index + i + 1; // source index
483             const ti = index + i; // target index
484             ptr[ti] = ptr[si]; // TODO move construct?
485         }
486         --_length;
487         return value;
488     }
489     alias linearRemoveAt = linearPopAtIndex;
490     alias linearDeleteAt = linearPopAtIndex;
491 
492     /** Removal doesn't need to care about ordering. */
493     ContainerElementType!(typeof(this), E) linearPopFront() @trusted @("complexity", "O(length)")
494     {
495         checkEmptyPop;
496         typeof(return) value = ptr[0]; // TODO move construct?
497         // TODO functionize move
498         foreach (const i; 0 .. length - 1) // each element index that needs to be moved
499         {
500             const si = i + 1; // source index
501             const ti = i; // target index
502             ptr[ti] = ptr[si]; // TODO move construct?
503         }
504         --_length;
505         return value;
506     }
507 
508     /** Removal doesn't need to care about ordering. */
509     ContainerElementType!(typeof(this), E) popBack() @trusted @("complexity", "O(1)")
510     {
511         checkEmptyPop;
512         return ptr[--_length]; // TODO move construct?
513     }
514 
515     private void checkEmptyPop()
516     {
517         if (empty) { throw new Exception(`Cannot pop value from an empty array`); }
518     }
519 
520     static if (!IsOrdered!ordering) // for unsorted arrays
521     {
522         /// Push back (append) `values`.
523         void pushBack(Us...)(Us values) nothrow @("complexity", "O(1)")
524             if (values.length >= 1 &&
525                 allSatisfy!(isElementAssignable, Us))
526         {
527             pushBackHelper(values);
528         }
529         /// ditto
530         void pushBack(R)(R values) nothrow @("complexity", "O(length)")
531             if (isInputRange!R &&
532                 allSatisfy!(isElementAssignable, ElementType!R))
533         {
534             import std.range : hasLength;
535             static if (hasLength!R) { /* dln("Reuse logic in range constructor"); */ }
536             foreach (ref value; values)
537             {
538                 pushBackHelper(value);
539             }
540         }
541         /// ditto.
542         void pushBack(A)(const ref A values) @trusted nothrow @("complexity", "O(values.length)") // TODO `in` parameter qualifier doesn't work here. Compiler bug?
543             if (isArray!A &&
544                 isElementAssignable!(ElementType!A))
545         {
546             if (ptr == values.ptr) // called as: this ~= this
547             {
548                 reserve(2*length);
549                 // NOTE: this is not needed because we don't need range checking here?:
550                 // ptr[length .. 2*length] = values.ptr[0 .. length];
551                 foreach (const i; 0 .. length) { ptr[length + i] = values.ptr[i]; } // TODO move. reuse memcpy
552                 _length *= 2;
553             }
554             else
555             {
556                 reserve(length + values.length);
557                 if (is(Unqual!E == Unqual!(ElementType!A)))
558                 {
559                     // TODO reuse memcopy if ElementType!A is same as E)
560                 }
561                 foreach (const i, ref value; values.slice)
562                 {
563                     ptr[length + i] = value;
564                 }
565                 _length += values.length;
566             }
567         }
568         alias append = pushBack;
569 
570         // NOTE these separate overloads of opOpAssign are needed because one
571         // `const ref`-parameter-overload doesn't work because of compiler bug
572         // with: `this(this) @disable`
573         void opOpAssign(string op, Us...)(Us values) if (op == "~" &&
574                                                          values.length >= 1 &&
575                                                          allSatisfy!(isElementAssignable, Us))
576         {
577             pushBack(values);
578         }
579 	void opOpAssign(string op, R)(R values) if (op == "~" &&
580                                                     isInputRange!R &&
581                                                     allSatisfy!(isElementAssignable, ElementType!R))
582         {
583             pushBack(values);
584         }
585 	void opOpAssign(string op, A)(const ref A values) if (op == "~" &&
586                                                               isArray!A &&
587                                                               isElementAssignable!(ElementType!A)) { pushBack(values); }
588     }
589 
590     static if (IsOrdered!ordering)
591     {
592         import std.range : SearchPolicy;
593         import std.range : assumeSorted;
594 
595         /// Returns: `true` iff this contains `value`.
596         bool contains(U)(U value) const nothrow @nogc @("complexity", "O(log(length))")
597         {
598             return this[].contains(value);
599         }
600 
601         static if (ordering == Ordering.sortedUniqueSet)
602         {
603             /** Inserts `values` into `this` ordered set.
604                 Returns: `bool`-array with same length as `values`, where i:th
605                 `bool` value is set if `value[i]` wasn't previously in `this`.
606             */
607             bool[Us.length] linearInsert(SearchPolicy sp = SearchPolicy.binarySearch, Us...)(Us values) @("complexity", "O(length)")
608                 if (values.length >= 1 &&
609                     allSatisfy!(isElementAssignable, Us))
610             in
611             {
612                 // assert no duplicates in `values`
613                 import std.range : empty;
614                 import std.algorithm.searching : findAdjacent;
615                 import std.algorithm.sorting : sort;
616                 assert(sort([values]).findAdjacent.empty, "Parameter `values` must not contain duplicate elements");
617             }
618             body
619             {
620                 static if (values.length == 1) // faster because `contains()` followed by `completeSort()` searches array twice
621                 {
622                     static if (false)
623                     {
624                         import std.traits : CommonType;
625                         size_t[Us.length] ixs;
626                         CommonType!Us[Us.length] vs;
627                         size_t i = 0;
628                         foreach (const ref value; sort([values]))
629                         {
630                             const index = indexOf(value);
631                             if (index != size_t.max)
632                             {
633                                 ixs[i] = index;
634                                 vs[i] = value;
635                                 ++i;
636                             }
637                         }
638                         // TODO insert them in one go in reverse starting from
639                         // the end of this array
640                     }
641 
642                     auto hit = slice.assumeSorted!comp.upperBound!sp(values); // faster than `completeSort` for single value
643                     assert(length >= hit.length);
644                     const index = length - hit.length; // index after potential existing element
645                     if (index == 0 ||                // value must be put first
646                         ptr[index - 1] != values[0]) // or doesn't already exist
647                     {
648                         linearInsertAtIndexHelper(index, values);
649                         return [true];
650                     }
651                     else
652                     {
653                         return [false];
654                     }
655                 }
656                 else
657                 {
658                     import std.algorithm.sorting : completeSort;
659                     typeof(return) hits = void;
660                     size_t expandedLength = 0;
661                     const initialLength = length;
662                     foreach (const i, ref value; values)
663                     {
664                         // TODO reuse completeSort with uniqueness handling?
665                         static if (values.length == 1)
666                         {
667                             // TODO reuse single parameter overload linearUniqueInsert() and return
668                         }
669                         else
670                         {
671                             // TODO reuse completeSort with uniqueness handling?
672                         }
673                         hits[i] = !this[0 .. initialLength].contains(value);
674                         if (hits[i])
675                         {
676                             pushBackHelper(value); // NOTE: append but don't yet sort
677                             ++expandedLength;
678                         }
679                     }
680 
681                     if (expandedLength != 0)
682                     {
683                         const ix = length - expandedLength;
684                         completeSort!comp(ptr[0 .. ix].assumeSorted!comp,
685                                           ptr[ix .. length]);
686                     }
687                     return hits;
688                 }
689             }
690         }
691         else static if (ordering == Ordering.sortedValues)
692         {
693             /** Inserts `values`. */
694             void linearInsert(SearchPolicy sp = SearchPolicy.binarySearch, Us...)(Us values) @("complexity", "O(log(length))")
695                 if (values.length >= 1 &&
696                     allSatisfy!(isElementAssignable, Us))
697             {
698                 // TODO add optimization for values.length == 2
699                 static if (values.length == 1)
700                 {
701                     auto hit = slice.assumeSorted!comp.upperBound!sp(values); // faster than `completeSort` for single value
702                     linearInsertAtIndexHelper(length - hit.length, values);
703                 }
704                 else
705                 {
706                     import std.algorithm.sorting : completeSort;
707                     pushBackHelper(values); // simpler because duplicates are allowed
708                     const ix = length - values.length;
709                     completeSort!comp(ptr[0 .. ix].assumeSorted!comp,
710                                       ptr[ix .. length]);
711                 }
712             }
713         }
714         alias linsert = linearInsert;
715     }
716     else
717     {
718         /** Insert element(s) `values` at array offset `index`. */
719         void linearInsertAtIndex(Us...)(size_t index, Us values) nothrow @("complexity", "O(length)")
720             if (values.length >= 1 &&
721                 allSatisfy!(isElementAssignable, Us))
722         {
723             linearInsertAtIndexHelper(index, values);
724         }
725 
726         /** Insert element(s) `values` at the beginning. */
727         void linearPushFront(Us...)(Us values) nothrow @("complexity", "O(length)")
728             if (values.length >= 1 &&
729                 allSatisfy!(isElementAssignable, Us))
730         {
731             linearInsertAtIndex(0, values);
732         }
733 
734         alias prepend = linearPushFront;
735     }
736 
737     /** Helper function used externally for unsorted and internally for sorted. */
738     private void linearInsertAtIndexHelper(Us...)(size_t index, Us values) nothrow @("complexity", "O(length)")
739     {
740         reserve(length + values.length);
741 
742         // TODO factor this to robustCopy. It uses copy when no overlaps (my algorithm_em), iteration otherwise
743         enum usePhobosCopy = false;
744         static if (usePhobosCopy)
745         {
746             // TODO why does this fail?
747             import std.algorithm.mutation : copy;
748             copy(ptr[index ..
749                      length],        // source
750                  ptr[index + values.length ..
751                      length + values.length]); // target
752         }
753         else
754         {
755             // move second part in reverse
756             // TODO functionize move
757             foreach (const i; 0 .. length - index) // each element index that needs to be moved
758             {
759                 const si = length - 1 - i; // source index
760                 const ti = si + values.length; // target index
761                 ptr[ti] = ptr[si]; // TODO move construct?
762             }
763         }
764 
765         // set new values
766         foreach (const i, ref value; values)
767         {
768             ptr[index + i] = value; // TODO use range algorithm instead?
769         }
770 
771         _length += values.length;
772     }
773 
774     private void pushBackHelper(Us...)(Us values) nothrow @("complexity", "O(1)")
775     {
776         reserve(length + values.length);
777         size_t i = 0;
778         foreach (ref value; values)
779         {
780             ptr[length + i] = value;
781             ++i;
782         }
783         _length += values.length;
784     }
785 
786     @property @("complexity", "O(1)")
787     pragma(inline, true):
788 
789     /// ditto
790     static if (IsOrdered!ordering)
791     {
792         /// Slice operator must be const when ordered.
793         auto opSlice() const nothrow @nogc
794         {
795             return opSlice!(typeof(this))(0, _length);
796         }
797         /// ditto
798         auto opSlice(this This)(size_t i, size_t j) const nothrow @nogc // const because mutation only via `op.*Assign`
799         {
800             alias ET = ContainerElementType!(This, E);
801             import std.range : assumeSorted;
802             return (cast(ET[])slice[i .. j]).assumeSorted!comp;
803         }
804 
805         /// Index operator must be const when ordered.
806         auto ref opIndex(size_t i) const nothrow @trusted @nogc // const because mutation only via `op.*Assign`
807         {
808             alias ET = ContainerElementType!(typeof(this), E);
809             return cast(ET)slice[i];
810         }
811     }
812     else
813     {
814         /// Slice operator overload is mutable when unordered.
815         auto opSlice() nothrow @nogc
816         {
817             return this.opSlice(0, _length);
818         }
819         /// ditto
820         auto opSlice(this This)(size_t i, size_t j) nothrow @nogc
821         {
822             alias ET = ContainerElementType!(This, E);
823             return cast(ET[])slice[i .. j];
824         }
825 
826         /// Index operator overload mutable when unordered.
827         auto ref opIndex(size_t i) nothrow @trusted @nogc
828         {
829             alias ET = ContainerElementType!(typeof(this), E);
830             return cast(ET)slice[i];
831         }
832     }
833 
834     /// Get front element.
835     E front() const @trusted
836     {
837         if (empty) { throw new RangeError(); }
838         return ptr[0];
839     }
840 
841     pure nothrow @nogc:
842 
843     /// Check if empty.
844     bool empty() const @safe
845     {
846         return _length == 0;
847     }
848 
849     /// Get length.
850     size_t length() const @safe
851     {
852         return _length;
853     }
854     alias opDollar = length;    ///< ditto
855 
856     /// Get length of reserved store.
857     size_t reservedLength() const @safe
858     {
859         return _storeLength;
860     }
861 
862     /// Get internal pointer.
863     private inout(E*) ptr() inout
864     {
865         // TODO Use cast(ET[])?: alias ET = ContainerElementType!(typeof(this), E);
866         return _storePtr;
867     }
868 
869     /// Get internal slice.
870     private auto ref slice() inout
871     {
872         return ptr[0 .. length];
873     }
874 
875     // TODO reuse Store store
876     E* _storePtr;               // store
877     size_t _storeLength;        // store length
878 
879     size_t _length;             // length
880 }
881 
882 static void tester(Ordering ordering, bool supportGC, alias less)()
883 {
884     import std.functional : binaryFun;
885     import std.range : iota, retro, chain, repeat, only, ElementType;
886     import std.algorithm : filter, map;
887     import std.algorithm.sorting : isSorted, sort;
888     import std.exception : assertThrown, assertNotThrown;
889     import std.traits : isInstanceOf;
890 
891     alias comp = binaryFun!less; //< comparison
892 
893     alias E = int;
894     alias A = Array;
895 
896     foreach (Ch; AliasSeq!(char, wchar, dchar))
897     {
898         alias Str = A!(Ch, ordering, supportGC, less);
899         Str str;
900         static assert(is(ElementType!Str == Ch));
901         static assert(str.isString);
902     }
903 
904     static if (E.sizeof == 4)
905     {
906         foreach (n; [0, 1, 2, 3, 4])
907         {
908             assert(A!(E, ordering, supportGC, less)(n).isSmall);
909         }
910         assert(!(A!(E, ordering, supportGC, less)(5).isSmall));
911     }
912 
913     foreach (const n; chain(0.only,
914                             iota(0, 10).map!(x => 2^^x)))
915     {
916         import std.array : array;
917         import std.range : radial, retro;
918 
919         const zi = cast(int)0;
920         const ni = cast(int)n;
921 
922         auto fw = iota(zi, ni); // 0, 1, 2, ..., n-1
923 
924         // TODO use radial instead
925         auto bw = fw.array.radial;
926 
927         A!(E, ordering, supportGC, less) ss0 = bw; // reversed
928         static assert(is(ElementType!(typeof(ss0)) == E));
929         static assert(isInstanceOf!(Array, typeof(ss0)));
930         assert(ss0.length == n);
931 
932         static if (IsOrdered!ordering)
933         {
934             if (!ss0.empty) { assert(ss0[0] == ss0[0]); } // trigger use of opindex
935             assert(ss0[].equal(fw.array.sort!comp));
936             assert(ss0[].isSorted!comp);
937         }
938 
939         A!(E, ordering, supportGC, less) ss1 = fw; // ordinary
940         assert(ss1.length == n);
941 
942         static if (IsOrdered!ordering)
943         {
944             assert(ss1[].equal(fw.array.sort!comp));
945             assert(ss1[].isSorted!comp);
946         }
947 
948         A!(E, ordering, supportGC, less) ss2 = fw.filter!(x => x & 1);
949         assert(ss2.length == n/2);
950 
951         static if (IsOrdered!ordering)
952         {
953             assert(ss2[].equal(fw.filter!(x => x & 1).array.sort!comp));
954             assert(ss2[].isSorted!comp);
955         }
956 
957         auto ss32 = A!(E, ordering, supportGC, less)(32);
958 
959         auto ssA = A!(E, ordering, supportGC, less)(0);
960         static if (IsOrdered!ordering)
961         {
962             foreach (i; bw)
963             {
964                 static if (ordering == Ordering.sortedUniqueSet)
965                 {
966                     assert(ssA.linearInsert(i)[].equal([true]));
967                     assert(ssA.linearInsert(i)[].equal([false]));
968                 }
969                 else
970                 {
971                     ssA.linearInsert(i);
972                 }
973             }
974             assert(ssA[].equal(sort!comp(fw.array)));
975 
976             auto ssB = A!(E, ordering, supportGC, less)(0);
977             static if (ordering == Ordering.sortedUniqueSet)
978             {
979                 assert(ssB.linearInsert(1, 7, 4, 9)[].equal(true.repeat(4)));
980                 assert(ssB.linearInsert(3, 6, 8, 5, 1, 9)[].equal([true, true, true, true, false, false]));
981                 assert(ssB.linearInsert(3, 0, 2, 10, 11, 5)[].equal([false, true, true, true, true, false]));
982                 assert(ssB.linearInsert(0, 2, 10, 11)[].equal(false.repeat(4))); // false becuse already inserted
983                 assert(ssB.reservedLength == 16);
984             }
985             else
986             {
987                 ssB.linearInsert(1, 7, 4, 9);
988                 ssB.linearInsert(3, 6, 8, 5);
989                 ssB.linearInsert(0, 2, 10, 11);
990                 assert(ssB.reservedLength == 16);
991             }
992 
993             auto ssI = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11].sort!comp; // values
994             const ssO = [12, 13]; // values not range
995 
996             assert(ssB[].equal(ssI));
997 
998             foreach (s; ssI) { assert(ssB.contains(s)); }
999             foreach (s; ssO) { assert(!ssB.contains(s)); }
1000 
1001             ssB.compress;
1002             assert(ssB.reservedLength == 12);
1003         }
1004         else
1005         {
1006             ssA ~= 3;
1007             ssA ~= 2;
1008             ssA ~= 1;
1009             assert(ssA[].equal([3, 2, 1]));
1010             assert(ssA.reservedLength == 4);
1011 
1012             ssA.compress;
1013             assert(ssA.reservedLength == 3);
1014 
1015             // popBack
1016             ssA[0] = 1;
1017             ssA[1] = 2;
1018             assert(ssA[].equal([1, 2, 1]));
1019             assert(!ssA.empty);
1020             assert(ssA.front == 1);
1021 
1022             assertNotThrown(ssA.popBack);
1023             assert(ssA[].equal([1, 2]));
1024             assert(!ssA.empty);
1025             assert(ssA.front == 1);
1026 
1027             assertNotThrown(ssA.popBack);
1028             assert(ssA[].equal([1]));
1029             assert(!ssA.empty);
1030             assert(ssA.front == 1);
1031 
1032             assertNotThrown(ssA.popBack);
1033             assert(ssA.length == 0);
1034             assert(ssA.empty);
1035             assert(ssA.reservedLength != 0);
1036 
1037             ssA.compress;
1038             assert(ssA.length == 0);
1039             assert(ssA.reservedLength == 0);
1040             assert(ssA.empty);
1041             assert(ssA.ptr is null);
1042 
1043             // linearInsertAt
1044             ssA ~= 1;
1045             ssA ~= 2;
1046             ssA ~= 3;
1047             ssA ~= 4;
1048             ssA ~= 5;
1049             ssA ~= 6;
1050             ssA ~= 7;
1051             ssA ~= 8;
1052             assert(ssA[].equal([1, 2, 3, 4, 5, 6, 7, 8]));
1053             ssA.linearInsertAtIndex(3, 100, 101);
1054             assert(ssA[].equal([1, 2, 3, 100, 101, 4, 5, 6, 7, 8]));
1055             assertNotThrown(ssA.linearPopFront);
1056             assert(ssA[].equal([2, 3, 100, 101, 4, 5, 6, 7, 8]));
1057             assertNotThrown(ssA.linearPopFront);
1058             assert(ssA[].equal([3, 100, 101, 4, 5, 6, 7, 8]));
1059             assertNotThrown(ssA.linearPopFront);
1060             assert(ssA[].equal([100, 101, 4, 5, 6, 7, 8]));
1061             assertNotThrown(ssA.linearPopFront);
1062             assertNotThrown(ssA.linearPopFront);
1063             assertNotThrown(ssA.linearPopFront);
1064             assertNotThrown(ssA.linearPopFront);
1065             assertNotThrown(ssA.linearPopFront);
1066             assertNotThrown(ssA.linearPopFront);
1067             assertNotThrown(ssA.linearPopFront);
1068             assert(ssA.empty);
1069             ssA.compress;
1070             assert(ssA.ptr is null);
1071 
1072             // linearPopAtIndex
1073             ssA ~= 1;
1074             ssA ~= 2;
1075             ssA ~= 3;
1076             ssA ~= 4;
1077             ssA ~= 5;
1078             assertNotThrown(ssA.linearPopAtIndex(2));
1079             assert(ssA[].equal([1, 2, 4, 5]));
1080 
1081             // pushBack and assignment from slice
1082             auto ssB = A!(E, ordering, supportGC, less)(0);
1083             ssB.pushBack([1, 2, 3, 4, 5]);
1084             ssB.pushBack([6, 7]);
1085             assert(ssB[].equal([1, 2, 3, 4, 5, 6, 7]));
1086 
1087             // pushBack(Array)
1088             {
1089                 const s = [1, 2, 3];
1090                 A!(E, ordering, supportGC, less) s1 = s;
1091                 A!(E, ordering, supportGC, less) s2 = s1[];
1092                 assert(s1[].equal(s));
1093                 s1 ~= s1;
1094                 assert(s1[].equal(chain(s, s)));
1095                 s1 ~= s2;
1096                 assert(s1[].equal(chain(s, s, s)));
1097             }
1098         }
1099     }
1100 }
1101 
1102 /// use GC
1103 pure nothrow unittest
1104 {
1105     import std.traits : EnumMembers;
1106     foreach (ordering; EnumMembers!Ordering)
1107     {
1108         tester!(ordering, true, "a < b"); // use GC
1109         tester!(ordering, true, "a > b"); // use GC
1110     }
1111 }
1112 
1113 /// don't use GC
1114 pure nothrow /+TODO @nogc+/ unittest
1115 {
1116     import std.traits : EnumMembers;
1117     foreach (ordering; EnumMembers!Ordering)
1118     {
1119         tester!(ordering, false, "a < b"); // don't use GC
1120         tester!(ordering, false, "a > b"); // don't use GC
1121     }
1122 }
1123 
1124 template ContainerElementType(ContainerType, ElementType)
1125 {
1126     import std.traits : isMutable, hasIndirections, PointerTarget, isPointer, Unqual;
1127 
1128     template ET(bool isConst, T)
1129     {
1130         static if (isPointer!ElementType)
1131         {
1132             enum PointerIsConst = is(ElementType == const);
1133             enum PointerIsImmutable = is(ElementType == immutable);
1134             enum DataIsConst = is(PointerTarget!ElementType == const);
1135             enum DataIsImmutable = is(PointerTarget!ElementType == immutable);
1136             static if (isConst)
1137             {
1138                 static if (PointerIsConst)
1139                     alias ET = ElementType;
1140                 else static if (PointerIsImmutable)
1141                     alias ET = ElementType;
1142                 else
1143                     alias ET = const(PointerTarget!ElementType)*;
1144             }
1145             else
1146             {
1147                 static assert(DataIsImmutable, "An immutable container cannot reference const or mutable data");
1148                 static if (PointerIsConst)
1149                     alias ET = immutable(PointerTarget!ElementType)*;
1150                 else
1151                     alias ET = ElementType;
1152             }
1153         }
1154         else
1155         {
1156             static if (isConst)
1157             {
1158                 static if (is(ElementType == immutable))
1159                     alias ET = ElementType;
1160                 else
1161                     alias ET = const(Unqual!ElementType);
1162             }
1163             else
1164                 alias ET = immutable(Unqual!ElementType);
1165         }
1166     }
1167 
1168     static if (isMutable!ContainerType)
1169         alias ContainerElementType = ElementType;
1170     else
1171     {
1172         static if (hasIndirections!ElementType)
1173             alias ContainerElementType = ET!(is(ContainerType == const), ElementType);
1174         else
1175             alias ContainerElementType = ElementType;
1176     }
1177 }