Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
208 changes: 202 additions & 6 deletions src/Data/List/NonEmpty.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Data.List.NonEmpty
, fromList
, toList
, singleton
, length
, cons
, snoc
, head
Expand All @@ -13,11 +14,46 @@ module Data.List.NonEmpty
, init
, uncons
, unsnoc
, length
, (!!), index
, elemIndex
, elemLastIndex
, findIndex
, findLastIndex
, insertAt
, updateAt
, modifyAt
, reverse
, concat
, concatMap
, filter
, filterM
, mapMaybe
, catMaybes
, appendFoldable
, mapWithIndex
, sort
, sortBy
, take
, takeWhile
, drop
, dropWhile
, span
, group
, group'
, groupBy
, partition
, nub
, nubBy
, union
, unionBy
, intersect
, intersectBy
, zipWith
, zipWithA
, zip
, unzip
, foldM
, module Exports
) where

import Prelude
Expand All @@ -26,12 +62,50 @@ import Data.Foldable (class Foldable)
import Data.List ((:))
import Data.List as L
import Data.List.Types (NonEmptyList(..))
import Data.Maybe (Maybe(..), maybe, fromMaybe, fromJust)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.NonEmpty ((:|))
import Data.NonEmpty as NE
import Data.Tuple (Tuple(..))
import Data.Semigroup.Traversable (sequence1)
import Data.Tuple (Tuple(..), fst, snd)
import Data.Unfoldable (class Unfoldable, unfoldr)
import Partial.Unsafe (unsafePartial)
import Partial.Unsafe (unsafeCrashWith)

import Data.Foldable (foldl, foldr, foldMap, fold, intercalate, elem, notElem, find, findMap, any, all) as Exports
import Data.Semigroup.Foldable (fold1, foldMap1, for1_, sequence1_, traverse1_) as Exports
import Data.Semigroup.Traversable (sequence1, traverse1, traverse1Default) as Exports
import Data.Traversable (scanl, scanr) as Exports

-- | Internal function: any operation on a list that is guaranteed not to delete
-- | all elements also applies to a NEL, this function is a helper for defining
-- | those cases.
wrappedOperation
:: forall a b
. String
-> (L.List a -> L.List b)
-> NonEmptyList a
-> NonEmptyList b
wrappedOperation name f (NonEmptyList (x :| xs)) =
case f (x : xs) of
x' : xs' -> NonEmptyList (x' :| xs')
L.Nil -> unsafeCrashWith ("Impossible: empty list in NonEmptyList " <> name)

-- | Like `wrappedOperation`, but for functions that operate on 2 lists.
wrappedOperation2
:: forall a b c
. String
-> (L.List a -> L.List b -> L.List c)
-> NonEmptyList a
-> NonEmptyList b
-> NonEmptyList c
wrappedOperation2 name f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
case f (x : xs) (y : ys) of
x' : xs' -> NonEmptyList (x' :| xs')
L.Nil -> unsafeCrashWith ("Impossible: empty list in NonEmptyList " <> name)

-- | Lifts a function that operates on a list to work on a NEL. This does not
-- | preserve the non-empty status of the result.
lift :: forall a b. (L.List a -> b) -> NonEmptyList a -> b
lift f (NonEmptyList (x :| xs)) = f (x : xs)

toUnfoldable :: forall f. Unfoldable f => NonEmptyList ~> f
toUnfoldable =
Expand Down Expand Up @@ -79,16 +153,138 @@ unsnoc (NonEmptyList (x :| xs)) = case L.unsnoc xs of
length :: forall a. NonEmptyList a -> Int
length (NonEmptyList (x :| xs)) = 1 + L.length xs

index :: forall a. NonEmptyList a -> Int -> Maybe a
index (NonEmptyList (x :| xs)) i
| i == 0 = Just x
| otherwise = L.index xs (i - 1)

infixl 8 index as !!

elemIndex :: forall a. Eq a => a -> NonEmptyList a -> Maybe Int
elemIndex x = findIndex (_ == x)

elemLastIndex :: forall a. Eq a => a -> NonEmptyList a -> Maybe Int
elemLastIndex x = findLastIndex (_ == x)

findIndex :: forall a. (a -> Boolean) -> NonEmptyList a -> Maybe Int
findIndex f (NonEmptyList (x :| xs))
| f x = Just 0
| otherwise = (_ + 1) <$> L.findIndex f xs

