-- Copyright 2023 Evan Laforge
-- This program is distributed under the terms of the GNU General Public
-- License 3.0, see COPYING or http://www.gnu.org/licenses/gpl-3.0.txt

-- | Functions to operate on lists.
{-# LANGUAGE BangPatterns #-}
module Util.Lists (
    NonNull
    , head, tail
    , last
    , unsnoc
    -- * indexing
    , at
    , insertAt
    , removeAt
    , takeAt
    , modifyAt
    , findModify
    , updateAt
    , move
    -- * enumeration
    , range, range', rangeEnd, range_
    -- * transformation
    , keyOn
    , keyOnSnd
    , keyOnJust
    , firstLast
    , mapMaybeFst, mapMaybeSnd
    , mapHead, mapTail, mapHeadTail
    , mapInit, mapLast
    , scanlOn
    -- * min / max
    , minOn, maxOn
    , minimumOn, maximumOn
    , minimum, maximum
    -- * ordered lists
    , insertOn
    , sortOn
    , reverseSortOn
    , merge, mergeBy, mergeOn
    , mergeLists, mergeAscLists

    -- * grouping
    -- ** adjacent
    , groupAdjacent
    , keyedGroupAdjacent
    , groupAdjacentFst
    , groupAdjacentSnd
    -- ** sort
    , keyedGroupSort
    , groupFst, groupSnd
    , groupSort
    -- ** stable
    , groupStableWith
    , groupStable
    , keyedGroupStable

    -- * zipping
    , zipNext, zipNexts
    , zipPrev
    , zipNeighbors
    , zipRemainder
    , zipper

    -- * Paired
    , Paired(..)
    , pairedSecond, pairedFirst
    , partitionPaired
    , zipPadded, zipPaddedFst, zipPaddedSnd
    , diff
    , diffEither
    , diffIndex
    , diffIndexOn
    , pairSorted
    , pairSortedOn, pairSortedOn1
    , pairOn1
    -- * partition
    , partition2
    , partitionOn
    -- * sublists
    , chunked
    , rotate
    , rotate2
    -- * prefix / suffix
    , dropBefore
    , dropPrefix
    , dropSuffix

    -- * permutations
    , cartesian
    -- * enumeration
    , enumerate
    -- * sublists
    , takeEnd
    , dropEnd
    , takeWhileEnd
    -- * split / join
    , splitWith
    , breakWith
    -- * transform
    , mapAccumLM
    -- ** split and join
    , split
    , join
    , splitBefore, splitBetween
    -- * span and break
    , spanWhile
    -- * duplicates
    , dropDups
    , dropWith
    , partitionDups
    , findDups
    , dropInitialDups
    , unique
    , uniqueOn
    , uniqueSort
    -- * replace
    , replace, replace1
    -- * search
    , count
) where
import           Prelude hiding (head, last, tail, minimum, maximum)
import qualified Data.Algorithm.Diff as Diff
import           Data.Bifunctor (Bifunctor(bimap), first, second)
import qualified Data.Either as Either
import qualified Data.Function as Function
import qualified Data.List as List
import           Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.Ordered as Ordered
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import qualified Data.Ord as Ord
import qualified Data.Set as Set


-- | This is just a list, but is documentation that a return value will never
-- be null, or an argument should never be null.  This is for cases where
-- 'NonEmpty' is too annoying to work with.
type NonNull a = [a]

-- * extract

-- | Total variants of unsafe list operations.
head :: [a] -> Maybe a
head :: forall a. [a] -> Maybe a
head [] = forall a. Maybe a
Nothing
head (a
x:[a]
_) = forall a. a -> Maybe a
Just a
x

tail :: [a] -> Maybe [a]
tail :: forall a. [a] -> Maybe [a]
tail [] = forall a. Maybe a
Nothing
tail (a
_:[a]
xs) = forall a. a -> Maybe a
Just [a]
xs

last :: [a] -> Maybe a
last :: forall a. [a] -> Maybe a
last [] = forall a. Maybe a
Nothing
last [a]
xs = forall a. a -> Maybe a
Just (forall a. [a] -> a
List.last [a]
xs)

-- | List initial and final element, if any.
unsnoc :: [a] -> Maybe ([a], a)
unsnoc :: forall a. [a] -> Maybe ([a], a)
unsnoc [] = forall a. Maybe a
Nothing
unsnoc (a
x:[a]
xs) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall {a}. a -> [a] -> ([a], a)
go a
x [a]
xs
    where
    go :: a -> [a] -> ([a], a)
go a
x0 [] = ([], a
x0)
    go a
x0 (a
x:[a]
xs) = let ([a]
pre, a
post) = a -> [a] -> ([a], a)
go a
x [a]
xs in (a
x0forall a. a -> [a] -> [a]
:[a]
pre, a
post)

-- * indexing

-- | Get @xs !! n@, but return Nothing if the index is out of range.
at :: [a] -> Int -> Maybe a
at :: forall a. [a] -> Int -> Maybe a
at [a]
xs Int
n
    | Int
n forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. Maybe a
Nothing
    | Bool
otherwise = forall {t} {a}. (Eq t, Num t) => [a] -> t -> Maybe a
go [a]
xs Int
n
    where
    go :: [a] -> t -> Maybe a
go [] t
_ = forall a. Maybe a
Nothing
    go (a
x:[a]
_) t
0 = forall a. a -> Maybe a
Just a
x
    go (a
_:[a]
xs) t
n = [a] -> t -> Maybe a
go [a]
xs (t
nforall a. Num a => a -> a -> a
-t
1)

-- | Insert @x@ into @xs@ at index @i@.  If @i@ is out of range, insert at the
-- beginning or end of the list.
insertAt :: Int -> a -> [a] -> [a]
insertAt :: forall a. Int -> a -> [a] -> [a]
insertAt Int
i a
x [a]
xs = let ([a]
pre, [a]
post) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
i [a]
xs in [a]
pre forall a. [a] -> [a] -> [a]
++ (a
x forall a. a -> [a] -> [a]
: [a]
post)

-- | Remove the element at the given index.  Do nothing if the index is out
-- of range.
removeAt :: Int -> [a] -> [a]
removeAt :: forall a. Int -> [a] -> [a]
removeAt Int
i [a]
xs = let ([a]
pre, [a]
post) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
i [a]
xs in [a]
pre forall a. [a] -> [a] -> [a]
++ forall a. Int -> [a] -> [a]
drop Int
1 [a]
post

-- | Like 'removeAt' but return the removed element as well.
takeAt :: Int -> [a] -> Maybe (a, [a])
takeAt :: forall a. Int -> [a] -> Maybe (a, [a])
takeAt Int
i [a]
xs = case [a]
post of
        a
v : [a]
vs -> forall a. a -> Maybe a
Just (a
v, [a]
pre forall a. [a] -> [a] -> [a]
++ [a]
vs)
        [] -> forall a. Maybe a
Nothing
    where ([a]
pre, [a]
post) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
i [a]
xs

-- | Modify element at an index by applying a function to it.  If the index is
-- out of range, nothing happens.
modifyAt :: Int -> (a -> a) -> [a] -> [a]
modifyAt :: forall a. Int -> (a -> a) -> [a] -> [a]
modifyAt Int
i a -> a
f [a]
xs = case [a]
post of
    [] -> [a]
pre
    a
elt : [a]
rest -> [a]
pre forall a. [a] -> [a] -> [a]
++ a -> a
f a
elt forall a. a -> [a] -> [a]
: [a]
rest
    where ([a]
pre, [a]
post) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
i [a]
xs

-- | Find an element, then change it.  Return Nothing if the element wasn't
-- found.
findModify :: (a -> Bool) -> (a -> a) -> [a] -> Maybe [a]
findModify :: forall a. (a -> Bool) -> (a -> a) -> [a] -> Maybe [a]
findModify a -> Bool
match a -> a
modify = [a] -> Maybe [a]
go
    where
    go :: [a] -> Maybe [a]
go (a
x:[a]
xs)
        | a -> Bool
match a
x = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ a -> a
modify a
x forall a. a -> [a] -> [a]
: [a]
xs
        | Bool
otherwise = (a
x:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a] -> Maybe [a]
go [a]
xs
    go [] = forall a. Maybe a
Nothing

-- | Similar to 'modifyAt', but will insert an element for an out of range
-- positive index.  The list will be extended with @deflt@, and the modify
-- function passed a Nothing.
updateAt :: a -> Int -> (Maybe a -> a) -> [a] -> [a]
updateAt :: forall a. a -> Int -> (Maybe a -> a) -> [a] -> [a]
updateAt a
deflt Int
i Maybe a -> a
f [a]
xs
    | Int
i forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"updateAt: negative index " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
i
    | Bool
otherwise = forall {t}. (Eq t, Num t) => t -> [a] -> [a]
go Int
i [a]
xs
    where
    go :: t -> [a] -> [a]
go t
0 [] = [Maybe a -> a
f forall a. Maybe a
Nothing]
    go t
0 (a
x:[a]
xs) = Maybe a -> a
f (forall a. a -> Maybe a
Just a
x) forall a. a -> [a] -> [a]
: [a]
xs
    go t
i [] = a
deflt forall a. a -> [a] -> [a]
: t -> [a] -> [a]
go (t
iforall a. Num a => a -> a -> a
-t
1) []
    go t
i (a
x:[a]
xs) = a
x forall a. a -> [a] -> [a]
: t -> [a] -> [a]
go (t
iforall a. Num a => a -> a -> a
-t
1) [a]
xs

-- | Move an element from one index to another, or Nothing if the @from@
-- index was out of range.
move :: Int -> Int -> [a] -> Maybe [a]
move :: forall a. Int -> Int -> [a] -> Maybe [a]
move Int
from Int
to [a]
xs = do
    (a
x, [a]
dropped) <- forall a. Int -> [a] -> Maybe (a, [a])
takeAt Int
from [a]
xs
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Int -> a -> [a] -> [a]
insertAt Int
to a
x [a]
dropped

-- * enumeration

-- | Enumerate an inclusive range.  Uses multiplication instead of successive
-- addition to avoid loss of precision.
--
-- Also it doesn't require an Enum instance.
range :: (Num a, Ord a) => a -> a -> a -> [a]
range :: forall a. (Num a, Ord a) => a -> a -> a -> [a]
range a
start a
end a
step = a -> [a]
go a
0
    where
    go :: a -> [a]
go a
i
        | a
step forall a. Ord a => a -> a -> Bool
>= a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
> a
end = []
        | a
step forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
< a
end = []
        | Bool
otherwise = a
val forall a. a -> [a] -> [a]
: a -> [a]
go (a
iforall a. Num a => a -> a -> a
+a
1)
        where val :: a
val = a
start forall a. Num a => a -> a -> a
+ (a
iforall a. Num a => a -> a -> a
*a
step)
{-# INLINEABLE range #-}
{-# SPECIALIZE range :: Int -> Int -> Int -> [Int] #-}

-- | Enumerate a half-open range.
range' :: (Num a, Ord a) => a -> a -> a -> [a]
range' :: forall a. (Num a, Ord a) => a -> a -> a -> [a]
range' a
start a
end a
step = a -> [a]
go a
0
    where
    go :: a -> [a]
go a
i
        | a
step forall a. Ord a => a -> a -> Bool
>= a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
>= a
end = []
        | a
step forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
<= a
end = []
        | Bool
otherwise = a
val forall a. a -> [a] -> [a]
: a -> [a]
go (a
iforall a. Num a => a -> a -> a
+a
1)
        where val :: a
val = a
start forall a. Num a => a -> a -> a
+ (a
iforall a. Num a => a -> a -> a
*a
step)
{-# INLINEABLE range' #-}
{-# SPECIALIZE range' :: Int -> Int -> Int -> [Int] #-}

-- | Like 'range', but always includes the end, even if it doesn't line up on
-- a step.
rangeEnd :: (Num a, Ord a) => a -> a -> a -> [a]
rangeEnd :: forall a. (Num a, Ord a) => a -> a -> a -> [a]
rangeEnd a
start a
end a
step = a -> [a]
go a
0
    where
    go :: a -> [a]
go a
i
        | a
step forall a. Ord a => a -> a -> Bool
>= a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
>= a
end = [a
end]
        | a
step forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
&& a
val forall a. Ord a => a -> a -> Bool
<= a
end = [a
end]
        | Bool
otherwise = a
val forall a. a -> [a] -> [a]
: a -> [a]
go (a
iforall a. Num a => a -> a -> a
+a
1)
        where val :: a
val = a
start forall a. Num a => a -> a -> a
+ (a
iforall a. Num a => a -> a -> a
*a
step)
{-# INLINEABLE rangeEnd #-}
{-# SPECIALIZE rangeEnd :: Int -> Int -> Int -> [Int] #-}

-- | Infinite range.
range_ :: Num a => a -> a -> [a]
range_ :: forall a. Num a => a -> a -> [a]
range_ a
start a
step = a -> [a]
go a
0
    where go :: a -> [a]
go a
i = a
start forall a. Num a => a -> a -> a
+ (a
iforall a. Num a => a -> a -> a
*a
step) forall a. a -> [a] -> [a]
: a -> [a]
go (a
iforall a. Num a => a -> a -> a
+a
1)
{-# INLINEABLE range_ #-}
{-# SPECIALIZE range_ :: Int -> Int -> [Int] #-}

-- * transformation

keyOn :: (a -> k) -> [a] -> [(k, a)]
keyOn :: forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn a -> k
f [a]
xs = forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map a -> k
f [a]
xs) [a]
xs

keyOnSnd :: (a -> k) -> [a] -> [(a, k)]
keyOnSnd :: forall a k. (a -> k) -> [a] -> [(a, k)]
keyOnSnd a -> k
f [a]
xs = forall a b. [a] -> [b] -> [(a, b)]
zip [a]
xs (forall a b. (a -> b) -> [a] -> [b]
map a -> k
f [a]
xs)

keyOnJust :: (a -> Maybe k) -> [a] -> [(k, a)]
keyOnJust :: forall a k. (a -> Maybe k) -> [a] -> [(k, a)]
keyOnJust a -> Maybe k
f [a]
xs = [(k
k, a
a) | (Just k
k, a
a) <- forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn a -> Maybe k
f [a]
xs]

-- | Apply a function to the first and last elements.  Middle elements are
-- unchanged.  A null or singleton list is also unchanged.
firstLast :: (a -> a) -> (a -> a) -> [a] -> [a]
firstLast :: forall a. (a -> a) -> (a -> a) -> [a] -> [a]
firstLast a -> a
start a -> a
end [a]
xs = case [a]
xs of
    [] -> []
    [a
x] -> [a
x]
    a
x : [a]
xs -> a -> a
start a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs
    where
    go :: [a] -> [a]
go [] = []
    go [a
x] = [a -> a
end a
x]
    go (a
x:[a]
xs) = a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs

-- | Filter on the fst values returning Just.
mapMaybeFst :: (a -> Maybe a2) -> [(a, b)] -> [(a2, b)]
mapMaybeFst :: forall a a2 b. (a -> Maybe a2) -> [(a, b)] -> [(a2, b)]
mapMaybeFst a -> Maybe a2
f [(a, b)]
xs = [(a2
a, b
b) | (Just a2
a, b
b) <- forall a b. (a -> b) -> [a] -> [b]
map (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first a -> Maybe a2
f) [(a, b)]
xs]

-- | Filter on the snd values returning Just.
mapMaybeSnd :: (b -> Maybe b2) -> [(a, b)] -> [(a, b2)]
mapMaybeSnd :: forall b b2 a. (b -> Maybe b2) -> [(a, b)] -> [(a, b2)]
mapMaybeSnd b -> Maybe b2
f [(a, b)]
xs = [(a
a, b2
b) | (a
a, Just b2
b) <- forall a b. (a -> b) -> [a] -> [b]
map (forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second b -> Maybe b2
f) [(a, b)]
xs]

mapHead :: (a -> a) -> [a] -> [a]
mapHead :: forall a. (a -> a) -> [a] -> [a]
mapHead a -> a
_ [] = []
mapHead a -> a
f (a
x:[a]
xs) = a -> a
f a
x forall a. a -> [a] -> [a]
: [a]
xs

mapTail :: (a -> a) -> [a] -> [a]
mapTail :: forall a. (a -> a) -> [a] -> [a]
mapTail a -> a
f (a
x:[a]
xs) = a
x forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map a -> a
f [a]
xs
mapTail a -> a
_ [] = []

mapHeadTail :: (a -> b) -> (a -> b) -> [a] -> [b]
mapHeadTail :: forall a b. (a -> b) -> (a -> b) -> [a] -> [b]
mapHeadTail a -> b
f a -> b
g (a
x : [a]
xs) = a -> b
f a
x forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map a -> b
g [a]
xs
mapHeadTail a -> b
_ a -> b
_ [] = []

mapInit :: (a -> a) -> [a] -> [a]
mapInit :: forall a. (a -> a) -> [a] -> [a]
mapInit a -> a
_ [] = []
mapInit a -> a
_ [a
x] = [a
x]
mapInit a -> a
f (a
x:[a]
xs) = a -> a
f a
x forall a. a -> [a] -> [a]
: forall a. (a -> a) -> [a] -> [a]
mapInit a -> a
f [a]
xs

mapLast :: (a -> a) -> [a] -> [a]
mapLast :: forall a. (a -> a) -> [a] -> [a]
mapLast a -> a
_ [] = []
mapLast a -> a
f [a
x] = [a -> a
f a
x]
mapLast a -> a
f (a
x:[a]
xs) = a
x forall a. a -> [a] -> [a]
: forall a. (a -> a) -> [a] -> [a]
mapLast a -> a
f [a]
xs

-- | This is like 'scanl', but you can scan with a key function.  E.g. to
-- accumulate line lengths: @scanlOn length (+) 0@.
scanlOn :: (accum -> key -> accum) -> (a -> key) -> accum -> [a]
    -> [(accum, a)]
scanlOn :: forall accum key a.
(accum -> key -> accum)
-> (a -> key) -> accum -> [a] -> [(accum, a)]
scanlOn accum -> key -> accum
f a -> key
key accum
z [a]
xs = forall a b. [a] -> [b] -> [(a, b)]
zip (forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl (\accum
t -> accum -> key -> accum
f accum
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> key
key) accum
z [a]
xs) [a]
xs

-- * min / max

minOn :: Ord k => (a -> k) -> a -> a -> a
minOn :: forall k a. Ord k => (a -> k) -> a -> a -> a
minOn a -> k
key a
x a
y = if a -> k
key a
x forall a. Ord a => a -> a -> Bool
<= a -> k
key a
y then a
x else a
y

maxOn :: Ord k => (a -> k) -> a -> a -> a
maxOn :: forall k a. Ord k => (a -> k) -> a -> a -> a
maxOn a -> k
key a
x a
y = if a -> k
key a
x forall a. Ord a => a -> a -> Bool
>= a -> k
key a
y then a
x else a
y

minimumOn :: Ord k => (a -> k) -> [a] -> Maybe a
minimumOn :: forall k a. Ord k => (a -> k) -> [a] -> Maybe a
minimumOn a -> k
_ [] = forall a. Maybe a
Nothing
minimumOn a -> k
key [a]
xs = forall a. a -> Maybe a
Just (forall a. (a -> a -> a) -> [a] -> a
List.foldl1' a -> a -> a
f [a]
xs)
    where f :: a -> a -> a
f a
low a
x = if a -> k
key a
x forall a. Ord a => a -> a -> Bool
< a -> k
key a
low then a
x else a
low

maximumOn :: Ord k => (a -> k) -> [a] -> Maybe a
maximumOn :: forall k a. Ord k => (a -> k) -> [a] -> Maybe a
maximumOn a -> k
_ [] = forall a. Maybe a
Nothing
maximumOn a -> k
key [a]
xs = forall a. a -> Maybe a
Just (forall a. (a -> a -> a) -> [a] -> a
List.foldl1' a -> a -> a
f [a]
xs)
    where f :: a -> a -> a
f a
high a
x = if a -> k
key a
x forall a. Ord a => a -> a -> Bool
> a -> k
key a
high then a
x else a
high

minimum :: Ord a => [a] -> Maybe a
minimum :: forall a. Ord a => [a] -> Maybe a
minimum [] = forall a. Maybe a
Nothing
minimum [a]
xs = forall a. a -> Maybe a
Just (forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
List.minimum [a]
xs)

maximum :: Ord a => [a] -> Maybe a
maximum :: forall a. Ord a => [a] -> Maybe a
maximum [] = forall a. Maybe a
Nothing
maximum [a]
xs = forall a. a -> Maybe a
Just (forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
List.maximum [a]
xs)

-- * ordered lists

insertOn :: Ord k => (a -> k) -> a -> [a] -> [a]
insertOn :: forall k a. Ord k => (a -> k) -> a -> [a] -> [a]
insertOn a -> k
key = forall a. (a -> a -> Ordering) -> a -> [a] -> [a]
List.insertBy (\a
a a
b -> forall a. Ord a => a -> a -> Ordering
compare (a -> k
key a
a) (a -> k
key a
b))

-- | Stable sort on a cheap key function.  Different from 'List.sortOn', which
-- is for an expensive key function.
sortOn :: Ord k => (a -> k) -> [a] -> [a]
sortOn :: forall k a. Ord k => (a -> k) -> [a] -> [a]
sortOn = forall k a. Ord k => (a -> k) -> [a] -> [a]
Ordered.sortOn'

-- | Like 'sortOn', but sort highest-to-lowest.
reverseSortOn :: Ord b => (a -> b) -> [a] -> [a]
reverseSortOn :: forall k a. Ord k => (a -> k) -> [a] -> [a]
reverseSortOn a -> b
f = forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy forall a b. (a -> b) -> a -> b
$ \a
a a
b -> forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing a -> b
f a
b a
a

-- | Merge sorted lists.  If two elements compare equal, the one from the left
-- list comes first.
merge :: Ord a => [a] -> [a] -> [a]
merge :: forall a. Ord a => [a] -> [a] -> [a]
merge = forall k a. Ord k => (a -> k) -> [a] -> [a] -> [a]
mergeOn forall a. a -> a
id

mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy :: forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy = forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
Ordered.mergeBy

mergeOn :: Ord k => (a -> k) -> [a] -> [a] -> [a]
mergeOn :: forall k a. Ord k => (a -> k) -> [a] -> [a] -> [a]
mergeOn a -> k
key = forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
Ordered.mergeBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing a -> k
key)

mergeLists :: Ord k => (a -> k) -> [[a]] -> [a]
mergeLists :: forall k a. Ord k => (a -> k) -> [[a]] -> [a]
mergeLists a -> k
key = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall k a. Ord k => (a -> k) -> [a] -> [a] -> [a]
mergeOn a -> k
key) []

-- | If the heads of the sublists are also sorted I can be lazy in the list of
-- sublists too.  This version is optimized for minimal overlap.
mergeAscLists :: Ord k => (a -> k) -> [[a]] -> [a]
mergeAscLists :: forall k a. Ord k => (a -> k) -> [[a]] -> [a]
mergeAscLists a -> k
key = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr [a] -> [a] -> [a]
go []
    where
    go :: [a] -> [a] -> [a]
go [] [a]
ys = [a]
ys
    go (a
x:[a]
xs) [a]
ys = a
x forall a. a -> [a] -> [a]
: forall k a. Ord k => (a -> k) -> [a] -> [a] -> [a]
mergeOn a -> k
key [a]
xs [a]
ys

-- * grouping

-- ** adjacent

-- Adjacent groups only group adjacent elements, just like 'List.group'.

-- | This is just 'List.groupBy' except with a key function.
groupAdjacent :: Eq key => (a -> key) -> [a] -> [NonNull a]
groupAdjacent :: forall key a. Eq key => (a -> key) -> [a] -> [[a]]
groupAdjacent a -> key
key = forall a. (a -> a -> Bool) -> [a] -> [[a]]
List.groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`Function.on` a -> key
key)

-- | Like 'groupAdjacent', but include the key.
keyedGroupAdjacent :: Eq key => (a -> key) -> [a] -> [(key, NonNull a)]
keyedGroupAdjacent :: forall key a. Eq key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupAdjacent a -> key
key =
    forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn (a -> key
key forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
List.head) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Bool) -> [a] -> [[a]]
List.groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`Function.on` a -> key
key)

groupAdjacentFst :: Eq a => [(a, b)] -> [(a, NonNull b)]
groupAdjacentFst :: forall a b. Eq a => [(a, b)] -> [(a, NonNull b)]
groupAdjacentFst [(a, b)]
xs =
    [(a
key, forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(a, b)]
group) | (a
key, [(a, b)]
group) <- forall key a. Eq key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupAdjacent forall a b. (a, b) -> a
fst [(a, b)]
xs]

groupAdjacentSnd :: Eq b => [(a, b)] -> [(NonNull a, b)]
groupAdjacentSnd :: forall b a. Eq b => [(a, b)] -> [(NonNull a, b)]
groupAdjacentSnd [(a, b)]
xs =
    [(forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(a, b)]
group, b
key) | (b
key, [(a, b)]
group) <- forall key a. Eq key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupAdjacent forall a b. (a, b) -> b
snd [(a, b)]
xs]

-- ** sort

-- Sort groups sort the input by the group key as a side-effect of grouping.

-- | Group the unsorted list into @(key x, xs)@ where all @xs@ compare equal
-- after @key@ is applied to them.
keyedGroupSort :: Ord key => (a -> key) -> [a] -> [(key, NonNull a)]
    -- ^ Sorted by key. The NonNull group is in the same order as the input.
keyedGroupSort :: forall key a. Ord key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupSort a -> key
key = forall k a. Map k a -> [(k, a)]
Map.toAscList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> Map key [a] -> Map key [a]
go forall k a. Map k a
Map.empty
    where go :: a -> Map key [a] -> Map key [a]
go a
x = forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Map.alter (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. b -> (a -> b) -> Maybe a -> b
maybe [a
x] (a
x:)) (a -> key
key a
x)

-- | Similar to 'keyedGroupSort', but key on the fst element, and strip the
-- key out of the groups.
groupFst :: Ord a => [(a, b)] -> [(a, NonNull b)]
groupFst :: forall a b. Ord a => [(a, b)] -> [(a, NonNull b)]
groupFst [(a, b)]
xs = [(a
key, forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(a, b)]
group) | (a
key, [(a, b)]
group) <- forall key a. Ord key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupSort forall a b. (a, b) -> a
fst [(a, b)]
xs]

