diff --git a/bower.json b/bower.json index b91431cc..a8fc8a4c 100644 --- a/bower.json +++ b/bower.json @@ -16,7 +16,7 @@ "package.json" ], "dependencies": { - "purescript-foldable-traversable": "^3.0.0", + "purescript-foldable-traversable": "^3.3.0", "purescript-nonempty": "^4.0.0", "purescript-partial": "^1.2.0", "purescript-st": "^3.0.0", diff --git a/src/Data/Array/NonEmpty.js b/src/Data/Array/NonEmpty.js new file mode 100644 index 00000000..0971fc45 --- /dev/null +++ b/src/Data/Array/NonEmpty.js @@ -0,0 +1,77 @@ +"use strict"; + +exports.fold1Impl = function (f) { + return function (xs) { + var acc = xs[0]; + var len = xs.length; + for (var i = 1; i < len; i++) { + acc = f(acc)(xs[i]); + } + return acc; + }; +}; + +exports.traverse1Impl = function () { + function Cont(fn) { + this.fn = fn; + } + + var emptyList = {}; + + var ConsCell = function (head, tail) { + this.head = head; + this.tail = tail; + }; + + function finalCell(head) { + return new ConsCell(head, emptyList); + } + + function consList(x) { + return function (xs) { + return new ConsCell(x, xs); + }; + } + + function listToArray(list) { + var arr = []; + var xs = list; + while (xs !== emptyList) { + arr.push(xs.head); + xs = xs.tail; + } + return arr; + } + + return function (apply) { + return function (map) { + return function (f) { + var buildFrom = function (x, ys) { + return apply(map(consList)(f(x)))(ys); + }; + + var go = function (acc, currentLen, xs) { + if (currentLen === 0) { + return acc; + } else { + var last = xs[currentLen - 1]; + return new Cont(function () { + var built = go(buildFrom(last, acc), currentLen - 1, xs); + return built; + }); + } + }; + + return function (array) { + var acc = map(finalCell)(f(array[array.length - 1])); + var result = go(acc, array.length - 1, array); + while (result instanceof Cont) { + result = result.fn(); + } + + return map(listToArray)(result); + }; + }; + }; + }; +}(); diff --git a/src/Data/Array/NonEmpty.purs b/src/Data/Array/NonEmpty.purs new file mode 100644 index 00000000..65921840 --- /dev/null +++ b/src/Data/Array/NonEmpty.purs @@ -0,0 +1,478 @@ +module Data.Array.NonEmpty + ( NonEmptyArray + , fromArray + , fromNonEmpty + , toArray + , toNonEmpty + + , fromFoldable + , fromFoldable1 + , toUnfoldable + , singleton + , (..), range + , replicate + , some + + , length + + , (:), cons + , cons' + , snoc + , snoc' + , appendArray + , insert + , insertBy + + , head + , last + , tail + , init + , uncons + , unsnoc + + , (!!), index + , elemIndex + , elemLastIndex + , findIndex + , findLastIndex + , insertAt + , deleteAt + , updateAt + , updateAtIndices + , modifyAt + , modifyAtIndices + , alterAt + + , reverse + , concat + , concatMap + , filter + , partition + , filterA + , mapMaybe + , catMaybes + + , sort + , sortBy + , sortWith + , slice + , take + , takeEnd + , takeWhile + , drop + , dropEnd + , dropWhile + , span + + , nub + , nubBy + , union + , union' + , unionBy + , unionBy' + , delete + , deleteBy + + , (\\), difference + , difference' + , intersect + , intersect' + , intersectBy + , intersectBy' + + , zipWith + , zipWithA + , zip + , unzip + + , foldM + , foldRecM + + , unsafeIndex + ) where + +import Prelude + +import Control.Alt (class Alt) +import Control.Alternative (class Alternative) +import Control.Lazy (class Lazy) +import Control.Monad.Rec.Class (class MonadRec) +import Data.Array as A +import Data.Bifunctor (bimap) +import Data.Eq (class Eq1) +import Data.Foldable (class Foldable) +import Data.FoldableWithIndex (class FoldableWithIndex) +import Data.FunctorWithIndex (class FunctorWithIndex) +import Data.Maybe (Maybe(..), fromJust) +import Data.NonEmpty (NonEmpty, (:|)) +import Data.Ord (class Ord1) +import Data.Semigroup.Foldable (class Foldable1, foldMap1Default) +import Data.Semigroup.Traversable (class Traversable1, sequence1Default) +import Data.Traversable (class Traversable) +import Data.TraversableWithIndex (class TraversableWithIndex) +import Data.Tuple (Tuple) +import Data.Unfoldable (class Unfoldable) +import Partial.Unsafe (unsafePartial) + +newtype NonEmptyArray a = NonEmptyArray (Array a) + +instance showNonEmptyArray :: Show a => Show (NonEmptyArray a) where + show (NonEmptyArray xs) = "(NonEmptyArray " <> show xs <> ")" + +derive newtype instance eqNonEmptyArray :: Eq a => Eq (NonEmptyArray a) +derive newtype instance eq1NonEmptyArray :: Eq1 NonEmptyArray + +derive newtype instance ordNonEmptyArray :: Ord a => Ord (NonEmptyArray a) +derive newtype instance ord1NonEmptyArray :: Ord1 NonEmptyArray + +derive newtype instance functorNonEmptyArray :: Functor NonEmptyArray +derive newtype instance functorWithIndexNonEmptyArray :: FunctorWithIndex Int NonEmptyArray + +derive newtype instance foldableNonEmptyArray :: Foldable NonEmptyArray +derive newtype instance foldableWithIndexNonEmptyArray :: FoldableWithIndex Int NonEmptyArray + +instance foldable1NonEmptyArray :: Foldable1 NonEmptyArray where + foldMap1 = foldMap1Default + fold1 = fold1Impl (<>) + +derive newtype instance traversableNonEmptyArray :: Traversable NonEmptyArray +derive newtype instance traversableWithIndexNonEmptyArray :: TraversableWithIndex Int NonEmptyArray + +instance traversable1NonEmptyArray :: Traversable1 NonEmptyArray where + traverse1 = traverse1Impl apply map + sequence1 = sequence1Default + +derive newtype instance applyNonEmptyArray :: Apply NonEmptyArray + +derive newtype instance applicativeNonEmptyArray :: Applicative NonEmptyArray + +derive newtype instance bindNonEmptyArray :: Bind NonEmptyArray + +derive newtype instance monadNonEmptyArray :: Monad NonEmptyArray + +derive newtype instance altNonEmptyArray :: Alt NonEmptyArray + +-- | Internal - adapt an Array transform to NonEmptyArray +-- +-- Note that this is unsafe: if the transform returns an empty array, this can +-- explode at runtime. +unsafeAdapt :: forall a b. (Array a -> Array b) -> NonEmptyArray a -> NonEmptyArray b +unsafeAdapt f = NonEmptyArray <<< adaptAny f + +-- | Internal - adapt an Array transform to NonEmptyArray, +-- with polymorphic result. +-- +-- Note that this is unsafe: if the transform returns an empty array, this can +-- explode at runtime. +adaptAny :: forall a b. (Array a -> b) -> NonEmptyArray a -> b +adaptAny f = f <<< toArray + +-- | Internal - adapt Array functions returning Maybes to NonEmptyArray +adaptMaybe :: forall a b. (Array a -> Maybe b) -> NonEmptyArray a -> b +adaptMaybe f = unsafePartial $ fromJust <<< f <<< toArray + +fromArray :: forall a. Array a -> Maybe (NonEmptyArray a) +fromArray xs + | A.length xs > 0 = Just (NonEmptyArray xs) + | otherwise = Nothing + +-- | INTERNAL +unsafeFromArray :: forall a. Array a -> NonEmptyArray a +unsafeFromArray = NonEmptyArray + +fromNonEmpty :: forall a. NonEmpty Array a -> NonEmptyArray a +fromNonEmpty (x :| xs) = cons' x xs + +toArray :: forall a. NonEmptyArray a -> Array a +toArray (NonEmptyArray xs) = xs + +toNonEmpty :: forall a. NonEmptyArray a -> NonEmpty Array a +toNonEmpty = uncons >>> \{head: x, tail: xs} -> x :| xs + +fromFoldable :: forall f a. Foldable f => f a -> Maybe (NonEmptyArray a) +fromFoldable = fromArray <<< A.fromFoldable + +fromFoldable1 :: forall f a. Foldable1 f => f a -> NonEmptyArray a +fromFoldable1 = unsafeFromArray <<< A.fromFoldable + +toUnfoldable :: forall f a. Unfoldable f => NonEmptyArray a -> f a +toUnfoldable = adaptAny A.toUnfoldable + +singleton :: forall a. a -> NonEmptyArray a +singleton = NonEmptyArray <<< A.singleton + +range :: Int -> Int -> NonEmptyArray Int +range x y = unsafeFromArray $ A.range x y + +infix 8 range as .. + +-- | Replicate an item at least once +replicate :: forall a. Int -> a -> NonEmptyArray a +replicate i x = NonEmptyArray $ A.replicate (max 1 i) x + +some + :: forall f a + . Alternative f + => Lazy (f (Array a)) + => f a -> f (NonEmptyArray a) +some = map NonEmptyArray <<< A.some + +length :: forall a. NonEmptyArray a -> Int +length = adaptAny A.length + +cons :: forall a. a -> NonEmptyArray a -> NonEmptyArray a +cons x = unsafeAdapt $ A.cons x + +infixr 6 cons as : + +cons' :: forall a. a -> Array a -> NonEmptyArray a +cons' x xs = unsafeFromArray $ A.cons x xs + +snoc :: forall a. NonEmptyArray a -> a -> NonEmptyArray a +snoc xs x = unsafeFromArray $ A.snoc (toArray xs) x + +snoc' :: forall a. Array a -> a -> NonEmptyArray a +snoc' xs x = unsafeFromArray $ A.snoc xs x + +appendArray :: forall a. NonEmptyArray a -> Array a -> NonEmptyArray a +appendArray xs ys = unsafeFromArray $ toArray xs <> ys + +insert :: forall a. Ord a => a -> NonEmptyArray a -> NonEmptyArray a +insert x = unsafeAdapt $ A.insert x + +insertBy :: forall a. (a -> a -> Ordering) -> a -> NonEmptyArray a -> NonEmptyArray a +insertBy f x = unsafeAdapt $ A.insertBy f x + +head :: forall a. NonEmptyArray a -> a +head = adaptMaybe A.head + +last :: forall a. NonEmptyArray a -> a +last = adaptMaybe A.last + +tail :: forall a. NonEmptyArray a -> Array a +tail = adaptMaybe A.tail + +init :: forall a. NonEmptyArray a -> Array a +init = adaptMaybe A.init + +uncons :: forall a. NonEmptyArray a -> { head :: a, tail :: Array a } +uncons = adaptMaybe A.uncons + +unsnoc :: forall a. NonEmptyArray a -> { init :: Array a, last :: a } +unsnoc = adaptMaybe A.unsnoc + +index :: forall a. NonEmptyArray a -> Int -> Maybe a +index = adaptAny A.index + +infixl 8 index as !! + +elemIndex :: forall a. Eq a => a -> NonEmptyArray a -> Maybe Int +elemIndex x = adaptAny $ A.elemIndex x + +elemLastIndex :: forall a. Eq a => a -> NonEmptyArray a -> Maybe Int +elemLastIndex x = adaptAny $ A.elemLastIndex x + +findIndex :: forall a. (a -> Boolean) -> NonEmptyArray a -> Maybe Int +findIndex x = adaptAny $ A.findIndex x + +findLastIndex :: forall a. (a -> Boolean) -> NonEmptyArray a -> Maybe Int +findLastIndex x = adaptAny $ A.findLastIndex x + +insertAt :: forall a. Int -> a -> NonEmptyArray a -> Maybe (NonEmptyArray a) +insertAt i x = map NonEmptyArray <<< A.insertAt i x <<< toArray + +deleteAt :: forall a. Int -> NonEmptyArray a -> Maybe (Array a) +deleteAt i = adaptAny $ A.deleteAt i + +updateAt :: forall a. Int -> a -> NonEmptyArray a -> Maybe (NonEmptyArray a) +updateAt i x = map NonEmptyArray <<< A.updateAt i x <<< toArray + +updateAtIndices :: forall t a. Foldable t => t (Tuple Int a) -> NonEmptyArray a -> NonEmptyArray a +updateAtIndices pairs = unsafeAdapt $ A.updateAtIndices pairs + +modifyAt :: forall a. Int -> (a -> a) -> NonEmptyArray a -> Maybe (NonEmptyArray a) +modifyAt i f = map NonEmptyArray <<< A.modifyAt i f <<< toArray + +modifyAtIndices :: forall t a. Foldable t => t Int -> (a -> a) -> NonEmptyArray a -> NonEmptyArray a +modifyAtIndices is f = unsafeAdapt $ A.modifyAtIndices is f + +alterAt :: forall a. Int -> (a -> Maybe a) -> NonEmptyArray a -> Maybe (Array a) +alterAt i f = A.alterAt i f <<< toArray + +reverse :: forall a. NonEmptyArray a -> NonEmptyArray a +reverse = unsafeAdapt A.reverse + +concat :: forall a. NonEmptyArray (NonEmptyArray a) -> NonEmptyArray a +concat = NonEmptyArray <<< A.concat <<< toArray <<< map toArray + +concatMap :: forall a b. (a -> NonEmptyArray b) -> NonEmptyArray a -> NonEmptyArray b +concatMap = flip bind + +filter :: forall a. (a -> Boolean) -> NonEmptyArray a -> Array a +filter f = adaptAny $ A.filter f + +partition + :: forall a + . (a -> Boolean) + -> NonEmptyArray a + -> { yes :: Array a, no :: Array a} +partition f = adaptAny $ A.partition f + +filterA + :: forall a f + . Applicative f + => (a -> f Boolean) + -> NonEmptyArray a + -> f (Array a) +filterA f = adaptAny $ A.filterA f + +mapMaybe :: forall a b. (a -> Maybe b) -> NonEmptyArray a -> Array b +mapMaybe f = adaptAny $ A.mapMaybe f + +catMaybes :: forall a. NonEmptyArray (Maybe a) -> Array a +catMaybes = adaptAny A.catMaybes + +sort :: forall a. Ord a => NonEmptyArray a -> NonEmptyArray a +sort = unsafeAdapt A.sort + +sortBy :: forall a. (a -> a -> Ordering) -> NonEmptyArray a -> NonEmptyArray a +sortBy f = unsafeAdapt $ A.sortBy f + +sortWith :: forall a b. Ord b => (a -> b) -> NonEmptyArray a -> NonEmptyArray a +sortWith f = unsafeAdapt $ A.sortWith f + +slice :: forall a. Int -> Int -> NonEmptyArray a -> Array a +slice start end = adaptAny $ A.slice start end + +take :: forall a. Int -> NonEmptyArray a -> Array a +take i = adaptAny $ A.take i + +takeEnd :: forall a. Int -> NonEmptyArray a -> Array a +takeEnd i = adaptAny $ A.takeEnd i + +takeWhile :: forall a. (a -> Boolean) -> NonEmptyArray a -> Array a +takeWhile f = adaptAny $ A.takeWhile f + +drop :: forall a. Int -> NonEmptyArray a -> Array a +drop i = adaptAny $ A.drop i + +dropEnd :: forall a. Int -> NonEmptyArray a -> Array a +dropEnd i = adaptAny $ A.dropEnd i + +dropWhile :: forall a. (a -> Boolean) -> NonEmptyArray a -> Array a +dropWhile f = adaptAny $ A.dropWhile f + +span + :: forall a + . (a -> Boolean) + -> NonEmptyArray a + -> { init :: Array a, rest :: Array a } +span f = adaptAny $ A.span f + +nub :: forall a. Eq a => NonEmptyArray a -> NonEmptyArray a +nub = unsafeAdapt A.nub + +nubBy :: forall a. (a -> a -> Boolean) -> NonEmptyArray a -> NonEmptyArray a +nubBy f = unsafeAdapt $ A.nubBy f + +union :: forall a. Eq a => NonEmptyArray a -> NonEmptyArray a -> NonEmptyArray a +union = unionBy (==) + +union' :: forall a. Eq a => NonEmptyArray a -> Array a -> NonEmptyArray a +union' = unionBy' (==) + +unionBy + :: forall a + . (a -> a -> Boolean) + -> NonEmptyArray a + -> NonEmptyArray a + -> NonEmptyArray a +unionBy eq xs = unionBy' eq xs <<< toArray + +unionBy' + :: forall a + . (a -> a -> Boolean) + -> NonEmptyArray a + -> Array a + -> NonEmptyArray a +unionBy' eq xs = unsafeFromArray <<< A.unionBy eq (toArray xs) + +delete :: forall a. Eq a => a -> NonEmptyArray a -> Array a +delete x = adaptAny $ A.delete x + +deleteBy :: forall a. (a -> a -> Boolean) -> a -> NonEmptyArray a -> Array a +deleteBy f x = adaptAny $ A.deleteBy f x + +difference :: forall a. Eq a => NonEmptyArray a -> NonEmptyArray a -> Array a +difference xs = adaptAny $ difference' xs + +difference' :: forall a. Eq a => NonEmptyArray a -> Array a -> Array a +difference' xs = A.difference $ toArray xs + +intersect :: forall a . Eq a => NonEmptyArray a -> NonEmptyArray a -> Array a +intersect = intersectBy eq + +intersect' :: forall a . Eq a => NonEmptyArray a -> Array a -> Array a +intersect' = intersectBy' eq + +intersectBy + :: forall a + . (a -> a -> Boolean) + -> NonEmptyArray a + -> NonEmptyArray a + -> Array a +intersectBy eq xs = intersectBy' eq xs <<< toArray + +intersectBy' + :: forall a + . (a -> a -> Boolean) + -> NonEmptyArray a + -> Array a + -> Array a +intersectBy' eq xs = A.intersectBy eq (toArray xs) + +infix 5 difference as \\ + +zipWith + :: forall a b c + . (a -> b -> c) + -> NonEmptyArray a + -> NonEmptyArray b + -> NonEmptyArray c +zipWith f xs ys = NonEmptyArray $ A.zipWith f (toArray xs) (toArray ys) + + +zipWithA + :: forall m a b c + . Applicative m + => (a -> b -> m c) + -> NonEmptyArray a + -> NonEmptyArray b + -> m (NonEmptyArray c) +zipWithA f xs ys = NonEmptyArray <$> A.zipWithA f (toArray xs) (toArray ys) + +zip :: forall a b. NonEmptyArray a -> NonEmptyArray b -> NonEmptyArray (Tuple a b) +zip xs ys = NonEmptyArray $ toArray xs `A.zip` toArray ys + +unzip :: forall a b. NonEmptyArray (Tuple a b) -> Tuple (NonEmptyArray a) (NonEmptyArray b) +unzip = bimap NonEmptyArray NonEmptyArray <<< A.unzip <<< toArray + +foldM :: forall m a b. Monad m => (a -> b -> m a) -> a -> NonEmptyArray b -> m a +foldM f acc = adaptAny $ A.foldM f acc + +foldRecM :: forall m a b. MonadRec m => (a -> b -> m a) -> a -> NonEmptyArray b -> m a +foldRecM f acc = adaptAny $ A.foldRecM f acc + +unsafeIndex :: forall a. Partial => NonEmptyArray a -> Int -> a +unsafeIndex = adaptAny A.unsafeIndex + +-- we use FFI here to avoid the unnecessary copy created by `tail` +foreign import fold1Impl :: forall a. (a -> a -> a) -> NonEmptyArray a -> a + +foreign import traverse1Impl + :: forall m a b + . (forall a' b'. (m (a' -> b') -> m a' -> m b')) + -> (forall a' b'. (a' -> b') -> m a' -> m b') + -> (a -> m b) + -> NonEmptyArray a + -> m (NonEmptyArray b) diff --git a/test/Test/Data/Array/NonEmpty.purs b/test/Test/Data/Array/NonEmpty.purs new file mode 100644 index 00000000..1b92db8b --- /dev/null +++ b/test/Test/Data/Array/NonEmpty.purs @@ -0,0 +1,302 @@ +module Test.Data.Array.NonEmpty (testNonEmptyArray) where + +import Prelude + +import Control.Monad.Eff (Eff) +import Control.Monad.Eff.Console (CONSOLE, log) +import Data.Array.NonEmpty as NEA +import Data.Const (Const(..)) +import Data.Foldable (for_, sum, traverse_) +import Data.FunctorWithIndex (mapWithIndex) +import Data.Maybe (Maybe(..), fromJust) +import Data.Monoid.Additive (Additive(..)) +import Data.Semigroup.Foldable (foldMap1) +import Data.Semigroup.Traversable (traverse1) +import Data.Tuple (Tuple(..)) +import Partial.Unsafe (unsafePartial) +import Test.Assert (ASSERT, assert) + +testNonEmptyArray :: forall eff. Eff (console :: CONSOLE, assert :: ASSERT | eff) Unit +testNonEmptyArray = do + let fromArray :: forall a. Array a -> NEA.NonEmptyArray a + fromArray = unsafePartial fromJust <<< NEA.fromArray + + log "singleton should construct an array with a single value" + assert $ NEA.toArray (NEA.singleton 1) == [1] + assert $ NEA.toArray (NEA.singleton "foo") == ["foo"] + + log "range should create an inclusive array of integers for the specified start and end" + assert $ NEA.toArray (NEA.range 0 5) == [0, 1, 2, 3, 4, 5] + assert $ NEA.toArray (NEA.range 2 (-3)) == [2, 1, 0, -1, -2, -3] + assert $ NEA.toArray (NEA.range 0 0) == [0] + + log "replicate should produce an array containg an item a specified number of times" + assert $ NEA.toArray (NEA.replicate 3 true) == [true, true, true] + assert $ NEA.toArray (NEA.replicate 1 "foo") == ["foo"] + assert $ NEA.toArray (NEA.replicate 0 "foo") == ["foo"] + assert $ NEA.toArray (NEA.replicate (-1) "foo") == ["foo"] + + log "length should return the number of items in an array" + assert $ NEA.length (NEA.singleton 1) == 1 + assert $ NEA.length (fromArray [1, 2, 3, 4, 5]) == 5 + + log "cons should add an item to the start of an array" + assert $ NEA.cons 4 (fromArray [1, 2, 3]) == fromArray [4, 1, 2, 3] + assert $ NEA.cons' 4 [1, 2, 3] == fromArray [4, 1, 2, 3] + + log "snoc should add an item to the end of an array" + assert $ fromArray [1, 2, 3] `NEA.snoc` 4 == fromArray [1, 2, 3, 4] + assert $ [1, 2, 3] `NEA.snoc'` 4 == fromArray [1, 2, 3, 4] + + log "insert should add an item at the appropriate place in a sorted array" + assert $ NEA.insert 1.5 (fromArray [1.0, 2.0, 3.0]) + == fromArray [1.0, 1.5, 2.0, 3.0] + assert $ NEA.insert 4 (fromArray [1, 2, 3]) == fromArray [1, 2, 3, 4] + + log "insertBy should add an item at the appropriate place in a sorted array using the specified comparison" + assert $ NEA.insertBy (flip compare) 1.5 (fromArray [1.0, 2.0, 3.0]) + == fromArray [1.0, 2.0, 3.0, 1.5] + + log "head should return the first value of a non-empty array" + assert $ NEA.head (fromArray ["foo", "bar"]) == "foo" + + log "last should return the last value of a non-empty array" + assert $ NEA.last (fromArray ["foo", "bar"]) == "bar" + + log "tail should return an array containing all the items in an array apart from the first for a non-empty array" + assert $ NEA.tail (fromArray ["foo", "bar", "baz"]) == ["bar", "baz"] + + log "init should return an array containing all the items in an array apart from the first for a non-empty array" + assert $ NEA.init (fromArray ["foo", "bar", "baz"]) == ["foo", "bar"] + + log "uncons should split an array into a head and tail record" + let u1 = NEA.uncons $ NEA.singleton 1 + assert $ u1.head == 1 + assert $ u1.tail == [] + let u2 = NEA.uncons $ fromArray [1, 2, 3] + assert $ u2.head == 1 + assert $ u2.tail == [2, 3] + + log "unsnoc should split an array into an init and last record" + let u3 = NEA.unsnoc $ NEA.singleton 1 + assert $ u3.init == [] + assert $ u3.last == 1 + let u4 = NEA.unsnoc $ fromArray [1, 2, 3] + assert $ u4.init == [1, 2] + assert $ u4.last == 3 + + log "index should return Just x when the index is within the bounds of the array" + assert $ NEA.index (fromArray [1, 2, 3]) 0 == Just 1 + assert $ NEA.index (fromArray [1, 2, 3]) 1 == Just 2 + assert $ NEA.index (fromArray [1, 2, 3]) 2 == Just 3 + + log "index should return Nothing when the index is outside of the bounds of the array" + assert $ NEA.index (fromArray [1, 2, 3]) 6 == Nothing + assert $ NEA.index (fromArray [1, 2, 3]) (-1) == Nothing + + log "elemIndex should return the index of an item that a predicate returns true for in an array" + assert $ NEA.elemIndex 1 (fromArray [1, 2, 1]) == Just 0 + assert $ NEA.elemIndex 4 (fromArray [1, 2, 1]) == Nothing + + log "elemLastIndex should return the last index of an item in an array" + assert $ NEA.elemLastIndex 1 (fromArray [1, 2, 1]) == Just 2 + assert $ NEA.elemLastIndex 4 (fromArray [1, 2, 1]) == Nothing + + log "findIndex should return the index of an item that a predicate returns true for in an array" + assert $ (NEA.findIndex (_ /= 1) (fromArray [1, 2, 1])) == Just 1 + assert $ (NEA.findIndex (_ == 3) (fromArray [1, 2, 1])) == Nothing + + log "findLastIndex should return the last index of an item in an array" + assert $ (NEA.findLastIndex (_ /= 1) (fromArray [2, 1, 2])) == Just 2 + assert $ (NEA.findLastIndex (_ == 3) (fromArray [2, 1, 2])) == Nothing + + log "insertAt should add an item at the specified index" + assert $ NEA.insertAt 0 1 (fromArray [2, 3]) == Just (fromArray [1, 2, 3]) + assert $ NEA.insertAt 1 1 (fromArray [2, 3]) == Just (fromArray [2, 1, 3]) + assert $ NEA.insertAt 2 1 (fromArray [2, 3]) == Just (fromArray [2, 3, 1]) + + log "insertAt should return Nothing if the index is out of A.range" + assert $ (NEA.insertAt 2 1 (NEA.singleton 1)) == Nothing + + log "deleteAt should remove an item at the specified index" + assert $ (NEA.deleteAt 0 (fromArray [1, 2, 3])) == Just [2, 3] + assert $ (NEA.deleteAt 1 (fromArray [1, 2, 3])) == Just [1, 3] + + log "deleteAt should return Nothing if the index is out of A.range" + assert $ (NEA.deleteAt 1 (NEA.singleton 1)) == Nothing + + log "updateAt should replace an item at the specified index" + assert $ NEA.updateAt 0 9 (fromArray [1, 2, 3]) == Just (fromArray [9, 2, 3]) + assert $ NEA.updateAt 1 9 (fromArray [1, 2, 3]) == Just (fromArray [1, 9, 3]) + + log "updateAt should return Nothing if the index is out of A.range" + assert $ NEA.updateAt 1 9 (NEA.singleton 0) == Nothing + + log "modifyAt should update an item at the specified index" + assert $ NEA.modifyAt 0 (_ + 1) (fromArray [1, 2, 3]) == Just (fromArray [2, 2, 3]) + assert $ NEA.modifyAt 1 (_ + 1) (fromArray [1, 2, 3]) == Just (fromArray [1, 3, 3]) + + log "modifyAt should return Nothing if the index is out of A.range" + assert $ NEA.modifyAt 1 (_ + 1) (NEA.singleton 0) == Nothing + + log "alterAt should update an item at the specified index when the function returns Just" + assert $ NEA.alterAt 0 (Just <<< (_ + 1)) (fromArray [1, 2, 3]) == Just [2, 2, 3] + assert $ NEA.alterAt 1 (Just <<< (_ + 1)) (fromArray [1, 2, 3]) == Just [1, 3, 3] + + log "alterAt should drop an item at the specified index when the function returns Nothing" + assert $ NEA.alterAt 0 (const Nothing) (fromArray [1, 2, 3]) == Just [2, 3] + assert $ NEA.alterAt 1 (const Nothing) (fromArray [1, 2, 3]) == Just [1, 3] + + log "alterAt should return Nothing if the index is out of NEA.range" + assert $ NEA.alterAt 1 (Just <<< (_ + 1)) (NEA.singleton 1) == Nothing + + log "reverse should reverse the order of items in an array" + assert $ NEA.reverse (fromArray [1, 2, 3]) == fromArray [3, 2, 1] + assert $ NEA.reverse (NEA.singleton 0) == NEA.singleton 0 + + log "concat should join an array of arrays" + assert $ NEA.concat (fromArray [fromArray [1, 2], fromArray [3, 4]]) == fromArray [1, 2, 3, 4] + + log "concatMap should be equivalent to (concat <<< map)" + assert $ NEA.concatMap doubleAndOrig (fromArray [1, 2, 3]) == NEA.concat (map doubleAndOrig (fromArray [1, 2, 3])) + + log "filter should remove items that don't match a predicate" + assert $ NEA.filter odd (NEA.range 0 10) == [1, 3, 5, 7, 9] + + log "filterA should remove items that don't match a predicate while using an applicative behaviour" + assert $ NEA.filterA (Just <<< odd) (NEA.range 0 10) == Just [1, 3, 5, 7, 9] + assert $ NEA.filterA (const Nothing) (NEA.range 0 10) == Nothing + + log "filterA should apply effects in the right order" + assert $ NEA.filterA (Const <<< show) (NEA.range 1 5) == Const "12345" + + log "mapMaybe should transform every item in an array, throwing out Nothing values" + assert $ NEA.mapMaybe (\x -> if x /= 0 then Just x else Nothing) (fromArray [0, 1, 0, 0, 2, 3]) == [1, 2, 3] + + log "catMaybe should take an array of Maybe values and throw out Nothings" + assert $ NEA.catMaybes (fromArray [Nothing, Just 2, Nothing, Just 4]) == [2, 4] + + log "mapWithIndex applies a function with an index for every element" + assert $ mapWithIndex (\i x -> x - i) (fromArray [9,8,7,6,5]) == fromArray [9,7,5,3,1] + + log "updateAtIndices changes the elements at specified indices" + assert $ NEA.updateAtIndices + [Tuple 0 false, Tuple 2 false, Tuple 8 false] + (fromArray [true, true, true, true]) == + fromArray [false, true, false, true] + + log "modifyAtIndices modifies the elements at specified indices" + assert $ NEA.modifyAtIndices [0, 2, 8] not (fromArray [true, true, true, true]) == + (fromArray [false, true, false, true]) + + log "sort should reorder a list into ascending order based on the result of compare" + assert $ NEA.sort (fromArray [1, 3, 2, 5, 6, 4]) == fromArray [1, 2, 3, 4, 5, 6] + + log "sortBy should reorder a list into ascending order based on the result of a comparison function" + assert $ NEA.sortBy (flip compare) (fromArray [1, 3, 2, 5, 6, 4]) == fromArray [6, 5, 4, 3, 2, 1] + + log "sortWith should reorder a list into ascending order based on the result of compare over a projection" + assert $ NEA.sortWith id (fromArray [1, 3, 2, 5, 6, 4]) == fromArray [1, 2, 3, 4, 5, 6] + + log "take should keep the specified number of items from the front of an array, discarding the rest" + assert $ NEA.take 1 (fromArray [1, 2, 3]) == [1] + assert $ NEA.take 2 (fromArray [1, 2, 3]) == [1, 2] + + log "takeWhile should keep all values that match a predicate from the front of an array" + assert $ NEA.takeWhile (_ /= 2) (fromArray [1, 2, 3]) == [1] + assert $ NEA.takeWhile (_ /= 3) (fromArray [1, 2, 3]) == [1, 2] + + log "take should keep the specified number of items from the end of an array, discarding the rest" + assert $ NEA.takeEnd 1 (fromArray [1, 2, 3]) == [3] + assert $ NEA.takeEnd 2 (fromArray [1, 2, 3]) == [2, 3] + + log "drop should remove the specified number of items from the front of an array" + assert $ NEA.drop 1 (fromArray [1, 2, 3]) == [2, 3] + assert $ NEA.drop 2 (fromArray [1, 2, 3]) == [3] + + log "dropWhile should remove all values that match a predicate from the front of an array" + assert $ NEA.dropWhile (_ /= 1) (fromArray [1, 2, 3]) == [1, 2, 3] + assert $ NEA.dropWhile (_ /= 2) (fromArray [1, 2, 3]) == [2, 3] + + log "drop should remove the specified number of items from the end of an array" + assert $ NEA.dropEnd 1 (fromArray [1, 2, 3]) == [1, 2] + assert $ NEA.dropEnd 2 (fromArray [1, 2, 3]) == [1] + + log "span should split an array in two based on a predicate" + let testSpan { p, input, init_, rest_ } = do + let result = NEA.span p input + assert $ result.init == init_ + assert $ result.rest == rest_ + + let oneToSeven = fromArray [1, 2, 3, 4, 5, 6, 7] + testSpan { p: (_ < 4), input: oneToSeven, init_: [1, 2, 3], rest_: [4, 5, 6, 7] } + + log "nub should remove duplicate elements from the list, keeping the first occurence" + assert $ NEA.nub (fromArray [1, 2, 2, 3, 4, 1]) == fromArray [1, 2, 3, 4] + + log "nubBy should remove duplicate items from the list using a supplied predicate" + let nubPred = \x y -> if odd x then false else x == y + assert $ NEA.nubBy nubPred (fromArray [1, 2, 2, 3, 3, 4, 4, 1]) == fromArray [1, 2, 3, 3, 4, 1] + + log "union should produce the union of two arrays" + assert $ NEA.union (fromArray [1, 2, 3]) (fromArray [2, 3, 4]) == fromArray [1, 2, 3, 4] + assert $ NEA.union (fromArray [1, 1, 2, 3]) (fromArray [2, 3, 4]) == fromArray [1, 1, 2, 3, 4] + + log "unionBy should produce the union of two arrays using the specified equality relation" + assert $ NEA.unionBy (\_ y -> y < 5) (fromArray [1, 2, 3]) (fromArray [2, 3, 4, 5, 6]) == fromArray [1, 2, 3, 5, 6] + + log "delete should remove the first matching item from an array" + assert $ NEA.delete 1 (fromArray [1, 2, 1]) == [2, 1] + assert $ NEA.delete 2 (fromArray [1, 2, 1]) == [1, 1] + + log "deleteBy should remove the first equality-relation-matching item from an array" + assert $ NEA.deleteBy (/=) 2 (fromArray [1, 2, 1]) == [2, 1] + assert $ NEA.deleteBy (/=) 1 (fromArray [1, 2, 1]) == [1, 1] + + log "intersect should return the intersection of two arrays" + assert $ NEA.intersect (fromArray [1, 2, 3, 4, 3, 2, 1]) (fromArray [1, 1, 2, 3]) == [1, 2, 3, 3, 2, 1] + + log "intersectBy should return the intersection of two arrays using the specified equivalence relation" + assert $ NEA.intersectBy (\x y -> (x * 2) == y) (fromArray [1, 2, 3]) (fromArray [2, 6]) == [1, 3] + + log "zipWith should use the specified function to zip two arrays together" + assert $ NEA.zipWith (\x y -> [show x, y]) (fromArray [1, 2, 3]) (fromArray ["a", "b", "c"]) == fromArray [["1", "a"], ["2", "b"], ["3", "c"]] + + log "zipWithA should use the specified function to zip two lists together" + assert $ NEA.zipWithA (\x y -> Just $ Tuple x y) (fromArray [1, 2, 3]) (fromArray ["a", "b", "c"]) == Just (fromArray [Tuple 1 "a", Tuple 2 "b", Tuple 3 "c"]) + + log "zip should use the specified function to zip two lists together" + assert $ NEA.zip (fromArray [1, 2, 3]) (fromArray ["a", "b", "c"]) == fromArray [Tuple 1 "a", Tuple 2 "b", Tuple 3 "c"] + + log "unzip should deconstruct a list of tuples into a tuple of lists" + assert $ NEA.unzip (fromArray [Tuple 1 "a", Tuple 2 "b", Tuple 3 "c"]) == Tuple (fromArray [1, 2, 3]) (fromArray ["a", "b", "c"]) + + log "fromFoldable" + for_ (fromArray [[], [1], [1,2], [1,2,3,4,5]]) \xs -> do + assert $ NEA.fromFoldable xs == NEA.fromArray xs + + log "toUnfoldable" + let toUnfoldableId xs = NEA.toUnfoldable xs == NEA.toArray xs + traverse_ (assert <<< toUnfoldableId) $ + fromArray ( + [ fromArray [1] + , fromArray [1,2,3] + , fromArray [2,3,1] + , fromArray [4,0,0,1,25,36,458,5842,23757] + ]) + + log "foldl should work" + -- test through sum + assert $ sum (fromArray [1, 2, 3, 4]) == 10 + + log "foldMap1 should work" + assert $ foldMap1 Additive (fromArray [1, 2, 3, 4]) == Additive 10 + + log "traverse1 should work" + assert $ traverse1 Just (fromArray [1, 2, 3, 4]) == NEA.fromArray [1, 2, 3, 4] + +odd :: Int -> Boolean +odd n = n `mod` 2 /= zero + +doubleAndOrig :: Int -> NEA.NonEmptyArray Int +doubleAndOrig x = NEA.cons (x * 2) (NEA.singleton x) diff --git a/test/Test/Main.purs b/test/Test/Main.purs index 3cd0aff7..d2850e71 100644 --- a/test/Test/Main.purs +++ b/test/Test/Main.purs @@ -10,6 +10,7 @@ import Test.Data.Array (testArray) import Test.Data.Array.Partial (testArrayPartial) import Test.Data.Array.ST (testArrayST) import Test.Data.Array.ST.Partial (testArraySTPartial) +import Test.Data.Array.NonEmpty (testNonEmptyArray) main :: forall eff. Eff (console :: CONSOLE, assert :: ASSERT | eff) Unit main = do @@ -17,3 +18,4 @@ main = do testArrayST testArrayPartial testArraySTPartial + testNonEmptyArray