findLastIndex :: forall a. (a -> Boolean) -> NonEmptyList a -> Maybe Int
findLastIndex f (NonEmptyList (x :| xs)) =
case L.findLastIndex f xs of
Just i -> Just (i + 1)
Nothing
| f x -> Just 0
| otherwise -> Nothing

insertAt :: forall a. Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a)
insertAt i a (NonEmptyList (x :| xs))
| i == 0 = Just (NonEmptyList (a :| x : xs))
| otherwise = NonEmptyList <<< (x :| _) <$> L.insertAt (i - 1) a xs

updateAt :: forall a. Int -> a -> NonEmptyList a -> Maybe (NonEmptyList a)
updateAt i a (NonEmptyList (x :| xs))
| i == 0 = Just (NonEmptyList (a :| xs))
| otherwise = NonEmptyList <<< (x :| _) <$> L.updateAt (i - 1) a xs

modifyAt :: forall a. Int -> (a -> a) -> NonEmptyList a -> Maybe (NonEmptyList a)
modifyAt i f (NonEmptyList (x :| xs))
| i == 0 = Just (NonEmptyList (f x :| xs))
| otherwise = NonEmptyList <<< (x :| _) <$> L.modifyAt (i - 1) f xs

reverse :: forall a. NonEmptyList a -> NonEmptyList a
reverse = wrappedOperation "reverse" L.reverse

filter :: forall a. (a -> Boolean) -> NonEmptyList a -> L.List a
filter = lift <<< L.filter

filterM :: forall m a. Monad m => (a -> m Boolean) -> NonEmptyList a -> m (L.List a)
filterM = lift <<< L.filterM

mapMaybe :: forall a b. (a -> Maybe b) -> NonEmptyList a -> L.List b
mapMaybe = lift <<< L.mapMaybe

catMaybes :: forall a. NonEmptyList (Maybe a) -> L.List a
catMaybes = lift L.catMaybes

concat :: forall a. NonEmptyList (NonEmptyList a) -> NonEmptyList a
concat = (_ >>= id)

concatMap :: forall a b. (a -> NonEmptyList b) -> NonEmptyList a -> NonEmptyList b
concatMap = flip bind

appendFoldable :: forall t a. Foldable t => NonEmptyList a -> t a -> NonEmptyList a
appendFoldable (NonEmptyList (x :| xs)) ys =
NonEmptyList (x :| (xs <> L.fromFoldable ys))

mapWithIndex :: forall a b. (Int -> a -> b) -> NonEmptyList a -> NonEmptyList b
mapWithIndex = wrappedOperation "mapWithIndex" <<< L.mapWithIndex

sort :: forall a. Ord a => NonEmptyList a -> NonEmptyList a
sort xs = sortBy compare xs

sortBy :: forall a. (a -> a -> Ordering) -> NonEmptyList a -> NonEmptyList a
sortBy cmp xs = unsafeFromList $ L.sortBy cmp (toList xs)
where unsafeFromList ys = unsafePartial $ fromJust $ fromList ys
sortBy = wrappedOperation "sortBy" <<< L.sortBy

take :: forall a. Int -> NonEmptyList a -> L.List a
take = lift <<< L.take

takeWhile :: forall a. (a -> Boolean) -> NonEmptyList a -> L.List a
takeWhile = lift <<< L.takeWhile

drop :: forall a. Int -> NonEmptyList a -> L.List a
drop = lift <<< L.drop

dropWhile :: forall a. (a -> Boolean) -> NonEmptyList a -> L.List a
dropWhile = lift <<< L.dropWhile

span :: forall a. (a -> Boolean) -> NonEmptyList a -> { init :: L.List a, rest :: L.List a }
span = lift <<< L.span

group :: forall a. Eq a => NonEmptyList a -> NonEmptyList (NonEmptyList a)
group = wrappedOperation "group" L.group

group' :: forall a. Ord a => NonEmptyList a -> NonEmptyList (NonEmptyList a)
group' = wrappedOperation "group'" L.group'

groupBy :: forall a. (a -> a -> Boolean) -> NonEmptyList a -> NonEmptyList (NonEmptyList a)
groupBy = wrappedOperation "groupBy" <<< L.groupBy

partition :: forall a. (a -> Boolean) -> NonEmptyList a -> { yes :: L.List a, no :: L.List a }
partition = lift <<< L.partition

nub :: forall a. Eq a => NonEmptyList a -> NonEmptyList a
nub = wrappedOperation "nub" L.nub