-- | Like 'groupFst', but group on the snd element.
groupSnd :: Ord b => [(a, b)] -> [(NonNull a, b)]
groupSnd :: forall b a. Ord b => [(a, b)] -> [(NonNull a, b)]
groupSnd [(a, b)]
xs = [(forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(a, b)]
group, b
key) | (b
key, [(a, b)]
group) <- forall key a. Ord key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupSort forall a b. (a, b) -> b
snd [(a, b)]
xs]

-- | Like 'List.groupBy', but the list doesn't need to be sorted, and use a key
-- function instead of equality.  The list is sorted by the key, and the groups
-- appear in their original order in the input list.
groupSort :: Ord key => (a -> key) -> [a] -> [NonNull a]
groupSort :: forall key a. Ord key => (a -> key) -> [a] -> [[a]]
groupSort a -> key
key = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall key a. Ord key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupSort a -> key
key

-- ** stable

-- Stable groups preserve the original input order, in both the heads of the
-- groups, and within the groups themselves.

-- | Group each element with all the other elements that compare equal to it.
-- The heads of the groups appear in their original order.
groupStableWith :: (a -> a -> Bool) -> [a] -> [NonEmpty a]
groupStableWith :: forall a. (a -> a -> Bool) -> [a] -> [NonEmpty a]
groupStableWith a -> a -> Bool
is_equal = [a] -> [NonEmpty a]
go
    where
    go :: [a] -> [NonEmpty a]
