{-# LANGUAGE ScopedTypeVariables
,TypeFamilies
,MultiParamTypeClasses
,FunctionalDependencies
,FlexibleInstances
,BangPatterns
,FlexibleContexts
,ConstraintKinds
,CPP #-}
{-# LANGUAGE TypeOperators #-}
module Data.ListLike.Base
(
ListLike(..), ListOps,
toList, fromList,
InfiniteListLike(..),
zip, zipWith, sequence_
) where
import Prelude
( Applicative(..), Bool(..), Eq(..), Int, Integer, Integral
, Maybe(..), Monad, Monoid(..), Num(..), Ord(..), Ordering(..)
, ($), (.), (&&), (||), (++), asTypeOf, error, flip, fst, snd
, id, maybe, max, min, not, otherwise
, sequenceA
)
#if MIN_VERSION_base(4,17,0)
import Data.Type.Equality
#endif
import qualified Data.List as L
import Data.ListLike.FoldableLL
( FoldableLL(foldr, foldr1, foldl), fold, foldMap, sequence_ )
import qualified Control.Applicative as A
import Data.Monoid ( All(All, getAll), Any(Any, getAny) )
import Data.Maybe ( listToMaybe )
import GHC.Exts (IsList(Item, fromList, toList))
class (IsList full, item ~ Item full, FoldableLL full item, Monoid full) =>
ListLike full item | full -> item where
empty :: full
empty = full
forall a. Monoid a => a
mempty
singleton :: item -> full
cons :: item -> full -> full
cons item
item full
l = full -> full -> full
forall full item. ListLike full item => full -> full -> full
append (item -> full
forall full item. ListLike full item => item -> full
singleton item
item) full
l
snoc :: full -> item -> full
snoc full
l item
item = full -> full -> full
forall full item. ListLike full item => full -> full -> full
append full
l (item -> full
forall full item. ListLike full item => item -> full
singleton item
item)
append :: full -> full -> full
append = full -> full -> full
forall a. Monoid a => a -> a -> a
mappend
head :: full -> item
head = item -> ((item, full) -> item) -> Maybe (item, full) -> item
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> item
forall a. HasCallStack => [Char] -> a
error [Char]
"head") (item, full) -> item
forall a b. (a, b) -> a
fst (Maybe (item, full) -> item)
-> (full -> Maybe (item, full)) -> full -> item
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full -> Maybe (item, full)
forall full item. ListLike full item => full -> Maybe (item, full)
uncons
uncons :: full -> Maybe (item, full)
uncons full
x = if full -> Bool
forall full item. ListLike full item => full -> Bool
null full
x then Maybe (item, full)
forall a. Maybe a
Nothing else (item, full) -> Maybe (item, full)
forall a. a -> Maybe a
Just (full -> item
forall full item. ListLike full item => full -> item
head full
x, full -> full
forall full item. ListLike full item => full -> full
tail full
x)
last :: full -> item
last full
l = case full -> Integer
forall a. Num a => full -> a
forall full item a. (ListLike full item, Num a) => full -> a
genericLength full
l of
(Integer
0::Integer) -> [Char] -> item
forall a. HasCallStack => [Char] -> a
error [Char]
"Called last on empty list"
Integer
1 -> full -> item
forall full item. ListLike full item => full -> item
head full
l
Integer
_ -> full -> item
forall full item. ListLike full item => full -> item
last (full -> full
forall full item. ListLike full item => full -> full
tail full
l)
tail :: full -> full
tail = full -> ((item, full) -> full) -> Maybe (item, full) -> full
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> full
forall a. HasCallStack => [Char] -> a
error [Char]
"tail") (item, full) -> full
forall a b. (a, b) -> b
snd (Maybe (item, full) -> full)
-> (full -> Maybe (item, full)) -> full -> full
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full -> Maybe (item, full)
forall full item. ListLike full item => full -> Maybe (item, full)
uncons
init :: full -> full
init full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = [Char] -> full
forall a. HasCallStack => [Char] -> a
error [Char]
"init: empty list"
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
xs = full
forall full item. ListLike full item => full
empty
| Bool
otherwise = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons (full -> item
forall full item. ListLike full item => full -> item
head full
l) (full -> full
forall full item. ListLike full item => full -> full
init full
xs)
where xs :: full
xs = full -> full
forall full item. ListLike full item => full -> full
tail full
l
null :: full -> Bool
null full
x = full -> Integer
forall a. Num a => full -> a
forall full item a. (ListLike full item, Num a) => full -> a
genericLength full
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== (Integer
0::Integer)
length :: full -> Int
length = full -> Int
forall a. Num a => full -> a
forall full item a. (ListLike full item, Num a) => full -> a
genericLength
map :: ListLike full' item' => (item -> item') -> full -> full'
map item -> item'
func full
inp
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
inp = full'
forall full item. ListLike full item => full
empty
| Bool
otherwise = item' -> full' -> full'
forall full item. ListLike full item => item -> full -> full
cons (item -> item'
func (full -> item
forall full item. ListLike full item => full -> item
head full
inp)) ((item -> item') -> full -> full'
forall full' item'.
ListLike full' item' =>
(item -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map item -> item'
func (full -> full
forall full item. ListLike full item => full -> full
tail full
inp))
rigidMap :: (item -> item) -> full -> full
rigidMap = (item -> item) -> full -> full
forall full' item'.
ListLike full' item' =>
(item -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map
reverse :: full -> full
reverse full
l = full -> full -> full
forall {full} {t}.
(Item full ~ Item t, ListLike t (Item t),
ListLike full (Item t)) =>
full -> t -> t
rev full
l full
forall full item. ListLike full item => full
empty
where rev :: full -> t -> t
rev full
rl t
a
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
rl = t
a
| Bool
otherwise = full -> t -> t
rev (full -> full
forall full item. ListLike full item => full -> full
tail full
rl) (Item full -> t -> t
forall full item. ListLike full item => item -> full -> full
cons (full -> Item full
forall full item. ListLike full item => full -> item
head full
rl) t
a)
intersperse :: item -> full -> full
intersperse item
sep full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
xs = item -> full
forall full item. ListLike full item => item -> full
singleton item
x
| Bool
otherwise = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x (item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
sep (item -> full -> full
forall full item. ListLike full item => item -> full -> full
intersperse item
sep full
xs))
where x :: item
x = full -> item
forall full item. ListLike full item => full -> item
head full
l
xs :: full
xs = full -> full
forall full item. ListLike full item => full -> full
tail full
l
concat :: (ListLike full' full) => full' -> full
concat = full' -> full
forall full item.
(FoldableLL full item, Monoid item) =>
full -> item
fold
concatMap :: (ListLike full' item') =>
(item -> full') -> full -> full'
concatMap = (item -> full') -> full -> full'
forall full item m.
(FoldableLL full item, Monoid m) =>
(item -> m) -> full -> m
foldMap
rigidConcatMap :: (item -> full) -> full -> full
rigidConcatMap = (item -> full) -> full -> full
forall full' item'.
ListLike full' item' =>
(item -> full') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> full') -> full -> full'
concatMap
any :: (item -> Bool) -> full -> Bool
any item -> Bool
p = Any -> Bool
getAny (Any -> Bool) -> (full -> Any) -> full -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (item -> Any) -> full -> Any
forall full item m.
(FoldableLL full item, Monoid m) =>
(item -> m) -> full -> m
foldMap (Bool -> Any
Any (Bool -> Any) -> (item -> Bool) -> item -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. item -> Bool
p)
all :: (item -> Bool) -> full -> Bool
all item -> Bool
p = All -> Bool
getAll (All -> Bool) -> (full -> All) -> full -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (item -> All) -> full -> All
forall full item m.
(FoldableLL full item, Monoid m) =>
(item -> m) -> full -> m
foldMap (Bool -> All
All (Bool -> All) -> (item -> Bool) -> item -> All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. item -> Bool
p)
maximum :: Ord item => full -> item
maximum = (item -> item -> item) -> full -> item
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
foldr1 item -> item -> item
forall a. Ord a => a -> a -> a
max
minimum :: Ord item => full -> item
minimum = (item -> item -> item) -> full -> item
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
foldr1 item -> item -> item
forall a. Ord a => a -> a -> a
min
replicate :: Int -> item -> full
replicate = Int -> item -> full
forall a. Integral a => a -> item -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> item -> full
genericReplicate
take :: Int -> full -> full
take = Int -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericTake
drop :: Int -> full -> full
drop = Int -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericDrop
splitAt :: Int -> full -> (full, full)
splitAt = Int -> full -> (full, full)
forall a. Integral a => a -> full -> (full, full)
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> (full, full)
genericSplitAt
takeWhile :: (item -> Bool) -> full -> full
takeWhile item -> Bool
func full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| item -> Bool
func item
x = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x ((item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
takeWhile item -> Bool
func (full -> full
forall full item. ListLike full item => full -> full
tail full
l))
| Bool
otherwise = full
forall full item. ListLike full item => full
empty
where x :: item
x = full -> item
forall full item. ListLike full item => full -> item
head full
l
dropWhile :: (item -> Bool) -> full -> full
dropWhile item -> Bool
func full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| item -> Bool
func (full -> item
forall full item. ListLike full item => full -> item
head full
l) = (item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
dropWhile item -> Bool
func (full -> full
forall full item. ListLike full item => full -> full
tail full
l)
| Bool
otherwise = full
l
dropWhileEnd :: (item -> Bool) -> full -> full
dropWhileEnd item -> Bool
func = (item -> full -> full) -> full -> full -> full
forall b. (item -> b -> b) -> b -> full -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
foldr (\item
x full
xs -> if item -> Bool
func item
x Bool -> Bool -> Bool
&& full -> Bool
forall full item. ListLike full item => full -> Bool
null full
xs then full
forall full item. ListLike full item => full
empty else item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x full
xs) full
forall full item. ListLike full item => full
empty
span :: (item -> Bool) -> full -> (full, full)
span item -> Bool
func full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = (full
forall full item. ListLike full item => full
empty, full
forall full item. ListLike full item => full
empty)
| item -> Bool
func item
x = (item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x full
ys, full
zs)
| Bool
otherwise = (full
forall full item. ListLike full item => full
empty, full
l)
where (full
ys, full
zs) = (item -> Bool) -> full -> (full, full)
forall full item.
ListLike full item =>
(item -> Bool) -> full -> (full, full)
span item -> Bool
func (full -> full
forall full item. ListLike full item => full -> full
tail full
l)
x :: item
x = full -> item
forall full item. ListLike full item => full -> item
head full
l
break :: (item -> Bool) -> full -> (full, full)
break item -> Bool
p = (item -> Bool) -> full -> (full, full)
forall full item.
ListLike full item =>
(item -> Bool) -> full -> (full, full)
span (Bool -> Bool
not (Bool -> Bool) -> (item -> Bool) -> item -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. item -> Bool
p)
group :: (ListLike full' full, Eq item) => full -> full'
group = (item -> item -> Bool) -> full -> full'
forall full'.
(ListLike full' full, Eq item) =>
(item -> item -> Bool) -> full -> full'
forall full item full'.
(ListLike full item, ListLike full' full, Eq item) =>
(item -> item -> Bool) -> full -> full'
groupBy item -> item -> Bool
forall a. Eq a => a -> a -> Bool
(==)
inits :: (ListLike full' full) => full -> full'
inits full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full -> full'
forall full item. ListLike full item => item -> full
singleton full
forall full item. ListLike full item => full
empty
| Bool
otherwise =
full' -> full' -> full'
forall full item. ListLike full item => full -> full -> full
append (full -> full'
forall full item. ListLike full item => item -> full
singleton full
forall full item. ListLike full item => full
empty)
((full -> full) -> [full] -> full'
forall full' item'.
ListLike full' item' =>
(full -> item') -> [full] -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map (item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons (full -> item
forall full item. ListLike full item => full -> item
head full
l)) [full]
theinits)
where theinits :: [full]
theinits = [full] -> [full] -> [full]
forall a. a -> a -> a
asTypeOf (full -> [full]
forall full'. ListLike full' full => full -> full'
forall full item full'.
(ListLike full item, ListLike full' full) =>
full -> full'
inits (full -> full
forall full item. ListLike full item => full -> full
tail full
l)) [full
l]
tails :: ListLike full' full => full -> full'
tails full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full -> full'
forall full item. ListLike full item => item -> full
singleton full
forall full item. ListLike full item => full
empty
| Bool
otherwise = full -> full' -> full'
forall full item. ListLike full item => item -> full -> full
cons full
l (full -> full'
forall full'. ListLike full' full => full -> full'
forall full item full'.
(ListLike full item, ListLike full' full) =>
full -> full'
tails (full -> full
forall full item. ListLike full item => full -> full
tail full
l))
isPrefixOf :: Eq item => full -> full -> Bool
isPrefixOf full
needle full
haystack
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
needle = Bool
True
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
haystack = Bool
False
| Bool
otherwise = (full -> item
forall full item. ListLike full item => full -> item
head full
needle) item -> item -> Bool
forall a. Eq a => a -> a -> Bool
== (full -> item
forall full item. ListLike full item => full -> item
head full
haystack) Bool -> Bool -> Bool
&&
full -> full -> Bool
forall full item.
(ListLike full item, Eq item) =>
full -> full -> Bool
isPrefixOf (full -> full
forall full item. ListLike full item => full -> full
tail full
needle) (full -> full
forall full item. ListLike full item => full -> full
tail full
haystack)
isSuffixOf :: Eq item => full -> full -> Bool
isSuffixOf full
needle full
haystack = full -> full -> Bool
forall full item.
(ListLike full item, Eq item) =>
full -> full -> Bool
isPrefixOf (full -> full
forall full item. ListLike full item => full -> full
reverse full
needle) (full -> full
forall full item. ListLike full item => full -> full
reverse full
haystack)
isInfixOf :: Eq item => full -> full -> Bool
isInfixOf full
needle full
haystack =
(full -> Bool) -> [full] -> Bool
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Bool
any (full -> full -> Bool
forall full item.
(ListLike full item, Eq item) =>
full -> full -> Bool
isPrefixOf full
needle) [full]
thetails
where thetails :: [full]
thetails = [full] -> [full] -> [full]
forall a. a -> a -> a
asTypeOf (full -> [full]
forall full'. ListLike full' full => full -> full'
forall full item full'.
(ListLike full item, ListLike full' full) =>
full -> full'
tails full
haystack) [full
haystack]
stripPrefix :: Eq item => full -> full -> Maybe full
stripPrefix full
xs full
ys = if full
xs full -> full -> Bool
forall full item.
(ListLike full item, Eq item) =>
full -> full -> Bool
`isPrefixOf` full
ys
then full -> Maybe full
forall a. a -> Maybe a
Just (full -> Maybe full) -> full -> Maybe full
forall a b. (a -> b) -> a -> b
$ Int -> full -> full
forall full item. ListLike full item => Int -> full -> full
drop (full -> Int
forall full item. ListLike full item => full -> Int
length full
xs) full
ys
else Maybe full
forall a. Maybe a
Nothing
stripSuffix :: Eq item => full -> full -> Maybe full
stripSuffix full
xs full
ys = if full
xs full -> full -> Bool
forall full item.
(ListLike full item, Eq item) =>
full -> full -> Bool
`isSuffixOf` full
ys
then full -> Maybe full
forall a. a -> Maybe a
Just (full -> Maybe full) -> full -> Maybe full
forall a b. (a -> b) -> a -> b
$ Int -> full -> full
forall full item. ListLike full item => Int -> full -> full
take (full -> Int
forall full item. ListLike full item => full -> Int
length full
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- full -> Int
forall full item. ListLike full item => full -> Int
length full
xs) full
ys
else Maybe full
forall a. Maybe a
Nothing
elem :: Eq item => item -> full -> Bool
elem item
i = (item -> Bool) -> full -> Bool
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Bool
any (item -> item -> Bool
forall a. Eq a => a -> a -> Bool
== item
i)
notElem :: Eq item => item -> full -> Bool
notElem item
i = (item -> Bool) -> full -> Bool
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Bool
all (item -> item -> Bool
forall a. Eq a => a -> a -> Bool
/= item
i)
find :: (item -> Bool) -> full -> Maybe item
find item -> Bool
f full
l = case (item -> Bool) -> full -> Maybe Int
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Maybe Int
findIndex item -> Bool
f full
l of
Maybe Int
Nothing -> Maybe item
forall a. Maybe a
Nothing
Just Int
x -> item -> Maybe item
forall a. a -> Maybe a
Just (full -> Int -> item
forall full item. ListLike full item => full -> Int -> item
index full
l Int
x)
filter :: (item -> Bool) -> full -> full
filter item -> Bool
func full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| item -> Bool
func (full -> item
forall full item. ListLike full item => full -> item
head full
l) = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons (full -> item
forall full item. ListLike full item => full -> item
head full
l) ((item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter item -> Bool
func (full -> full
forall full item. ListLike full item => full -> full
tail full
l))
| Bool
otherwise = (item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter item -> Bool
func (full -> full
forall full item. ListLike full item => full -> full
tail full
l)
partition :: (item -> Bool) -> full -> (full, full)
partition item -> Bool
p full
xs = ((item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter item -> Bool
p full
xs, (item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter (Bool -> Bool
not (Bool -> Bool) -> (item -> Bool) -> item -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. item -> Bool
p) full
xs)
index :: full -> Int -> item
index full
l Int
i
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = [Char] -> item
forall a. HasCallStack => [Char] -> a
error [Char]
"index: index not found"
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = [Char] -> item
forall a. HasCallStack => [Char] -> a
error [Char]
"index: index must be >= 0"
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = full -> item
forall full item. ListLike full item => full -> item
head full
l
| Bool
otherwise = full -> Int -> item
forall full item. ListLike full item => full -> Int -> item
index (full -> full
forall full item. ListLike full item => full -> full
tail full
l) (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
elemIndex :: Eq item => item -> full -> Maybe Int
elemIndex item
e full
l = (item -> Bool) -> full -> Maybe Int
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Maybe Int
findIndex (item -> item -> Bool
forall a. Eq a => a -> a -> Bool
== item
e) full
l
elemIndices :: (Eq item, ListLike result Int) => item -> full -> result
elemIndices item
i full
l = (item -> Bool) -> full -> result
forall result.
ListLike result Int =>
(item -> Bool) -> full -> result
forall full item result.
(ListLike full item, ListLike result Int) =>
(item -> Bool) -> full -> result
findIndices (item -> item -> Bool
forall a. Eq a => a -> a -> Bool
== item
i) full
l
findIndex :: (item -> Bool) -> full -> Maybe Int
findIndex item -> Bool
f = [Int] -> Maybe Int
forall a. [a] -> Maybe a
listToMaybe ([Int] -> Maybe Int) -> (full -> [Int]) -> full -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (item -> Bool) -> full -> [Int]
forall result.
ListLike result Int =>
(item -> Bool) -> full -> result
forall full item result.
(ListLike full item, ListLike result Int) =>
(item -> Bool) -> full -> result
findIndices item -> Bool
f
findIndices :: (ListLike result Int) => (item -> Bool) -> full -> result
findIndices item -> Bool
p full
xs = ((item, Int) -> Int) -> [(item, Int)] -> result
forall full' item'.
ListLike full' item' =>
((item, Int) -> item') -> [(item, Int)] -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map (item, Int) -> Int
forall a b. (a, b) -> b
snd ([(item, Int)] -> result) -> [(item, Int)] -> result
forall a b. (a -> b) -> a -> b
$ ((item, Int) -> Bool) -> [(item, Int)] -> [(item, Int)]
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter (item -> Bool
p (item -> Bool) -> ((item, Int) -> item) -> (item, Int) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (item, Int) -> item
forall a b. (a, b) -> a
fst) ([(item, Int)] -> [(item, Int)]) -> [(item, Int)] -> [(item, Int)]
forall a b. (a -> b) -> a -> b
$ [(item, Int)]
thezips
where thezips :: [(item, Int)]
thezips = [(item, Int)] -> [(item, Int)] -> [(item, Int)]
forall a. a -> a -> a
asTypeOf (full -> [Int] -> [(item, Int)]
forall full item fullb itemb result.
(ListLike full item, ListLike fullb itemb,
ListLike result (item, itemb)) =>
full -> fullb -> result
zip full
xs [Int
0..]) [(full -> item
forall full item. ListLike full item => full -> item
head full
xs, Int
0::Int)]
sequence :: (Applicative m, ListLike fullinp (m item)) =>
fullinp -> m full
sequence = (m item -> m full -> m full) -> m full -> fullinp -> m full
forall b. (m item -> b -> b) -> b -> fullinp -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
foldr ((item -> full -> full) -> m item -> m full -> m full
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
A.liftA2 item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons) (full -> m full
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure full
forall full item. ListLike full item => full
empty)
mapM :: (Applicative m, ListLike full' item') =>
(item -> m item') -> full -> m full'
mapM item -> m item'
func full
l = [m item'] -> m full'
forall full item (m :: * -> *) fullinp.
(ListLike full item, Applicative m, ListLike fullinp (m item)) =>
fullinp -> m full
forall (m :: * -> *) fullinp.
(Applicative m, ListLike fullinp (m item')) =>
fullinp -> m full'
sequence [m item']
mapresult
where mapresult :: [m item']
mapresult = [m item'] -> [m item'] -> [m item']
forall a. a -> a -> a
asTypeOf ((item -> m item') -> full -> [m item']
forall full' item'.
ListLike full' item' =>
(item -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map item -> m item'
func full
l) []
rigidMapM :: Monad m => (item -> m item) -> full -> m full
rigidMapM = (item -> m item) -> full -> m full
forall full item (m :: * -> *) full' item'.
(ListLike full item, Applicative m, ListLike full' item') =>
(item -> m item') -> full -> m full'
forall (m :: * -> *) full' item'.
(Applicative m, ListLike full' item') =>
(item -> m item') -> full -> m full'
mapM
nub :: Eq item => full -> full
nub = (item -> item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> full -> full
nubBy item -> item -> Bool
forall a. Eq a => a -> a -> Bool
(==)
delete :: Eq item => item -> full -> full
delete = (item -> item -> Bool) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> item -> full -> full
deleteBy item -> item -> Bool
forall a. Eq a => a -> a -> Bool
(==)
deleteFirsts :: Eq item => full -> full -> full
deleteFirsts = (full -> item -> full) -> full -> full -> full
forall a. (a -> item -> a) -> a -> full -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
foldl ((item -> full -> full) -> full -> item -> full
forall a b c. (a -> b -> c) -> b -> a -> c
flip item -> full -> full
forall full item.
(ListLike full item, Eq item) =>
item -> full -> full
delete)
union :: Eq item => full -> full -> full
union = (item -> item -> Bool) -> full -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> full -> full -> full
unionBy item -> item -> Bool
forall a. Eq a => a -> a -> Bool
(==)
intersect :: Eq item => full -> full -> full
intersect = (item -> item -> Bool) -> full -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> full -> full -> full
intersectBy item -> item -> Bool
forall a. Eq a => a -> a -> Bool
(==)
sort :: Ord item => full -> full
sort = (item -> item -> Ordering) -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Ordering) -> full -> full
sortBy item -> item -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
insert :: Ord item => item -> full -> full
insert = (item -> item -> Ordering) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Ordering) -> item -> full -> full
insertBy item -> item -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
toList' :: full -> [item]
toList' = full -> [item]
forall full'. ListLike full' item => full -> full'
forall full item full'.
(ListLike full item, ListLike full' item) =>
full -> full'
fromListLike
fromList' :: [item] -> full
fromList' [] = full
forall full item. ListLike full item => full
empty
fromList' (item
x:[item]
xs) = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x ([Item full] -> full
forall l. IsList l => [Item l] -> l
fromList [item]
[Item full]
xs)
fromListLike :: ListLike full' item => full -> full'
fromListLike = (item -> item) -> full -> full'
forall full' item'.
ListLike full' item' =>
(item -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map item -> item
forall a. a -> a
id
{-# INLINE fromListLike #-}
nubBy :: (item -> item -> Bool) -> full -> full
nubBy item -> item -> Bool
eq full
l = full -> full -> full
nubBy' full
l full
forall a. Monoid a => a
mempty
where
nubBy' :: full -> full -> full
nubBy' full
ys full
xs =
case full -> Maybe (item, full)
forall full item. ListLike full item => full -> Maybe (item, full)
uncons full
ys of
Maybe (item, full)
Nothing -> full
forall a. Monoid a => a
mempty
Just (item
y, full
ys')
| item -> full -> Bool
elem_by item
y full
xs -> full -> full -> full
nubBy' full
ys' full
xs
| Bool
otherwise -> item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
y (full -> full -> full
nubBy' full
ys' (item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
y full
xs))
elem_by :: item -> full -> Bool
elem_by :: item -> full -> Bool
elem_by item
y full
xs =
case full -> Maybe (item, full)
forall full item. ListLike full item => full -> Maybe (item, full)
uncons full
xs of
Maybe (item, full)
Nothing -> Bool
False
Just (item
x, full
xs') -> item
x item -> item -> Bool
`eq` item
y Bool -> Bool -> Bool
|| item -> full -> Bool
elem_by item
y full
xs'
deleteBy :: (item -> item -> Bool) -> item -> full -> full
deleteBy item -> item -> Bool
func item
i full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| Bool
otherwise =
if item -> item -> Bool
func item
i (full -> item
forall full item. ListLike full item => full -> item
head full
l)
then full -> full
forall full item. ListLike full item => full -> full
tail full
l
else item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons (full -> item
forall full item. ListLike full item => full -> item
head full
l) ((item -> item -> Bool) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> item -> full -> full
deleteBy item -> item -> Bool
func item
i (full -> full
forall full item. ListLike full item => full -> full
tail full
l))
deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> full
deleteFirstsBy item -> item -> Bool
func = (full -> item -> full) -> full -> full -> full
forall a. (a -> item -> a) -> a -> full -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
foldl ((item -> full -> full) -> full -> item -> full
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((item -> item -> Bool) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> item -> full -> full
deleteBy item -> item -> Bool
func))
unionBy :: (item -> item -> Bool) -> full -> full -> full
unionBy item -> item -> Bool
func full
x full
y =
full -> full -> full
forall full item. ListLike full item => full -> full -> full
append full
x (full -> full) -> full -> full
forall a b. (a -> b) -> a -> b
$ (full -> item -> full) -> full -> full -> full
forall a. (a -> item -> a) -> a -> full -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
foldl ((item -> full -> full) -> full -> item -> full
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((item -> item -> Bool) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> item -> full -> full
deleteBy item -> item -> Bool
func)) ((item -> item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Bool) -> full -> full
nubBy item -> item -> Bool
func full
y) full
x
intersectBy :: (item -> item -> Bool) -> full -> full -> full
intersectBy item -> item -> Bool
func full
xs full
ys = (item -> Bool) -> full -> full
forall full item.
ListLike full item =>
(item -> Bool) -> full -> full
filter (\item
x -> (item -> Bool) -> full -> Bool
forall full item.
ListLike full item =>
(item -> Bool) -> full -> Bool
any (item -> item -> Bool
func item
x) full
ys) full
xs
groupBy :: (ListLike full' full, Eq item) =>
(item -> item -> Bool) -> full -> full'
groupBy item -> item -> Bool
eq full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full'
forall full item. ListLike full item => full
empty
| Bool
otherwise = full -> full' -> full'
forall full item. ListLike full item => item -> full -> full
cons (item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x full
ys) ((item -> item -> Bool) -> full -> full'
forall full'.
(ListLike full' full, Eq item) =>
(item -> item -> Bool) -> full -> full'
forall full item full'.
(ListLike full item, ListLike full' full, Eq item) =>
(item -> item -> Bool) -> full -> full'
groupBy item -> item -> Bool
eq full
zs)
where (full
ys, full
zs) = (item -> Bool) -> full -> (full, full)
forall full item.
ListLike full item =>
(item -> Bool) -> full -> (full, full)
span (item -> item -> Bool
eq item
x) full
xs
x :: item
x = full -> item
forall full item. ListLike full item => full -> item
head full
l
xs :: full
xs = full -> full
forall full item. ListLike full item => full -> full
tail full
l
sortBy :: (item -> item -> Ordering) -> full -> full
sortBy item -> item -> Ordering
cmp = (item -> full -> full) -> full -> full -> full
forall b. (item -> b -> b) -> b -> full -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
foldr ((item -> item -> Ordering) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Ordering) -> item -> full -> full
insertBy item -> item -> Ordering
cmp) full
forall full item. ListLike full item => full
empty
insertBy :: (item -> item -> Ordering) -> item ->
full -> full
insertBy item -> item -> Ordering
cmp item
x full
ys =
case full -> Maybe (item, full)
forall full item. ListLike full item => full -> Maybe (item, full)
uncons full
ys of
Maybe (item, full)
Nothing -> item -> full
forall full item. ListLike full item => item -> full
singleton item
x
Just (item
ys_head,full
ys_tail) -> case item -> item -> Ordering
cmp item
x item
ys_head of
Ordering
GT -> item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
ys_head ((item -> item -> Ordering) -> item -> full -> full
forall full item.
ListLike full item =>
(item -> item -> Ordering) -> item -> full -> full
insertBy item -> item -> Ordering
cmp item
x full
ys_tail)
Ordering
_ -> item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x full
ys
genericLength :: Num a => full -> a
genericLength full
l = a -> full -> a
forall {t} {t}. (Num t, ListLike t (Item t)) => t -> t -> t
calclen a
0 full
l
where calclen :: t -> t -> t
calclen !t
accum t
cl =
if t -> Bool
forall full item. ListLike full item => full -> Bool
null t
cl
then t
accum
else t -> t -> t
calclen (t
accum t -> t -> t
forall a. Num a => a -> a -> a
+ t
1) (t -> t
forall full item. ListLike full item => full -> full
tail t
cl)
genericTake :: Integral a => a -> full -> full
genericTake a
n full
l
| a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 = full
forall full item. ListLike full item => full
empty
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
forall full item. ListLike full item => full
empty
| Bool
otherwise = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons (full -> item
forall full item. ListLike full item => full -> item
head full
l) (a -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericTake (a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (full -> full
forall full item. ListLike full item => full -> full
tail full
l))
genericDrop :: Integral a => a -> full -> full
genericDrop a
n full
l
| a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 = full
l
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
l = full
l
| Bool
otherwise = a -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericDrop (a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (full -> full
forall full item. ListLike full item => full -> full
tail full
l)
genericSplitAt :: Integral a => a -> full -> (full, full)
genericSplitAt a
n full
l = (a -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericTake a
n full
l, a -> full -> full
forall a. Integral a => a -> full -> full
forall full item a.
(ListLike full item, Integral a) =>
a -> full -> full
genericDrop a
n full
l)
genericReplicate :: Integral a => a -> item -> full
genericReplicate a
count item
x
| a
count a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 = full
forall full item. ListLike full item => full
empty
| Bool
otherwise = (a -> item) -> [a] -> full
forall full' item'.
ListLike full' item' =>
(a -> item') -> [a] -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map (\a
_ -> item
x) [a
1..a
count]
{-# MINIMAL (singleton, uncons, null) |
(singleton, uncons, genericLength) |
(singleton, head, tail, null) |
(singleton, head, tail, genericLength) #-}
type ListOps full = (ListLike full (Item full))
class (ListLike full item) => InfiniteListLike full item | full -> item where
iterate :: (item -> item) -> item -> full
iterate item -> item
f item
x = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x ((item -> item) -> item -> full
forall full item.
InfiniteListLike full item =>
(item -> item) -> item -> full
iterate item -> item
f (item -> item
f item
x))
repeat :: item -> full
repeat item
x = full
xs
where xs :: full
xs = item -> full -> full
forall full item. ListLike full item => item -> full -> full
cons item
x full
xs
cycle :: full -> full
cycle full
xs
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
xs = [Char] -> full
forall a. HasCallStack => [Char] -> a
error [Char]
"ListLike.cycle: empty list"
| Bool
otherwise = full
xs' where xs' :: full
xs' = full -> full -> full
forall full item. ListLike full item => full -> full -> full
append full
xs full
xs'
instance ListLike [a] a where
empty :: [a]
empty = []
singleton :: a -> [a]
singleton a
x = [a
x]
cons :: a -> [a] -> [a]
cons a
x [a]
l = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
l
snoc :: [a] -> a -> [a]
snoc [a]
l a
x = [a]
l [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
x]
append :: [a] -> [a] -> [a]
append = [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(++)
head :: [a] -> a
head = [a] -> a
forall a. HasCallStack => [a] -> a
L.head
last :: [a] -> a
last = [a] -> a
forall a. HasCallStack => [a] -> a
L.last
tail :: [a] -> [a]
tail = [a] -> [a]
forall a. HasCallStack => [a] -> [a]
L.tail
init :: [a] -> [a]
init = [a] -> [a]
forall a. HasCallStack => [a] -> [a]
L.init
null :: [a] -> Bool
null = [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null
length :: [a] -> Int
length = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
L.length
map :: forall full' item'.
ListLike full' item' =>
(a -> item') -> [a] -> full'
map a -> item'
f = [item'] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList ([item'] -> full') -> ([a] -> [item']) -> [a] -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> item') -> [a] -> [item']
forall a b. (a -> b) -> [a] -> [b]
L.map a -> item'
f
rigidMap :: (a -> a) -> [a] -> [a]
rigidMap = (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
L.map
reverse :: [a] -> [a]
reverse = [a] -> [a]
forall a. [a] -> [a]
L.reverse
intersperse :: a -> [a] -> [a]
intersperse = a -> [a] -> [a]
forall a. a -> [a] -> [a]
L.intersperse
concat :: forall full'. ListLike full' [a] => full' -> [a]
concat = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
L.concat ([[a]] -> [a]) -> (full' -> [[a]]) -> full' -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full' -> [[a]]
full' -> [Item full']
forall l. IsList l => l -> [Item l]
toList
rigidConcatMap :: (a -> [a]) -> [a] -> [a]
rigidConcatMap = (a -> [a]) -> [a] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
L.concatMap
any :: (a -> Bool) -> [a] -> Bool
any = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
L.any
all :: (a -> Bool) -> [a] -> Bool
all = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
L.all
maximum :: Ord a => [a] -> a
maximum = [a] -> a
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
L.maximum
minimum :: Ord a => [a] -> a
minimum = [a] -> a
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
L.minimum
replicate :: Int -> a -> [a]
replicate = Int -> a -> [a]
forall a. Int -> a -> [a]
L.replicate
take :: Int -> [a] -> [a]
take = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
L.take
drop :: Int -> [a] -> [a]
drop = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
L.drop
splitAt :: Int -> [a] -> ([a], [a])
splitAt = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
L.splitAt
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
L.takeWhile
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
L.dropWhile
span :: (a -> Bool) -> [a] -> ([a], [a])
span = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
L.span
break :: (a -> Bool) -> [a] -> ([a], [a])
break = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
L.break
group :: forall full'. (ListLike full' [a], Eq a) => [a] -> full'
group = [[a]] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList ([[a]] -> full') -> ([a] -> [[a]]) -> [a] -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
L.group
inits :: forall full'. ListLike full' [a] => [a] -> full'
inits = [[a]] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList ([[a]] -> full') -> ([a] -> [[a]]) -> [a] -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [[a]]
forall a. [a] -> [[a]]
L.inits
tails :: forall full'. ListLike full' [a] => [a] -> full'
tails = [[a]] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList ([[a]] -> full') -> ([a] -> [[a]]) -> [a] -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [[a]]
forall a. [a] -> [[a]]
L.tails
isPrefixOf :: Eq a => [a] -> [a] -> Bool
isPrefixOf = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
L.isPrefixOf
isSuffixOf :: Eq a => [a] -> [a] -> Bool
isSuffixOf = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
L.isSuffixOf
isInfixOf :: Eq a => [a] -> [a] -> Bool
isInfixOf = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
L.isInfixOf
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
stripPrefix = [a] -> [a] -> Maybe [a]
forall a. Eq a => [a] -> [a] -> Maybe [a]
L.stripPrefix
elem :: Eq a => a -> [a] -> Bool
elem = a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
L.elem
notElem :: Eq a => a -> [a] -> Bool
notElem = a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
L.notElem
find :: (a -> Bool) -> [a] -> Maybe a
find = (a -> Bool) -> [a] -> Maybe a
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
L.find
filter :: (a -> Bool) -> [a] -> [a]
filter = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
L.filter
partition :: (a -> Bool) -> [a] -> ([a], [a])
partition = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
L.partition
index :: [a] -> Int -> a
index = [a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
(L.!!)
elemIndex :: Eq a => a -> [a] -> Maybe Int
elemIndex = a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
L.elemIndex
elemIndices :: forall result. (Eq a, ListLike result Int) => a -> [a] -> result
elemIndices a
item = [Int] -> result
[Item result] -> result
forall l. IsList l => [Item l] -> l
fromList ([Int] -> result) -> ([a] -> [Int]) -> [a] -> result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [a] -> [Int]
forall a. Eq a => a -> [a] -> [Int]
L.elemIndices a
item
findIndex :: (a -> Bool) -> [a] -> Maybe Int
findIndex = (a -> Bool) -> [a] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
L.findIndex
sequence :: forall (m :: * -> *) fullinp.
(Applicative m, ListLike fullinp (m a)) =>
fullinp -> m [a]
sequence = [m a] -> m [a]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA ([m a] -> m [a]) -> (fullinp -> [m a]) -> fullinp -> m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. fullinp -> [m a]
fullinp -> [Item fullinp]
forall l. IsList l => l -> [Item l]
toList
nub :: Eq a => [a] -> [a]
nub = [a] -> [a]
forall a. Eq a => [a] -> [a]
L.nub
delete :: Eq a => a -> [a] -> [a]
delete = a -> [a] -> [a]
forall a. Eq a => a -> [a] -> [a]
L.delete
deleteFirsts :: Eq a => [a] -> [a] -> [a]
deleteFirsts = [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
(L.\\)
union :: Eq a => [a] -> [a] -> [a]
union = [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
L.union
intersect :: Eq a => [a] -> [a] -> [a]
intersect = [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
L.intersect
sort :: Ord a => [a] -> [a]
sort = [a] -> [a]
forall a. Ord a => [a] -> [a]
L.sort
groupBy :: forall full'.
(ListLike full' [a], Eq a) =>
(a -> a -> Bool) -> [a] -> full'
groupBy a -> a -> Bool
func = [[a]] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList ([[a]] -> full') -> ([a] -> [[a]]) -> [a] -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> Bool) -> [a] -> [[a]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy a -> a -> Bool
func
unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
unionBy = (a -> a -> Bool) -> [a] -> [a] -> [a]
forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
L.unionBy
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
intersectBy = (a -> a -> Bool) -> [a] -> [a] -> [a]
forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]
L.intersectBy
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
sortBy = (a -> a -> Ordering) -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy
insert :: Ord a => a -> [a] -> [a]
insert = a -> [a] -> [a]
forall a. Ord a => a -> [a] -> [a]
L.insert
genericLength :: forall a. Num a => [a] -> a
genericLength = [a] -> a
forall i a. Num i => [a] -> i
L.genericLength
zip :: (ListLike full item,
ListLike fullb itemb,
ListLike result (item, itemb)) =>
full -> fullb -> result
zip :: forall full item fullb itemb result.
(ListLike full item, ListLike fullb itemb,
ListLike result (item, itemb)) =>
full -> fullb -> result
zip = (item -> itemb -> (item, itemb)) -> full -> fullb -> result
forall full item fullb itemb result resultitem.
(ListLike full item, ListLike fullb itemb,
ListLike result resultitem) =>
(item -> itemb -> resultitem) -> full -> fullb -> result
zipWith (,)
zipWith :: (ListLike full item,
ListLike fullb itemb,
ListLike result resultitem) =>
(item -> itemb -> resultitem) -> full -> fullb -> result
zipWith :: forall full item fullb itemb result resultitem.
(ListLike full item, ListLike fullb itemb,
ListLike result resultitem) =>
(item -> itemb -> resultitem) -> full -> fullb -> result
zipWith item -> itemb -> resultitem
f full
a fullb
b
| full -> Bool
forall full item. ListLike full item => full -> Bool
null full
a = result
forall full item. ListLike full item => full
empty
| fullb -> Bool
forall full item. ListLike full item => full -> Bool
null fullb
b = result
forall full item. ListLike full item => full
empty
| Bool
otherwise = resultitem -> result -> result
forall full item. ListLike full item => item -> full -> full
cons (item -> itemb -> resultitem
f (full -> item
forall full item. ListLike full item => full -> item
head full
a) (fullb -> itemb
forall full item. ListLike full item => full -> item
head fullb
b)) ((item -> itemb -> resultitem) -> full -> fullb -> result
forall full item fullb itemb result resultitem.
(ListLike full item, ListLike fullb itemb,
ListLike result resultitem) =>
(item -> itemb -> resultitem) -> full -> fullb -> result
zipWith item -> itemb -> resultitem
f (full -> full
forall full item. ListLike full item => full -> full
tail full
a) (fullb -> fullb
forall full item. ListLike full item => full -> full
tail fullb
b))