nubBy :: forall a. (a -> a -> Boolean) -> NonEmptyList a -> NonEmptyList a
nubBy = wrappedOperation "nubBy" <<< L.nubBy

union :: forall a. Eq a => NonEmptyList a -> NonEmptyList a -> NonEmptyList a
union = wrappedOperation2 "union" L.union

unionBy :: forall a. (a -> a -> Boolean) -> NonEmptyList a -> NonEmptyList a -> NonEmptyList a
unionBy = wrappedOperation2 "unionBy" <<< L.unionBy

intersect :: forall a. Eq a => NonEmptyList a -> NonEmptyList a -> NonEmptyList a
intersect = wrappedOperation2 "intersect" L.intersect

intersectBy :: forall a. (a -> a -> Boolean) -> NonEmptyList a -> NonEmptyList a -> NonEmptyList a
intersectBy = wrappedOperation2 "intersectBy" <<< L.intersectBy

zipWith :: forall a b c. (a -> b -> c) -> NonEmptyList a -> NonEmptyList b -> NonEmptyList c
zipWith f (NonEmptyList (x :| xs)) (NonEmptyList (y :| ys)) =
NonEmptyList (f x y :| L.zipWith f xs ys)

zipWithA :: forall m a b c. Applicative m => (a -> b -> m c) -> NonEmptyList a -> NonEmptyList b -> m (NonEmptyList c)
zipWithA f xs ys = sequence1 (zipWith f xs ys)

zip :: forall a b. NonEmptyList a -> NonEmptyList b -> NonEmptyList (Tuple a b)
zip = zipWith Tuple

unzip :: forall a b. NonEmptyList (Tuple a b) -> Tuple (NonEmptyList a) (NonEmptyList b)
unzip ts = Tuple (map fst ts) (map snd ts)

foldM :: forall m a b. Monad m => (a -> b -> m a) -> a -> NonEmptyList b -> m a
foldM f a (NonEmptyList (b :| bs)) = f a b >>= \a' -> L.foldM f a' bs
19 changes: 18 additions & 1 deletion src/Data/List/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,13 +12,15 @@ import Control.MonadZero (class MonadZero)
import Control.Plus (class Plus)

import Data.Eq (class Eq1, eq1)
import Data.Foldable (class Foldable, foldr, foldl, intercalate)
import Data.Foldable (class Foldable, foldl, foldr, intercalate)
import Data.Maybe (Maybe(..))
import Data.Monoid (class Monoid, mempty)
import Data.Newtype (class Newtype)
import Data.NonEmpty (NonEmpty, (:|))
import Data.NonEmpty as NE
import Data.Ord (class Ord1, compare1)
import Data.Semigroup.Foldable (class Foldable1)
import Data.Semigroup.Traversable (class Traversable1, traverse1)
import Data.Traversable (class Traversable, traverse)
import Data.Tuple (Tuple(..))
import Data.Unfoldable (class Unfoldable)
Expand Down Expand Up @@ -128,6 +130,9 @@ newtype NonEmptyList a = NonEmptyList (NonEmpty List a)
toList :: NonEmptyList ~> List
toList (NonEmptyList (x :| xs)) = x : xs

nelCons :: forall a. a -> NonEmptyList a -> NonEmptyList a
nelCons a (NonEmptyList (b :| bs)) = NonEmptyList (a :| b : bs)

derive instance newtypeNonEmptyList :: Newtype (NonEmptyList a) _

derive newtype instance eqNonEmptyList :: Eq a => Eq (NonEmptyList a)
Expand Down Expand Up @@ -172,3 +177,15 @@ instance semigroupNonEmptyList :: Semigroup (NonEmptyList a) where
derive newtype instance foldableNonEmptyList :: Foldable NonEmptyList

derive newtype instance traversableNonEmptyList :: Traversable NonEmptyList

instance foldable1NonEmptyList :: Foldable1 NonEmptyList where
fold1 (NonEmptyList (a :| as)) =
foldl append a as
foldMap1 f (NonEmptyList (a :| as)) =
foldl (\acc -> append acc <<< f) (f a) as

instance traversable1NonEmptyList :: Traversable1 NonEmptyList where
traverse1 f (NonEmptyList (a :| as)) =
foldl (\acc -> lift2 (flip nelCons) acc <<< f) (pure <$> f a) as
<#> case _ of NonEmptyList (x :| xs) → foldl (flip nelCons) (pure x) xs
sequence1 = traverse1 id
Loading