go [] = []
    go (a
x:[a]
xs) = (a
x forall a. a -> [a] -> NonEmpty a
:| [a]
equal) forall a. a -> [a] -> [a]
: [a] -> [NonEmpty a]
go [a]
inequal
        where ([a]
equal, [a]
inequal) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition (a -> a -> Bool
is_equal a
x) [a]
xs

-- | 'groupStableWith' but with a key function.
groupStable :: Eq key => (a -> key) -> [a] -> [NonEmpty a]
groupStable :: forall key a. Eq key => (a -> key) -> [a] -> [NonEmpty a]
groupStable a -> key
key = forall a. (a -> a -> Bool) -> [a] -> [NonEmpty a]
groupStableWith (\a
x a
y -> a -> key
key a
x forall a. Eq a => a -> a -> Bool
== a -> key
key a
y)

keyedGroupStable :: Eq key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupStable :: forall key a. Eq key => (a -> key) -> [a] -> [(key, [a])]
keyedGroupStable a -> key
key = forall a b. (a -> b) -> [a] -> [b]
map (\(a
g :| [a]
gs) -> (a -> key
key a
g, a
gforall a. a -> [a] -> [a]
:[a]
gs)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall key a. Eq key => (a -> key) -> [a] -> [NonEmpty a]
groupStable a -> key
key

-- * zipping

-- | Pair each element with the following element.  The last element is paired
-- with Nothing.  Like @zip xs (drop 1 xs ++ [Nothing])@ but only traverses
-- @xs@ once.
zipNext :: [a] -> [(a, Maybe a)]
zipNext :: forall a. [a] -> [(a, Maybe a)]
zipNext [] = []
zipNext [a
x] = [(a
x, forall a. Maybe a
Nothing)]
zipNext (a
x : xs :: [a]
xs@(a
y:[a]
_)) = (a
x, forall a. a -> Maybe a
Just a
y) forall a. a -> [a] -> [a]
: forall a. [a] -> [(a, Maybe a)]
zipNext [a]
xs

zipNexts :: [a] -> [(a, [a])]
zipNexts :: forall a. [a] -> [(a, [a])]
zipNexts [a]
xs = forall a b. [a] -> [b] -> [(a, b)]
zip [a]
xs (forall a. Int -> [a] -> [a]
drop Int
1 (forall a. [a] -> [[a]]
List.tails [a]
xs))

zipPrev :: [a] -> [(Maybe a, a)]
zipPrev :: forall a. [a] -> [(Maybe a, a)]
zipPrev [a]
xs = forall a b. [a] -> [b] -> [(a, b)]
zip (forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall a. a -> Maybe a
Just [a]
xs) [a]
xs

-- | Like 'zipNext' but with both preceding and following elements.
zipNeighbors :: [a] -> [(Maybe a, a, Maybe a)]
zipNeighbors :: forall a. [a] -> [(Maybe a, a, Maybe a)]
zipNeighbors [] = []
zipNeighbors (a
x:[a]
xs) = (forall a. Maybe a
Nothing, a
x, forall a. [a] -> Maybe a
head [a]
xs) forall a. a -> [a] -> [a]
: forall {t}. t -> [t] -> [(Maybe t, t, Maybe t)]
go a
x [a]
xs
    where
    go :: t -> [t] -> [(Maybe t, t, Maybe t)]
go t
_ [] = []
    go t
prev [t
x] = [(forall a. a -> Maybe a
Just t
prev, t
x, forall a. Maybe a
Nothing)]
    go t
prev (t
x : xs :: [t]
xs@(t
y:[t]
_)) = (forall a. a -> Maybe a
Just t
prev, t
x, forall a. a -> Maybe a
Just t
y) forall a. a -> [a] -> [a]
: t -> [t] -> [(Maybe t, t, Maybe t)]
go t
x [t]
xs

-- | This is like 'zip', but it returns the remainder of the longer argument
-- instead of discarding it.
zipRemainder :: [a] -> [b] -> ([(a, b)], Either [a] [b])
zipRemainder :: forall a b. [a] -> [b] -> ([(a, b)], Either [a] [b])
zipRemainder (a
x:[a]
xs) (b
y:[b]
ys) = forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ((a
x, b
y) :) (forall a b. [a] -> [b] -> ([(a, b)], Either [a] [b])
zipRemainder [a]
xs [b]
ys)
zipRemainder [] [b]
ys = ([], forall a b. b -> Either a b
Right [b]
ys)
zipRemainder [a]
xs [] = ([], forall a b. a -> Either a b
Left [a]
xs)

-- | Return the reversed inits paired with the tails.  This is like a zipper
-- moving focus along the input list.
zipper :: [a] -> [a] -> [([a], [a])]
zipper :: forall a. [a] -> [a] -> [([a], [a])]
zipper [a]
prev [] = [([a]
prev, [])]
zipper [a]
prev lst :: [a]
lst@(a
x:[a]
xs) = ([a]
prev, [a]
lst) forall a. a -> [a] -> [a]
: forall a. [a] -> [a] -> [([a], [a])]
zipper (a
xforall a. a -> [a] -> [a]
:[a]
prev) [a]
xs

-- * Paired

data Paired a b = First !a | Second !b | Both !a !b
    deriving (Int -> Paired a b -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> Paired a b -> ShowS
forall a b. (Show a, Show b) => [Paired a b] -> ShowS
forall a b. (Show a, Show b) => Paired a b -> [Char]
showList :: [Paired a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [Paired a b] -> ShowS
show :: Paired a b -> [Char]
$cshow :: forall a b. (Show a, Show b) => Paired a b -> [Char]
showsPrec :: Int -> Paired a b -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> Paired a b -> ShowS
Show, Paired a b -> Paired a b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b. (Eq a, Eq b) => Paired a b -> Paired a b -> Bool
/= :: Paired a b -> Paired a b -> Bool
$c/= :: forall a b. (Eq a, Eq b) => Paired a b -> Paired a b -> Bool
== :: Paired a b -> Paired a b -> Bool
$c== :: forall a b. (Eq a, Eq b) => Paired a b -> Paired a b -> Bool
Eq)

instance Bifunctor Paired where
    bimap :: forall a b c d. (a -> b) -> (c -> d) -> Paired a c -> Paired b d
bimap a -> b
f c -> d
g Paired a c
paired = case Paired a c
paired of
        First a
a -> forall a b. a -> Paired a b
First (a -> b
f a
a)
        Second c
b -> forall a b. b -> Paired a b
Second (c -> d
g c
b)
        Both a
a c
b -> forall a b. a -> b -> Paired a b
Both (a -> b
f a
a) (c -> d
g c
b)

pairedSecond :: Paired a b -> Maybe b
pairedSecond :: forall a b. Paired a b -> Maybe b
pairedSecond (First a
_) = forall a. Maybe a
Nothing
pairedSecond (Second b
b) = forall a. a -> Maybe a
Just b
b
pairedSecond (Both a
_ b
b) = forall a. a -> Maybe a
Just b
b

pairedFirst :: Paired a b -> Maybe a
pairedFirst :: forall a b. Paired a b -> Maybe a
pairedFirst (First a
a) = forall a. a -> Maybe a
Just a
a
pairedFirst (Second b
_) = forall a. Maybe a
Nothing
pairedFirst (Both a
a b
_) = forall a. a -> Maybe a
Just a
a

partitionPaired :: [Paired a b] -> ([a], [b])
partitionPaired :: forall a b. [Paired a b] -> ([a], [b])
partitionPaired (Paired a b
pair : [Paired a b]
pairs) = case Paired a b
pair of
    Both a
a b
b -> (a
a forall a. a -> [a] -> [a]
: [a]
as, b
b forall a. a -> [a] -> [a]
: [b]
bs)
    First a
a -> (a
a forall a. a -> [a] -> [a]
: [a]
as, [b]
bs)
    Second b
b -> ([a]
as, b
b forall a. a -> [a] -> [a]
: [b]
bs)
    where ([a]
as, [b]
bs) = forall a b. [Paired a b] -> ([a], [b])
partitionPaired [Paired a b]
pairs
partitionPaired [] = ([], [])

-- | Like 'zip', but emit 'First's or 'Second's if the list lengths are
-- unequal.
zipPadded :: [a] -> [b] -> [Paired a b]
zipPadded :: forall a b. [a] -> [b] -> [Paired a b]
zipPadded [] [] = []
zipPadded [] [b]
bs = forall a b. (a -> b) -> [a] -> [b]
map forall a b. b -> Paired a b
Second [b]
bs
zipPadded [a]
as [] = forall a b. (a -> b) -> [a] -> [b]
map forall a b. a -> Paired a b
First [a]
as
zipPadded (a
a:[a]
as) (b
b:[b]
bs) = forall a b. a -> b -> Paired a b
Both a
a b
b forall a. a -> [a] -> [a]
: forall a b. [a] -> [b] -> [Paired a b]
zipPadded [a]
as [b]
bs

-- | Like 'zip', but the first list is padded with Nothings.
zipPaddedFst :: [a] -> [b] -> [(Maybe a, b)]
zipPaddedFst :: forall a b. [a] -> [b] -> [(Maybe a, b)]
zipPaddedFst [a]
_ [] = []
zipPaddedFst (a
a:[a]
as) (b
b:[b]
bs) = (forall a. a -> Maybe a
Just a
a, b
b) forall a. a -> [a] -> [a]
: forall a b. [a] -> [b] -> [(Maybe a, b)]
zipPaddedFst [a]
as [b]
bs
zipPaddedFst [] (b
b:[b]
bs) = forall a b. (a -> b) -> [a] -> [b]
map ((,) forall a. Maybe a
Nothing) (b
bforall a. a -> [a] -> [a]
:[b]
bs)

-- | Like 'zip', but the second list is padded with Nothings.
zipPaddedSnd :: [a] -> [b] -> [(a, Maybe b)]
zipPaddedSnd :: forall a b. [a] -> [b] -> [(a, Maybe b)]
zipPaddedSnd [] [b]
_ = []
zipPaddedSnd (a
a:[a]
as) (b
b:[b]
bs) = (a
a, forall a. a -> Maybe a
Just b
b) forall a. a -> [a] -> [a]
: forall a b. [a] -> [b] -> [(a, Maybe b)]
zipPaddedSnd [a]
as [b]
bs
zipPaddedSnd (a
a:[a]
as) [] = [(a
a, forall a. Maybe a
Nothing) | a
a <- a
a forall a. a -> [a] -> [a]
: [a]
as]

-- | Perform a Meyes diff.
diff :: (a -> b -> Bool) -> [a] -> [b] -> [Paired a b]
diff :: forall a b. (a -> b -> Bool) -> [a] -> [b] -> [Paired a b]
diff a -> b -> Bool
eq [a]
as [b]
bs = forall a b. (a -> b) -> [a] -> [b]
map forall {a} {b}. PolyDiff a b -> Paired a b
convert forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b -> Bool) -> [a] -> [b] -> [PolyDiff a b]
Diff.getDiffBy a -> b -> Bool
eq [a]
as [b]
bs
    where
    convert :: PolyDiff a b -> Paired a b
convert PolyDiff a b
a = case PolyDiff a b
a of
        Diff.First a
a -> forall a b. a -> Paired a b
First a
a
        Diff.Second b
b -> forall a b. b -> Paired a b
Second b
b
        Diff.Both a
a b
b -> forall a b. a -> b -> Paired a b
Both a
a b
b

-- | Left if the val was in the left list but not the right, Right for the
-- converse.
diffEither :: (a -> b -> Bool) -> [a] -> [b] -> [Either a b]
diffEither :: forall a b. (a -> b -> Bool) -> [a] -> [b] -> [Either a b]
diffEither a -> b -> Bool
eq [a]
as [b]
bs = forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe forall {a} {b}. Paired a b -> Maybe (Either a b)
to_either forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b -> Bool) -> [a] -> [b] -> [Paired a b]
diff a -> b -> Bool
eq [a]
as [b]
bs
    where
    to_either :: Paired a b -> Maybe (Either a b)
to_either (First a
a) = forall a. a -> Maybe a
Just (forall a b. a -> Either a b
Left a
a)
    to_either (Second b
a) = forall a. a -> Maybe a
Just (forall a b. b -> Either a b
Right b
a)
    to_either Paired a b
_ = forall a. Maybe a
Nothing

-- | This is like 'diff', except that the index of each pair in the
-- /right/ list is included.  So the index is where you should delete or
-- add the element to turn as into bs:
--
-- * @(i, Second b)@, @i@ is the position of @b@ in @bs@.
--
-- * @(i, First a)@, @i@ is where @a@ was deleted from @bs@.
diffIndex :: (a -> b -> Bool) -> [a] -> [b] -> [(Int, Paired a b)]
diffIndex :: forall a b. (a -> b -> Bool) -> [a] -> [b] -> [(Int, Paired a b)]
diffIndex a -> b -> Bool
eq [a]
as [b]
bs = forall a b. [a] -> [b] -> [(a, b)]
zip (forall {a} {b}. [Paired a b] -> [Int]
indexed [Paired a b]
pairs) [Paired a b]
pairs
    where
    pairs :: [Paired a b]
pairs = forall a b. (a -> b -> Bool) -> [a] -> [b] -> [Paired a b]
diff a -> b -> Bool
eq [a]
as [b]
bs
    indexed :: [Paired a b] -> [Int]
indexed = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall {p} {a} {b}. Num p => p -> Paired a b -> p
f Int
0
        where
        f :: p -> Paired a b -> p
f p
i (First a
_) = p
i
        f p
i Paired a b
_ = p
iforall a. Num a => a -> a -> a
+p
1

diffIndexOn :: Eq k => (a -> k) -> [a] -> [a] -> [(Int, Paired a a)]
diffIndexOn :: forall k a. Eq k => (a -> k) -> [a] -> [a] -> [(Int, Paired a a)]
diffIndexOn a -> k
key = forall a b. (a -> b -> Bool) -> [a] -> [b] -> [(Int, Paired a b)]
diffIndex (\a
a a
b -> a -> k
key a
a forall a. Eq a => a -> a -> Bool
== a -> k
key a
b)

-- | Pair up two lists of sorted pairs by their first element.
pairSorted :: Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted :: forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted [(k, a)]
xs [] = [(k
k, forall a b. a -> Paired a b
First a
v) | (k
k, a
v) <- [(k, a)]
xs]
pairSorted [] [(k, b)]
ys = [(k
k, forall a b. b -> Paired a b
Second b
v) | (k
k, b
v) <- [(k, b)]
ys]
pairSorted x :: [(k, a)]
x@((k
k0, a
v0) : [(k, a)]
xs) y :: [(k, b)]
y@((k
k1, b
v1) : [(k, b)]
ys)
    | k
k0 forall a. Eq a => a -> a -> Bool
== k
k1 = (k
k0, forall a b. a -> b -> Paired a b
Both a
v0 b
v1) forall a. a -> [a] -> [a]
: forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted [(k, a)]
xs [(k, b)]
ys
    | k
k0 forall a. Ord a => a -> a -> Bool
< k
k1 = (k
k0, forall a b. a -> Paired a b
First a
v0) forall a. a -> [a] -> [a]
: forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted [(k, a)]
xs [(k, b)]
y
    | Bool
otherwise = (k
k1, forall a b. b -> Paired a b
Second b
v1) forall a. a -> [a] -> [a]
: forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted [(k, a)]
x [(k, b)]
ys

-- | Like 'pairSorted', but use a key function, and omit the extracted key.
pairSortedOn1 :: Ord k => (a -> k) -> [a] -> [a] -> [Paired a a]
pairSortedOn1 :: forall k a. Ord k => (a -> k) -> [a] -> [a] -> [Paired a a]
pairSortedOn1 a -> k
key = forall k a b.
Ord k =>
(a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairSortedOn a -> k
key a -> k
key

-- | Like 'pairSorted', but use a key function, and omit the extracted key.
pairSortedOn :: Ord k => (a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairSortedOn :: forall k a b.
Ord k =>
(a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairSortedOn a -> k
key1 b -> k
key2 [a]
xs [b]
ys =
    forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted (forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn a -> k
key1 [a]
xs) (forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn b -> k
key2 [b]
ys)

-- | Sort the lists on with the key functions, then pair them up.
pairOn :: Ord k => (a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairOn :: forall k a b.
Ord k =>
(a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairOn a -> k
k1 b -> k
k2 [a]
xs [b]
ys = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$
    forall k a b. Ord k => [(k, a)] -> [(k, b)] -> [(k, Paired a b)]
pairSorted (forall k a. Ord k => (a -> k) -> [a] -> [a]
sortOn forall a b. (a, b) -> a
fst (forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn a -> k
k1 [a]
xs)) (forall k a. Ord k => (a -> k) -> [a] -> [a]
sortOn forall a b. (a, b) -> a
fst (forall a k. (a -> k) -> [a] -> [(k, a)]
keyOn b -> k
k2 [b]
ys))

-- | Like 'pairOn', but when the lists have the same type.
pairOn1 :: Ord k => (a -> k) -> [a] -> [a] -> [Paired a a]
pairOn1 :: forall k a. Ord k => (a -> k) -> [a] -> [a] -> [Paired a a]
pairOn1 a -> k
k = forall k a b.
Ord k =>
(a -> k) -> (b -> k) -> [a] -> [b] -> [Paired a b]
pairOn a -> k
k a -> k
k

-- * partition

-- | Like 'List.partition', but partition by two functions consecutively.
partition2 :: (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a], [a])
partition2 :: forall a. (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a], [a])
partition2 a -> Bool
f1 a -> Bool
f2 [a]
xs = ([a]
as, [a]
bs, [a]
xs3)
    where
    ([a]
as, [a]
xs2) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition a -> Bool
f1 [a]
xs
    ([a]
bs, [a]
xs3) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition a -> Bool
f2 [a]
xs2

-- | Partition and transform at the same time.
partitionOn :: (a -> Maybe b) -> [a] -> ([b], [a])
partitionOn :: forall a b. (a -> Maybe b) -> [a] -> ([b], [a])
partitionOn a -> Maybe b
f = [a] -> ([b], [a])
go
    where
    go :: [a] -> ([b], [a])
go [] = ([], [])
    go (a
x:[a]
xs) = case a -> Maybe b
f a
x of
        Just b
b -> (b
bforall a. a -> [a] -> [a]
:[b]
bs, [a]
as)
        Maybe b
Nothing -> ([b]
bs, a
xforall a. a -> [a] -> [a]
:[a]
as)
        where ([b]
bs, [a]
as) = [a] -> ([b], [a])
go [a]
xs

-- * sublists

-- | Split into groups of a certain size.
chunked :: Int -> [a] -> [[a]]
chunked :: forall a. Int -> [a] -> [[a]]
chunked Int
n [a]
xs = case forall a. Int -> [a] -> ([a], [a])
splitAt Int
n [a]
xs of
    ([], []) -> []
    ([a]
pre, []) -> [[a]
pre]
    ([a]
pre, [a]
post) -> [a]
pre forall a. a -> [a] -> [a]
: forall a. Int -> [a] -> [[a]]
chunked Int
n [a]
post


-- | Take a list of rows to a list of columns.  This is like a zip except
-- for variable-length lists.  Similar to zip, the result is trimmed to the
-- length of the shortest row.
--
-- 'List.transpose' is similar, but it skips missing elements, instead of
-- truncating all to the shortest.  Skipping means you lose what column the
-- element came from.
rotate :: [[a]] -> [[a]]
rotate :: forall a. [[a]] -> [[a]]
rotate [] = []
rotate [[a]]
xs = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall a. a -> [a] -> [a]
: forall a. [[a]] -> [[a]]
rotate (forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> [a]
List.tail [[a]]
xs)) (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall a. [a] -> Maybe a
head [[a]]
xs)

-- | Similar to 'rotate', except that the result is the length of the longest
-- row and missing columns are Nothing.  Analogous to 'zip_padded'.
rotate2 :: [[a]] -> [[Maybe a]]
rotate2 :: forall a. [[a]] -> [[Maybe a]]
rotate2 [[a]]
xs
    | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all forall a. Maybe a -> Bool
Maybe.isNothing [Maybe a]
heads = []
    | Bool
otherwise = [Maybe a]
heads forall a. a -> [a] -> [a]
: forall a. [[a]] -> [[Maybe a]]
rotate2 (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Int -> [a] -> [a]
drop Int
1) [[a]]
xs)
    where heads :: [Maybe a]
heads = forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Maybe a
head [[a]]
xs

-- * prefix / suffix

-- | Drop until the last element before or equal to the given element.
dropBefore :: Ord key => (a -> key) -> key -> [a] -> [a]
dropBefore :: forall key a. Ord key => (a -> key) -> key -> [a] -> [a]
dropBefore a -> key
key key
p = [a] -> [a]
go
    where
    go :: [a] -> [a]
go [] = []
    go (a
x0 : [a]
xs)
        | key
p forall a. Ord a => a -> a -> Bool
< a -> key
key a
x0 = a
x0 forall a. a -> [a] -> [a]
: [a]
xs
        | Bool
otherwise = case [a]
xs of
            a
x1 : [a]
_ | key
p forall a. Ord a => a -> a -> Bool
>= a -> key
key a
x1 -> [a] -> [a]
go [a]
xs
            [a]
_ -> a
x0 forall a. a -> [a] -> [a]
: [a]
xs

-- | If the list doesn't have the given prefix, return the original list and
-- False.  Otherwise, strip it off and return True.  'List.stripPrefix' is an
-- alternate version.
dropPrefix :: Eq a => [a] -> [a] -> ([a], Bool)
dropPrefix :: forall a. Eq a => [a] -> [a] -> ([a], Bool)
dropPrefix [a]
pref [a]
list = [a] -> [a] -> ([a], Bool)
go [a]
pref [a]
list
    where
    go :: [a] -> [a] -> ([a], Bool)
go [] [a]
xs = ([a]
xs, Bool
True)
    go [a]
_ [] = ([a]
list, Bool
False)
    go (a
p:[a]
ps) (a
x:[a]
xs)
        | a
p forall a. Eq a => a -> a -> Bool
== a
x = [a] -> [a] -> ([a], Bool)
go [a]
ps [a]
xs
        | Bool
otherwise = ([a]
list, Bool
False)

dropSuffix :: Eq a => [a] -> [a] -> ([a], Bool)
dropSuffix :: forall a. Eq a => [a] -> [a] -> ([a], Bool)
dropSuffix [a]
suffix [a]
list
    | [a]
post forall a. Eq a => a -> a -> Bool
== [a]
suffix = ([a]
pre, Bool
True)
    | Bool
otherwise = ([a]
list, Bool
False)
    where ([a]
pre, [a]
post) = forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
list forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
suffix) [a]
list

-- * permutations

-- | The cartesian product of a list of lists.  E.g.
-- @[[1, 2], [3, 4]]@ -> @[[1, 3], [1, 4], [2, 3], [2, 4]]@.
cartesian :: [[a]] -> [[a]]
cartesian :: forall a. [[a]] -> [[a]]
cartesian [] = []
cartesian [[a]
xs] = [[a
x] | a
x <- [a]
xs]
cartesian ([a]
xs:[[a]]
rest) = [a
xforall a. a -> [a] -> [a]
:[a]
ps | a
x <- [a]
xs, [a]
ps <- forall a. [[a]] -> [[a]]
cartesian [[a]]
rest]

-- * enumeration

enumerate :: [a] -> [(Int, a)]
enumerate :: forall a. [a] -> [(Int, a)]
enumerate = forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..]

-- * sublists

takeEnd :: Int -> [a] -> [a]
takeEnd :: forall a. Int -> [a] -> [a]
takeEnd Int
n = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a} {a}. (Ord a, Num a) => a -> (a, [a]) -> (a, [a])
go (Int
n, [])
    where
    go :: a -> (a, [a]) -> (a, [a])
go a
x (a
n, [a]
xs)
        | a
n forall a. Ord a => a -> a -> Bool
<= a
0 = (a
0, [a]
xs)
        | Bool
otherwise = (a
n forall a. Num a => a -> a -> a
- a
1, a
x forall a. a -> [a] -> [a]
: [a]
xs)

dropEnd :: Int -> [a] -> [a]
dropEnd :: forall a. Int -> [a] -> [a]
dropEnd Int
n = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id (forall a b. a -> b -> a
const []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {b} {a}. (Ord b, Num b) => a -> Either [a] b -> Either [a] b
f (forall a b. b -> Either a b
Right Int
n)
    where
    f :: a -> Either [a] b -> Either [a] b
f a
x (Right b
n)
        | b
n forall a. Ord a => a -> a -> Bool
<= b
0 = forall a b. a -> Either a b
Left [a
x]
        | Bool
otherwise = forall a b. b -> Either a b
Right (b
nforall a. Num a => a -> a -> a
-b
1)
    f a
x (Left [a]
xs) = forall a b. a -> Either a b
Left (a
xforall a. a -> [a] -> [a]
:[a]
xs)

takeWhileEnd :: (a -> Bool) -> [a] -> [a]
takeWhileEnd :: forall a. (a -> Bool) -> [a] -> [a]
takeWhileEnd a -> Bool
f = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id (forall a b. a -> b -> a
const []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> Either [a] [a] -> Either [a] [a]
go (forall a b. b -> Either a b
Right [])
    where
    -- Left means I'm done taking.
    go :: a -> Either [a] [a] -> Either [a] [a]
go a
_ (Left [a]
xs) = forall a b. a -> Either a b
Left [a]
xs
    go a
x (Right [a]
xs)
        | a -> Bool
f a
x = forall a b. b -> Either a b
Right (a
xforall a. a -> [a] -> [a]
:[a]
xs)
        | Bool
otherwise = forall a b. a -> Either a b
Left [a]
xs

-- * split / join

splitWith :: (a -> Maybe b) -> [a] -> ([a], [(b, [a])])
splitWith :: forall a b. (a -> Maybe b) -> [a] -> ([a], [(b, [a])])
splitWith a -> Maybe b
match = [a] -> ([a], [(b, [a])])
go1
    where
    go1 :: [a] -> ([a], [(b, [a])])
go1 [a]
as = case forall a b. (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
breakWith a -> Maybe b
match [a]
as of
        ([a]
pre, Maybe (b, [a])
Nothing) -> ([a]
pre, [])
        ([a]
pre, Just (b
b, [a]
post)) -> ([a]
pre, b -> [a] -> [(b, [a])]
go2 b
b [a]
post)
    go2 :: b -> [a] -> [(b, [a])]
go2 b
b0 [a]
as = case forall a b. (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
breakWith a -> Maybe b
match [a]
as of
        ([a]
pre, Maybe (b, [a])
Nothing) -> [(b
b0, [a]
pre)]
        ([a]
pre, Just (b
b1, [a]
post)) -> (b
b0, [a]
pre) forall a. a -> [a] -> [a]
: b -> [a] -> [(b, [a])]
go2 b
b1 [a]
post

breakWith :: (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
breakWith :: forall a b. (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
breakWith a -> Maybe b
f = [a] -> ([a], Maybe (b, [a]))
go
    where
    go :: [a] -> ([a], Maybe (b, [a]))
go (a
a : [a]
as) = case a -> Maybe b
f a
a of
        Just b
b -> ([], forall a. a -> Maybe a
Just (b
b, [a]
as))
        Maybe b
Nothing -> forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (a
a:) ([a] -> ([a], Maybe (b, [a]))
go [a]
as)
    go [] = ([], forall a. Maybe a
Nothing)


-- * transform

-- | Like 'List.mapAccumL', but monadic.  Strict in the accumulator.
mapAccumLM :: Monad m => (state -> x -> m (state, y)) -> state -> [x]
    -> m (state, [y])
mapAccumLM :: forall (m :: * -> *) state x y.
Monad m =>
(state -> x -> m (state, y)) -> state -> [x] -> m (state, [y])
mapAccumLM state -> x -> m (state, y)
f = state -> [x] -> m (state, [y])
go
    where
    go :: state -> [x] -> m (state, [y])
go !state
state [] = forall (m :: * -> *) a. Monad m => a -> m a
return (state
state, [])
    go !state
state (x
x:[x]
xs) = do
        (state
state, y
y) <- state -> x -> m (state, y)
f state
state x
x
        (state
state, [y]
ys) <- state -> [x] -> m (state, [y])
go state
state [x]
xs
        forall (m :: * -> *) a. Monad m => a -> m a
return (state
state, y
y forall a. a -> [a] -> [a]
: [y]
ys)

-- ** split and join

-- | Split before places where the function matches.
--
-- > > splitBefore (==1) [1, 2, 1]
-- > [[], [1, 2], [1]]
splitBefore :: (a -> Bool) -> [a] -> [[a]]
splitBefore :: forall a. (a -> Bool) -> [a] -> [[a]]
splitBefore a -> Bool
f = [a] -> [[a]]
go
    where
    go :: [a] -> [[a]]
go [] = []
    go [a]
xs0 = [a]
pre forall a. a -> [a] -> [a]
: case [a]
post of
        a
x : [a]
xs -> forall {a}. a -> [[a]] -> [[a]]
cons1 a
x ([a] -> [[a]]
go [a]
xs)
        [] -> []
        where ([a]
pre, [a]
post) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break a -> Bool
f [a]
xs0
    cons1 :: a -> [[a]] -> [[a]]
cons1 a
x [] = [[a
x]]
    cons1 a
x ([a]
g:[[a]]
gs) = (a
xforall a. a -> [a] -> [a]
:[a]
g) forall a. a -> [a] -> [a]
: [[a]]
gs

-- | Split @xs@ on @sep@, dropping @sep@ from the result.
split :: Eq a => NonNull a -> [a] -> NonNull [a]
split :: forall a. Eq a => NonNull a -> NonNull a -> NonNull (NonNull a)
split [] = forall a. HasCallStack => [Char] -> a
error [Char]
"Util.Lists.split: empty separator"
split [a]
sep = [a] -> [[a]]
go
    where
    go :: [a] -> [[a]]
go [a]
xs
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
post = [[a]
pre]
        | Bool
otherwise = [a]
pre forall a. a -> [a] -> [a]
: [a] -> [[a]]
go (forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
sep) [a]
post)
        where ([a]
pre, [a]
post) = forall a. ([a] -> Bool) -> [a] -> ([a], [a])
breakTails ([a]
sep `List.isPrefixOf`) [a]
xs

-- | Like 'split', but split on a single element.
split1 :: Eq a => a -> [a] -> [[a]]
split1 :: forall a. Eq a => a -> [a] -> [[a]]
split1 a
sep = [a] -> [[a]]
go
    where
    go :: [a] -> [[a]]
go [a]
xs
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
post = [[a]
pre]
        | Bool
otherwise = [a]
pre forall a. a -> [a] -> [a]
: [a] -> [[a]]
go (forall a. Int -> [a] -> [a]
drop Int
1 [a]
post)
        where ([a]
pre, [a]
post) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
==a
sep) [a]
xs

-- | Interspense a separator and concat.
join :: Monoid a => a -> [a] -> a
join :: forall a. Monoid a => a -> [a] -> a
join a
sep = forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
List.intersperse a
sep

-- | Split the list on the points where the given function returns true.
--
-- This is similar to 'groupBy', except this is defined to compare adjacent
-- elements.  'groupBy' actually compares to the first element of each group.
-- E.g. you can't group numeric runs with @groupBy (\a b -> b > a+1)@.
splitBetween :: (a -> a -> Bool) -> [a] -> [[a]]
splitBetween :: forall a. (a -> a -> Bool) -> [a] -> [[a]]
splitBetween a -> a -> Bool
_ [] = []
splitBetween a -> a -> Bool
f [a]
xs = [a]
pre forall a. a -> [a] -> [a]
: forall a. (a -> a -> Bool) -> [a] -> [[a]]
splitBetween a -> a -> Bool
f [a]
post
    where ([a]
pre, [a]
post) = forall a. (a -> a -> Bool) -> [a] -> ([a], [a])
breakBetween a -> a -> Bool
f [a]
xs

breakBetween :: (a -> a -> Bool) -> [a] -> ([a], [a])
breakBetween :: forall a. (a -> a -> Bool) -> [a] -> ([a], [a])
breakBetween a -> a -> Bool
f (a
x1 : xs :: [a]
xs@(a
x2:[a]
_))
    | a -> a -> Bool
f a
x1 a
x2 = ([a
x1], [a]
xs)
    | Bool
otherwise = let ([a]
pre, [a]
post) = forall a. (a -> a -> Bool) -> [a] -> ([a], [a])
breakBetween a -> a -> Bool
f [a]
xs in (a
x1 forall a. a -> [a] -> [a]
: [a]
pre, [a]
post)
breakBetween a -> a -> Bool
_ [a]
xs = ([a]
xs, [])

-- * span and break

-- | Like 'break', but the called function has access to the entire tail.
breakTails :: ([a] -> Bool) -> [a] -> ([a], [a])
breakTails :: forall a. ([a] -> Bool) -> [a] -> ([a], [a])
breakTails [a] -> Bool
_ [] = ([], [])
breakTails [a] -> Bool
f lst :: [a]
lst@(a
x:[a]
xs)
    | [a] -> Bool
f [a]
lst = ([], [a]
lst)
    | Bool
otherwise = let ([a]
pre, [a]
post) = forall a. ([a] -> Bool) -> [a] -> ([a], [a])
breakTails [a] -> Bool
f [a]
xs in (a
xforall a. a -> [a] -> [a]
:[a]
pre, [a]
post)

-- | Like 'span', but it can transform the spanned sublist.
spanWhile :: (a -> Maybe b) -> [a] -> ([b], [a])
spanWhile :: forall a b. (a -> Maybe b) -> [a] -> ([b], [a])
spanWhile a -> Maybe b
f = [a] -> ([b], [a])
go
    where
    go :: [a] -> ([b], [a])
go [] = ([], [])
    go (a
a:[a]
as) = case a -> Maybe b
f a
a of
        Just b
b -> forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (b
b:) ([a] -> ([b], [a])
go [a]
as)
        Maybe b
Nothing -> ([], a
a forall a. a -> [a] -> [a]
: [a]
as)

-- * duplicates

-- | Drop adjacent elts if they are equal after applying the key function.
-- The first elt is kept.
dropDups :: Eq k => (a -> k) -> [a] -> [a]
dropDups :: forall k a. Eq k => (a -> k) -> [a] -> [a]
dropDups a -> k
_ [] = []
dropDups a -> k
key (a
x:[a]
xs) = a
x forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, a) -> Bool
equal) (forall a b. [a] -> [b] -> [(a, b)]
zip (a
xforall a. a -> [a] -> [a]
:[a]
xs) [a]
xs))
    where equal :: (a, a) -> Bool
equal (a
a, a
b) = a -> k
key a
a forall a. Eq a => a -> a -> Bool
== a -> k
key a
b

-- | Filter out elts when the predicate is true for adjacent elts.  The first
-- elt is kept, and the later ones are dropped.  This is like 'dropDups'
-- except it can compare two elements.  E.g. @dropWith (>=)@ will ensure the
-- sequence is increasing.
dropWith :: (a -> a -> Bool) -> [a] -> [a]
dropWith :: forall a. (a -> a -> Bool) -> [a] -> [a]
dropWith a -> a -> Bool
_ [] = []
dropWith a -> a -> Bool
_ [a
x] = [a
x]
dropWith a -> a -> Bool
f (a
x:a
y:[a]
xs)
    | a -> a -> Bool
f a
x a
y = forall a. (a -> a -> Bool) -> [a] -> [a]
dropWith a -> a -> Bool
f (a
xforall a. a -> [a] -> [a]
:[a]
xs)
    | Bool
otherwise = a
x forall a. a -> [a] -> [a]
: forall a. (a -> a -> Bool) -> [a] -> [a]
dropWith a -> a -> Bool
f (a
yforall a. a -> [a] -> [a]
:[a]
xs)

-- | Sort the input by the key, extract unique values, and also return the
-- duplicates.
partitionDups :: Ord k => (a -> k) -> [a] -> ([a], [(a, NonNull a)])
    -- ^ ([unique], [(used_for_unique, [dups])])
partitionDups :: forall k a. Ord k => (a -> k) -> [a] -> ([a], [(a, [a])])
partitionDups a -> k
key [a]
xs =
    forall a b. [Either a b] -> ([a], [b])
Either.partitionEithers forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. [a] -> [Either a (a, [a])]
extract (forall key a. Ord key => (a -> key) -> [a] -> [[a]]
groupSort a -> k
key [a]
xs)
    where
    extract :: [a] -> [Either a (a, [a])]
extract [] = []
    extract [a
x] = [forall a b. a -> Either a b
Left a
x]
    extract (a
x:[a]
xs) = [forall a b. a -> Either a b
Left a
x, forall a b. b -> Either a b
Right (a
x, [a]
xs)]

-- | Find duplicate values.  There are always at least 2 of each output.
findDups :: Ord k => (a -> k) -> [a] -> [(a, NonEmpty a)]
findDups :: forall k a. Ord k => (a -> k) -> [a] -> [(a, NonEmpty a)]
findDups a -> k
key = forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe forall {a}. [a] -> Maybe (a, NonEmpty a)
extract forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall key a. Ord key => (a -> key) -> [a] -> [[a]]
groupSort a -> k
key
    where
    extract :: [a] -> Maybe (a, NonEmpty a)
extract [] = forall a. Maybe a
Nothing
    extract [a
_] = forall a. Maybe a
Nothing
    extract (a
x1:a
x2:[a]
xs) = forall a. a -> Maybe a
Just (a
x1, a
x2 forall a. a -> [a] -> NonEmpty a
:| [a]
xs)

-- | Like 'dropDups', but keep the last adjacent equal elt instead of the
-- first.
dropInitialDups :: Eq k => (a -> k) -> [a] -> [a]
dropInitialDups :: forall k a. Eq k => (a -> k) -> [a] -> [a]
dropInitialDups a -> k
_ [] = []
dropInitialDups a -> k
_ [a
x] = [a
x]
dropInitialDups a -> k
key (a
x:xs :: [a]
xs@(a
next:[a]
_))
    | a -> k
key a
x forall a. Eq a => a -> a -> Bool
== a -> k
key a
next = [a]
rest
    | Bool
otherwise = a
xforall a. a -> [a] -> [a]
:[a]
rest
    where rest :: [a]
rest = forall k a. Eq k => (a -> k) -> [a] -> [a]
dropInitialDups a -> k
key [a]
xs

unique :: Ord a => [a] -> [a]
unique :: forall a. Ord a => [a] -> [a]
unique = forall k a. Ord k => (a -> k) -> [a] -> [a]
uniqueOn forall a. a -> a
id

-- | This is like 'dropDups', except that it's not limited to just adjacent
-- elts.  The output list is in the same order as the input.
uniqueOn :: Ord k => (a -> k) -> [a] -> [a]
uniqueOn :: forall k a. Ord k => (a -> k) -> [a] -> [a]
uniqueOn a -> k
f [a]
xs = Set k -> [a] -> [a]
go forall a. Set a
Set.empty [a]
xs
    where
    go :: Set k -> [a] -> [a]
go Set k
_set [] = []
    go Set k
set (a
x:[a]
xs)
        | k
k forall a. Ord a => a -> Set a -> Bool
`Set.member` Set k
set = Set k -> [a] -> [a]
go Set k
set [a]
xs
        | Bool
otherwise = a
x forall a. a -> [a] -> [a]
: Set k -> [a] -> [a]
go (forall a. Ord a => a -> Set a -> Set a
Set.insert k
k Set k
set) [a]
xs
        where k :: k
k = a -> k
f a
x

-- | Like 'unique', but sort the list, and should be more efficient.
uniqueSort :: Ord a => [a] -> [a]
uniqueSort :: forall a. Ord a => [a] -> [a]
uniqueSort = forall a. Set a -> [a]
Set.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Set a
Set.fromList


-- * replace

-- | Replace sublist @from@ with @to@ in the given list.
replace :: Eq a => [a] -> [a] -> [a] -> [a]
replace :: forall a. Eq a => [a] -> [a] -> [a] -> [a]
replace [a]
from [a]
to = [a] -> [a]
go
    where
    len :: Int
len = forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
from
    go :: [a] -> [a]
go [] = []
    go lst :: [a]
lst@(a
x:[a]
xs)
        | [a]
from forall a. Eq a => [a] -> [a] -> Bool
`List.isPrefixOf` [a]
lst = [a]
to forall a. [a] -> [a] -> [a]
++ [a] -> [a]
go (forall a. Int -> [a] -> [a]
drop Int
len [a]
lst)
        | Bool
otherwise = a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs

-- | Replace occurrances of an element with zero or more other elements.
replace1 :: Eq a => a -> [a] -> [a] -> [a]
replace1 :: forall a. Eq a => a -> [a] -> [a] -> [a]
replace1 a
from [a]
to = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\a
v -> if a
v forall a. Eq a => a -> a -> Bool
== a
from then [a]
to else [a
v])


-- * search

count :: Foldable t => (a -> Bool) -> t a -> Int
count :: forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Int
count a -> Bool
f = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\Int
n a
c -> if a -> Bool
f a
c then Int
n forall a. Num a => a -> a -> a
+ Int
1 else Int
n) Int
0