{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
{-# OPTIONS_GHC -Wno-unused-type-patterns #-}
module Universum.Container.Class
(
ToPairs (..)
, FromList (..)
, Container (..)
, checkingNotNull
, flipfoldl'
, sum
, product
, mapM_
, forM_
, traverse_
, for_
, sequenceA_
, sequence_
, asum
, concatMap
, One(..)
) where
import Data.Coerce (Coercible, coerce)
import Data.Kind (Type)
import Prelude hiding (all, and, any, concatMap, elem, foldMap, foldl, foldr, mapM_, notElem, null,
or, print, product, sequence_, sum)
import Universum.Applicative (Alternative (..), Const, ZipList (..), pass)
import Universum.Base (HasCallStack, Word8)
import Universum.Container.Reexport (HashMap, HashSet, Hashable, IntMap, IntSet, Map, Seq, Set,
Vector)
import Universum.Functor (Identity)
import Universum.Monoid (All (..), Any (..), Dual, First (..), Last, Product, Sum)
import qualified GHC.Exts as Exts
import GHC.TypeLits (ErrorMessage (..), Symbol, TypeError)
import qualified Data.List.NonEmpty as NE
import Universum.List.Reexport (NonEmpty)
import qualified Data.Foldable as Foldable
import qualified Data.Sequence as SEQ
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.List (concatMap)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.HashMap.Strict as HM
import qualified Data.HashSet as HashSet
import qualified Data.IntMap as IM
import qualified Data.IntSet as IS
import qualified Data.Map as M
import qualified Data.Set as Set
import qualified Data.Vector as V
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
class ToPairs t where
{-# MINIMAL toPairs #-}
type Key t :: Type
type Val t :: Type
toPairs :: t -> [(Key t, Val t)]
keys :: t -> [Key t]
keys = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. ToPairs t => t -> [(Key t, Val t)]
toPairs
{-# INLINE keys #-}
elems :: t -> [Val t]
elems = 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 t. ToPairs t => t -> [(Key t, Val t)]
toPairs
{-# INLINE elems #-}
instance ToPairs (HashMap k v) where
type Key (HashMap k v) = k
type Val (HashMap k v) = v
toPairs :: HashMap k v -> [(Key (HashMap k v), Val (HashMap k v))]
toPairs = forall k v. HashMap k v -> [(k, v)]
HM.toList
{-# INLINE toPairs #-}
keys :: HashMap k v -> [Key (HashMap k v)]
keys = forall k v. HashMap k v -> [k]
HM.keys
{-# INLINE keys #-}
elems :: HashMap k v -> [Val (HashMap k v)]
elems = forall k v. HashMap k v -> [v]
HM.elems
{-# INLINE elems #-}
instance ToPairs (IntMap v) where
type Key (IntMap v) = Int
type Val (IntMap v) = v
toPairs :: IntMap v -> [(Key (IntMap v), Val (IntMap v))]
toPairs = forall a. IntMap a -> [(Key, a)]
IM.toList
{-# INLINE toPairs #-}
keys :: IntMap v -> [Key (IntMap v)]
keys = forall a. IntMap a -> [Key]
IM.keys
{-# INLINE keys #-}
elems :: IntMap v -> [Val (IntMap v)]
elems = forall a. IntMap a -> [a]
IM.elems
{-# INLINE elems #-}
instance ToPairs (Map k v) where
type Key (Map k v) = k
type Val (Map k v) = v
toPairs :: Map k v -> [(Key (Map k v), Val (Map k v))]
toPairs = forall k a. Map k a -> [(k, a)]
M.toList
{-# INLINE toPairs #-}
keys :: Map k v -> [Key (Map k v)]
keys = forall k a. Map k a -> [k]
M.keys
{-# INLINE keys #-}
elems :: Map k v -> [Val (Map k v)]
elems = forall k a. Map k a -> [a]
M.elems
{-# INLINE elems #-}
instance ToPairs [(k, v)] where
type Key [(k, v)] = k
type Val [(k, v)] = v
toPairs :: [(k, v)] -> [(Key [(k, v)], Val [(k, v)])]
toPairs = forall a. a -> a
id
{-# INLINE toPairs #-}
instance ToPairs (NonEmpty (k, v)) where
type Key (NonEmpty (k, v)) = k
type Val (NonEmpty (k, v)) = v
toPairs :: NonEmpty (k, v) -> [(Key (NonEmpty (k, v)), Val (NonEmpty (k, v)))]
toPairs = forall a. NonEmpty a -> [a]
NE.toList
{-# INLINE toPairs #-}
class FromList l where
type ListElement l :: Type
type ListElement l = Exts.Item l
type FromListC l :: Exts.Constraint
type FromListC l = ()
fromList :: FromListC l => [ListElement l] -> l
default fromList
:: (Exts.IsList l, Exts.Item l ~ a, ListElement l ~ a)
=> [ListElement l] -> l
fromList = forall l. IsList l => [Item l] -> l
Exts.fromList
instance FromList [a]
instance FromList (Vector a)
instance FromList (Seq a)
instance FromList (ZipList a) where
type ListElement (ZipList a) = a
fromList :: FromListC (ZipList a) => [ListElement (ZipList a)] -> ZipList a
fromList = forall a. [a] -> ZipList a
ZipList
instance FromList (NonEmpty a) where
type FromListC (NonEmpty a) = HasCallStack
fromList :: FromListC (NonEmpty a) => [ListElement (NonEmpty a)] -> NonEmpty a
fromList [ListElement (NonEmpty a)]
l = case [ListElement (NonEmpty a)]
l of
[] -> forall a. HasCallStack => [Char] -> a
error [Char]
"empty list"
ListElement (NonEmpty a)
x : [ListElement (NonEmpty a)]
xs -> ListElement (NonEmpty a)
x forall a. a -> [a] -> NonEmpty a
NE.:| [ListElement (NonEmpty a)]
xs
instance FromList IntSet
instance Ord a => FromList (Set a)
instance FromList (IntMap v)
instance Ord k => FromList (Map k v)
#if MIN_VERSION_hashable(1,4,0)
instance (Hashable k) => FromList (HashMap k v)
#else
instance (Eq k, Hashable k) => FromList (HashMap k v)
#endif
instance FromList T.Text
instance FromList TL.Text
instance FromList BS.ByteString where
type ListElement BS.ByteString = Word8
fromList :: FromListC ByteString => [ListElement ByteString] -> ByteString
fromList = [Word8] -> ByteString
BS.pack
instance FromList BSL.ByteString where
type ListElement BSL.ByteString = Word8
fromList :: FromListC ByteString => [ListElement ByteString] -> ByteString
fromList = [Word8] -> ByteString
BSL.pack
type family ElementDefault (t :: Type) :: Type where
ElementDefault (_ a) = a
class Container t where
type Element t :: Type
type Element t = ElementDefault t
toList :: t -> [Element t]
default toList :: (Foldable f, t ~ f a, Element t ~ a) => t -> [Element t]
toList = forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
{-# INLINE toList #-}
null :: t -> Bool
default null :: (Foldable f, t ~ f a) => t -> Bool
null = forall (t :: * -> *) a. Foldable t => t a -> Bool
Foldable.null
{-# INLINE null #-}
foldr :: (Element t -> b -> b) -> b -> t -> b
default foldr :: (Foldable f, t ~ f a, Element t ~ a) => (Element t -> b -> b) -> b -> t -> b
foldr = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr
{-# INLINE foldr #-}
foldl :: (b -> Element t -> b) -> b -> t -> b
default foldl :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b
foldl = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl
{-# INLINE foldl #-}
foldl' :: (b -> Element t -> b) -> b -> t -> b
default foldl' :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b
foldl' = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl'
{-# INLINE foldl' #-}
length :: t -> Int
default length :: (Foldable f, t ~ f a) => t -> Int
length = forall (t :: * -> *) a. Foldable t => t a -> Key
Foldable.length
{-# INLINE length #-}
elem :: Eq (Element t) => Element t -> t -> Bool
default elem :: ( Foldable f
, t ~ f a
, Element t ~ a
, Eq a
) => Element t -> t -> Bool
elem = forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
Foldable.elem
{-# INLINE elem #-}
foldMap :: Monoid m => (Element t -> m) -> t -> m
foldMap Element t -> m
f = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr (forall a. Monoid a => a -> a -> a
mappend forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element t -> m
f) forall a. Monoid a => a
mempty
{-# INLINE foldMap #-}
fold :: Monoid (Element t) => t -> Element t
fold = forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap forall a. a -> a
id
{-# INLINE fold #-}
foldr' :: (Element t -> b -> b) -> b -> t -> b
foldr' Element t -> b -> b
f b
z0 t
xs = forall t b. Container t => (b -> Element t -> b) -> b -> t -> b
foldl (b -> b) -> Element t -> b -> b
f' forall a. a -> a
id t
xs b
z0
where f' :: (b -> b) -> Element t -> b -> b
f' b -> b
k Element t
x b
z = b -> b
k forall a b. (a -> b) -> a -> b
$! Element t -> b -> b
f Element t
x b
z
{-# INLINE foldr' #-}
notElem :: Eq (Element t) => Element t -> t -> Bool
notElem Element t
x = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. (Container t, Eq (Element t)) => Element t -> t -> Bool
elem Element t
x
{-# INLINE notElem #-}
all :: (Element t -> Bool) -> t -> Bool
all Element t -> Bool
p = All -> Bool
getAll forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap (Bool -> All
All forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. Element t -> Bool
p)
any :: (Element t -> Bool) -> t -> Bool
any Element t -> Bool
p = Any -> Bool
getAny forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap (Bool -> Any
Any forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. Element t -> Bool
p)
{-# INLINE all #-}
{-# INLINE any #-}
and :: (Element t ~ Bool) => t -> Bool
and = All -> Bool
getAll forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap Bool -> All
All
or :: (Element t ~ Bool) => t -> Bool
or = Any -> Bool
getAny forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap Bool -> Any
Any
{-# INLINE and #-}
{-# INLINE or #-}
find :: (Element t -> Bool) -> t -> Maybe (Element t)
find Element t -> Bool
p = forall a. First a -> Maybe a
getFirst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t m. (Container t, Monoid m) => (Element t -> m) -> t -> m
foldMap (\ Element t
x -> forall a. Maybe a -> First a
First (if Element t -> Bool
p Element t
x then forall a. a -> Maybe a
Just Element t
x else forall a. Maybe a
Nothing))
{-# INLINE find #-}
safeHead :: t -> Maybe (Element t)
safeHead = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr (\Element t
x Maybe (Element t)
_ -> forall a. a -> Maybe a
Just Element t
x) forall a. Maybe a
Nothing
{-# INLINE safeHead #-}
safeMaximum :: Ord (Element t) => t -> Maybe (Element t)
default safeMaximum
:: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t))
=> t -> Maybe (Element t)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
Foldable.maximum
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element t) => t -> Maybe (Element t)
default safeMinimum
:: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t))
=> t -> Maybe (Element t)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
Foldable.minimum
{-# INLINE safeMinimum #-}
safeFoldr1 :: (Element t -> Element t -> Element t) -> t -> Maybe (Element t)
safeFoldr1 Element t -> Element t -> Element t
f t
xs = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr Element t -> Maybe (Element t) -> Maybe (Element t)
mf forall a. Maybe a
Nothing t
xs
where
mf :: Element t -> Maybe (Element t) -> Maybe (Element t)
mf Element t
x Maybe (Element t)
m = forall a. a -> Maybe a
Just (case Maybe (Element t)
m of
Maybe (Element t)
Nothing -> Element t
x
Just Element t
y -> Element t -> Element t -> Element t
f Element t
x Element t
y)
{-# INLINE safeFoldr1 #-}
safeFoldl1 :: (Element t -> Element t -> Element t) -> t -> Maybe (Element t)
safeFoldl1 Element t -> Element t -> Element t
f t
xs = forall t b. Container t => (b -> Element t -> b) -> b -> t -> b
foldl Maybe (Element t) -> Element t -> Maybe (Element t)
mf forall a. Maybe a
Nothing t
xs
where
mf :: Maybe (Element t) -> Element t -> Maybe (Element t)
mf Maybe (Element t)
m Element t
y = forall a. a -> Maybe a
Just (case Maybe (Element t)
m of
Maybe (Element t)
Nothing -> Element t
y
Just Element t
x -> Element t -> Element t -> Element t
f Element t
x Element t
y)
{-# INLINE safeFoldl1 #-}
checkingNotNull :: Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull :: forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull t -> Element t
f t
t
| forall t. Container t => t -> Bool
null t
t = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ t -> Element t
f t
t
{-# INLINE checkingNotNull #-}
instance Container T.Text where
type Element T.Text = Char
toList :: Text -> [Element Text]
toList = Text -> [Char]
T.unpack
{-# INLINE toList #-}
null :: Text -> Bool
null = Text -> Bool
T.null
{-# INLINE null #-}
foldr :: forall b. (Element Text -> b -> b) -> b -> Text -> b
foldr = forall a. (Char -> a -> a) -> a -> Text -> a
T.foldr
{-# INLINE foldr #-}
foldl :: forall b. (b -> Element Text -> b) -> b -> Text -> b
foldl = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl
{-# INLINE foldl #-}
foldl' :: forall b. (b -> Element Text -> b) -> b -> Text -> b
foldl' = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl'
{-# INLINE foldl' #-}
safeFoldr1 :: (Element Text -> Element Text -> Element Text)
-> Text -> Maybe (Element Text)
safeFoldr1 Element Text -> Element Text -> Element Text
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull ((Char -> Char -> Char) -> Text -> Char
T.foldr1 Element Text -> Element Text -> Element Text
f)
{-# INLINE safeFoldr1 #-}
safeFoldl1 :: (Element Text -> Element Text -> Element Text)
-> Text -> Maybe (Element Text)
safeFoldl1 Element Text -> Element Text -> Element Text
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull ((Char -> Char -> Char) -> Text -> Char
T.foldl1 Element Text -> Element Text -> Element Text
f)
{-# INLINE safeFoldl1 #-}
length :: Text -> Key
length = Text -> Key
T.length
{-# INLINE length #-}
elem :: Eq (Element Text) => Element Text -> Text -> Bool
elem Element Text
c = Text -> Text -> Bool
T.isInfixOf (Char -> Text
T.singleton Element Text
c)
{-# INLINE elem #-}
safeMaximum :: Ord (Element Text) => Text -> Maybe (Element Text)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull Text -> Char
T.maximum
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element Text) => Text -> Maybe (Element Text)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull Text -> Char
T.minimum
{-# INLINE safeMinimum #-}
all :: (Element Text -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
T.all
{-# INLINE all #-}
any :: (Element Text -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
T.any
{-# INLINE any #-}
find :: (Element Text -> Bool) -> Text -> Maybe (Element Text)
find = (Char -> Bool) -> Text -> Maybe Char
T.find
{-# INLINE find #-}
safeHead :: Text -> Maybe (Element Text)
safeHead = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe (Char, Text)
T.uncons
{-# INLINE safeHead #-}
instance Container TL.Text where
type Element TL.Text = Char
toList :: Text -> [Element Text]
toList = Text -> [Char]
TL.unpack
{-# INLINE toList #-}
null :: Text -> Bool
null = Text -> Bool
TL.null
{-# INLINE null #-}
foldr :: forall b. (Element Text -> b -> b) -> b -> Text -> b
foldr = forall a. (Char -> a -> a) -> a -> Text -> a
TL.foldr
{-# INLINE foldr #-}
foldl :: forall b. (b -> Element Text -> b) -> b -> Text -> b
foldl = forall a. (a -> Char -> a) -> a -> Text -> a
TL.foldl
{-# INLINE foldl #-}
foldl' :: forall b. (b -> Element Text -> b) -> b -> Text -> b
foldl' = forall a. (a -> Char -> a) -> a -> Text -> a
TL.foldl'
{-# INLINE foldl' #-}
safeFoldr1 :: (Element Text -> Element Text -> Element Text)
-> Text -> Maybe (Element Text)
safeFoldr1 Element Text -> Element Text -> Element Text
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull ((Char -> Char -> Char) -> Text -> Char
TL.foldr1 Element Text -> Element Text -> Element Text
f)
{-# INLINE safeFoldr1 #-}
safeFoldl1 :: (Element Text -> Element Text -> Element Text)
-> Text -> Maybe (Element Text)
safeFoldl1 Element Text -> Element Text -> Element Text
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull ((Char -> Char -> Char) -> Text -> Char
TL.foldl1 Element Text -> Element Text -> Element Text
f)
{-# INLINE safeFoldl1 #-}
length :: Text -> Key
length = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int64
TL.length
{-# INLINE length #-}
elem :: Eq (Element Text) => Element Text -> Text -> Bool
elem Element Text
c Text
s = Text -> Text -> Bool
TL.isInfixOf (Char -> Text
TL.singleton Element Text
c) Text
s
{-# INLINE elem #-}
safeMaximum :: Ord (Element Text) => Text -> Maybe (Element Text)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull Text -> Char
TL.maximum
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element Text) => Text -> Maybe (Element Text)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull Text -> Char
TL.minimum
{-# INLINE safeMinimum #-}
all :: (Element Text -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
TL.all
{-# INLINE all #-}
any :: (Element Text -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
TL.any
{-# INLINE any #-}
find :: (Element Text -> Bool) -> Text -> Maybe (Element Text)
find = (Char -> Bool) -> Text -> Maybe Char
TL.find
{-# INLINE find #-}
safeHead :: Text -> Maybe (Element Text)
safeHead = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe (Char, Text)
TL.uncons
{-# INLINE safeHead #-}
instance Container BS.ByteString where
type Element BS.ByteString = Word8
toList :: ByteString -> [Element ByteString]
toList = ByteString -> [Word8]
BS.unpack
{-# INLINE toList #-}
null :: ByteString -> Bool
null = ByteString -> Bool
BS.null
{-# INLINE null #-}
foldr :: forall b. (Element ByteString -> b -> b) -> b -> ByteString -> b
foldr = forall a. (Word8 -> a -> a) -> a -> ByteString -> a
BS.foldr
{-# INLINE foldr #-}
foldl :: forall b. (b -> Element ByteString -> b) -> b -> ByteString -> b
foldl = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BS.foldl
{-# INLINE foldl #-}
foldl' :: forall b. (b -> Element ByteString -> b) -> b -> ByteString -> b
foldl' = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BS.foldl'
{-# INLINE foldl' #-}
safeFoldr1 :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Maybe (Element ByteString)
safeFoldr1 Element ByteString -> Element ByteString -> Element ByteString
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull (HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
BS.foldr1 Element ByteString -> Element ByteString -> Element ByteString
f)
{-# INLINE safeFoldr1 #-}
safeFoldl1 :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Maybe (Element ByteString)
safeFoldl1 Element ByteString -> Element ByteString -> Element ByteString
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull (HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
BS.foldl1 Element ByteString -> Element ByteString -> Element ByteString
f)
{-# INLINE safeFoldl1 #-}
length :: ByteString -> Key
length = ByteString -> Key
BS.length
{-# INLINE length #-}
elem :: Eq (Element ByteString) => Element ByteString -> ByteString -> Bool
elem = Word8 -> ByteString -> Bool
BS.elem
{-# INLINE elem #-}
notElem :: Eq (Element ByteString) => Element ByteString -> ByteString -> Bool
notElem = Word8 -> ByteString -> Bool
BS.notElem
{-# INLINE notElem #-}
safeMaximum :: Ord (Element ByteString) =>
ByteString -> Maybe (Element ByteString)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull HasCallStack => ByteString -> Word8
BS.maximum
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element ByteString) =>
ByteString -> Maybe (Element ByteString)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull HasCallStack => ByteString -> Word8
BS.minimum
{-# INLINE safeMinimum #-}
all :: (Element ByteString -> Bool) -> ByteString -> Bool
all = (Word8 -> Bool) -> ByteString -> Bool
BS.all
{-# INLINE all #-}
any :: (Element ByteString -> Bool) -> ByteString -> Bool
any = (Word8 -> Bool) -> ByteString -> Bool
BS.any
{-# INLINE any #-}
find :: (Element ByteString -> Bool)
-> ByteString -> Maybe (Element ByteString)
find = (Word8 -> Bool) -> ByteString -> Maybe Word8
BS.find
{-# INLINE find #-}
safeHead :: ByteString -> Maybe (Element ByteString)
safeHead = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (Word8, ByteString)
BS.uncons
{-# INLINE safeHead #-}
instance Container BSL.ByteString where
type Element BSL.ByteString = Word8
toList :: ByteString -> [Element ByteString]
toList = ByteString -> [Word8]
BSL.unpack
{-# INLINE toList #-}
null :: ByteString -> Bool
null = ByteString -> Bool
BSL.null
{-# INLINE null #-}
foldr :: forall b. (Element ByteString -> b -> b) -> b -> ByteString -> b
foldr = forall a. (Word8 -> a -> a) -> a -> ByteString -> a
BSL.foldr
{-# INLINE foldr #-}
foldl :: forall b. (b -> Element ByteString -> b) -> b -> ByteString -> b
foldl = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BSL.foldl
{-# INLINE foldl #-}
foldl' :: forall b. (b -> Element ByteString -> b) -> b -> ByteString -> b
foldl' = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BSL.foldl'
{-# INLINE foldl' #-}
safeFoldr1 :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Maybe (Element ByteString)
safeFoldr1 Element ByteString -> Element ByteString -> Element ByteString
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull (HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
BSL.foldr1 Element ByteString -> Element ByteString -> Element ByteString
f)
{-# INLINE safeFoldr1 #-}
safeFoldl1 :: (Element ByteString -> Element ByteString -> Element ByteString)
-> ByteString -> Maybe (Element ByteString)
safeFoldl1 Element ByteString -> Element ByteString -> Element ByteString
f = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull (HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
BSL.foldl1 Element ByteString -> Element ByteString -> Element ByteString
f)
{-# INLINE safeFoldl1 #-}
length :: ByteString -> Key
length = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int64
BSL.length
{-# INLINE length #-}
elem :: Eq (Element ByteString) => Element ByteString -> ByteString -> Bool
elem = Word8 -> ByteString -> Bool
BSL.elem
{-# INLINE elem #-}
notElem :: Eq (Element ByteString) => Element ByteString -> ByteString -> Bool
notElem = Word8 -> ByteString -> Bool
BSL.notElem
{-# INLINE notElem #-}
safeMaximum :: Ord (Element ByteString) =>
ByteString -> Maybe (Element ByteString)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull HasCallStack => ByteString -> Word8
BSL.maximum
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element ByteString) =>
ByteString -> Maybe (Element ByteString)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull HasCallStack => ByteString -> Word8
BSL.minimum
{-# INLINE safeMinimum #-}
all :: (Element ByteString -> Bool) -> ByteString -> Bool
all = (Word8 -> Bool) -> ByteString -> Bool
BSL.all
{-# INLINE all #-}
any :: (Element ByteString -> Bool) -> ByteString -> Bool
any = (Word8 -> Bool) -> ByteString -> Bool
BSL.any
{-# INLINE any #-}
find :: (Element ByteString -> Bool)
-> ByteString -> Maybe (Element ByteString)
find = (Word8 -> Bool) -> ByteString -> Maybe Word8
BSL.find
{-# INLINE find #-}
safeHead :: ByteString -> Maybe (Element ByteString)
safeHead = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (Word8, ByteString)
BSL.uncons
{-# INLINE safeHead #-}
instance Container IntSet where
type Element IntSet = Int
toList :: IntSet -> [Element IntSet]
toList = IntSet -> [Key]
IS.toList
{-# INLINE toList #-}
null :: IntSet -> Bool
null = IntSet -> Bool
IS.null
{-# INLINE null #-}
foldr :: forall b. (Element IntSet -> b -> b) -> b -> IntSet -> b
foldr = forall b. (Key -> b -> b) -> b -> IntSet -> b
IS.foldr
{-# INLINE foldr #-}
foldl :: forall b. (b -> Element IntSet -> b) -> b -> IntSet -> b
foldl = forall a. (a -> Key -> a) -> a -> IntSet -> a
IS.foldl
{-# INLINE foldl #-}
foldl' :: forall b. (b -> Element IntSet -> b) -> b -> IntSet -> b
foldl' = forall a. (a -> Key -> a) -> a -> IntSet -> a
IS.foldl'
{-# INLINE foldl' #-}
length :: IntSet -> Key
length = IntSet -> Key
IS.size
{-# INLINE length #-}
elem :: Eq (Element IntSet) => Element IntSet -> IntSet -> Bool
elem = Key -> IntSet -> Bool
IS.member
{-# INLINE elem #-}
safeMaximum :: Ord (Element IntSet) => IntSet -> Maybe (Element IntSet)
safeMaximum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull IntSet -> Key
IS.findMax
{-# INLINE safeMaximum #-}
safeMinimum :: Ord (Element IntSet) => IntSet -> Maybe (Element IntSet)
safeMinimum = forall t. Container t => (t -> Element t) -> t -> Maybe (Element t)
checkingNotNull IntSet -> Key
IS.findMin
{-# INLINE safeMinimum #-}
safeHead :: IntSet -> Maybe (Element IntSet)
safeHead = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Key, IntSet)
IS.minView
{-# INLINE safeHead #-}
instance Ord v => Container (Set v) where
elem :: Eq (Element (Set v)) => Element (Set v) -> Set v -> Bool
elem = forall a. Ord a => a -> Set a -> Bool
Set.member
{-# INLINE elem #-}
notElem :: Eq (Element (Set v)) => Element (Set v) -> Set v -> Bool
notElem = forall a. Ord a => a -> Set a -> Bool
Set.notMember
{-# INLINE notElem #-}
#if MIN_VERSION_hashable(1,4,0)
instance (Hashable v) => Container (HashSet v) where
#else
instance (Eq v, Hashable v) => Container (HashSet v) where
#endif
elem :: Eq (Element (HashSet v)) =>
Element (HashSet v) -> HashSet v -> Bool
elem = forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
HashSet.member
{-# INLINE elem #-}
instance Container [a]
instance Container (Const a b)
instance Container (Dual a)
instance Container (First a)
instance Container (Last a)
instance Container (Product a)
instance Container (Sum a)
instance Container (NonEmpty a)
instance Container (ZipList a)
instance Container (HashMap k v)
instance Container (IntMap v)
instance Container (Map k v)
instance Container (Seq a)
instance Container (Vector a)
flipfoldl' :: (Container t, Element t ~ a) => (a -> b -> b) -> b -> t -> b
flipfoldl' :: forall t a b.
(Container t, Element t ~ a) =>
(a -> b -> b) -> b -> t -> b
flipfoldl' a -> b -> b
f = forall t b. Container t => (b -> Element t -> b) -> b -> t -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> b
f)
{-# INLINE flipfoldl' #-}
sum :: (Container t, Num (Element t)) => t -> Element t
sum :: forall t. (Container t, Num (Element t)) => t -> Element t
sum = forall t b. Container t => (b -> Element t -> b) -> b -> t -> b
foldl' forall a. Num a => a -> a -> a
(+) Element t
0
product :: (Container t, Num (Element t)) => t -> Element t
product :: forall t. (Container t, Num (Element t)) => t -> Element t
product = forall t b. Container t => (b -> Element t -> b) -> b -> t -> b
foldl' forall a. Num a => a -> a -> a
(*) Element t
1
traverse_
:: (Container t, Applicative f)
=> (Element t -> f b) -> t -> f ()
traverse_ :: forall t (f :: * -> *) b.
(Container t, Applicative f) =>
(Element t -> f b) -> t -> f ()
traverse_ Element t -> f b
f = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr (forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element t -> f b
f) forall (f :: * -> *). Applicative f => f ()
pass
for_
:: (Container t, Applicative f)
=> t -> (Element t -> f b) -> f ()
for_ :: forall t (f :: * -> *) b.
(Container t, Applicative f) =>
t -> (Element t -> f b) -> f ()
for_ = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall t (f :: * -> *) b.
(Container t, Applicative f) =>
(Element t -> f b) -> t -> f ()
traverse_
{-# INLINE for_ #-}
mapM_
:: (Container t, Monad m)
=> (Element t -> m b) -> t -> m ()
mapM_ :: forall t (m :: * -> *) b.
(Container t, Monad m) =>
(Element t -> m b) -> t -> m ()
mapM_ Element t -> m b
f= forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr (forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
(>>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element t -> m b
f) forall (f :: * -> *). Applicative f => f ()
pass
forM_
:: (Container t, Monad m)
=> t -> (Element t -> m b) -> m ()
forM_ :: forall t (m :: * -> *) b.
(Container t, Monad m) =>
t -> (Element t -> m b) -> m ()
forM_ = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall t (m :: * -> *) b.
(Container t, Monad m) =>
(Element t -> m b) -> t -> m ()
mapM_
{-# INLINE forM_ #-}
sequenceA_
:: (Container t, Applicative f, Element t ~ f a)
=> t -> f ()
sequenceA_ :: forall t (f :: * -> *) a.
(Container t, Applicative f, Element t ~ f a) =>
t -> f ()
sequenceA_ = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>) forall (f :: * -> *). Applicative f => f ()
pass
sequence_
:: (Container t, Monad m, Element t ~ m a)
=> t -> m ()
sequence_ :: forall t (m :: * -> *) a.
(Container t, Monad m, Element t ~ m a) =>
t -> m ()
sequence_ = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
(>>) forall (f :: * -> *). Applicative f => f ()
pass
asum
:: (Container t, Alternative f, Element t ~ f a)
=> t -> f a
asum :: forall t (f :: * -> *) a.
(Container t, Alternative f, Element t ~ f a) =>
t -> f a
asum = forall t b. Container t => (Element t -> b -> b) -> b -> t -> b
foldr forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINE asum #-}
concatMap :: Container c => (Element c -> [b]) -> c -> [b]
concatMap :: forall c b. Container c => (Element c -> [b]) -> c -> [b]
concatMap Element c -> [b]
f = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
Data.List.concatMap Element c -> [b]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Container t => t -> [Element t]
toList
{-# INLINE concatMap #-}
type family DisallowInstance (z :: Symbol) :: ErrorMessage where
DisallowInstance z = Text "Do not use 'Foldable' methods on " :<>: Text z
:$$: Text "Suggestions:"
:$$: Text " Instead of"
:$$: Text " for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()"
:$$: Text " use"
:$$: Text " whenJust :: Applicative f => Maybe a -> (a -> f ()) -> f ()"
:$$: Text " whenRight :: Applicative f => Either l r -> (r -> f ()) -> f ()"
:$$: Text ""
:$$: Text " Instead of"
:$$: Text " fold :: (Foldable t, Monoid m) => t m -> m"
:$$: Text " use"
:$$: Text " maybeToMonoid :: Monoid m => Maybe m -> m"
:$$: Text ""
instance TypeError (DisallowInstance "tuple") => Container (a, b)
instance TypeError (DisallowInstance "Maybe") => Container (Maybe a)
instance TypeError (DisallowInstance "Either") => Container (Either a b)
instance TypeError (DisallowInstance "Identity") => Container (Identity a)
class One x where
type OneItem x
one :: OneItem x -> x
instance One [a] where
type OneItem [a] = a
one :: OneItem [a] -> [a]
one = (forall a. a -> [a] -> [a]
:[])
{-# INLINE one #-}
instance One (NE.NonEmpty a) where
type OneItem (NE.NonEmpty a) = a
one :: OneItem (NonEmpty a) -> NonEmpty a
one = (forall a. a -> [a] -> NonEmpty a
NE.:|[])
{-# INLINE one #-}
instance One (SEQ.Seq a) where
type OneItem (SEQ.Seq a) = a
one :: OneItem (Seq a) -> Seq a
one = (forall a. Seq a
SEQ.empty forall a. Seq a -> a -> Seq a
SEQ.|>)
{-# INLINE one #-}
instance One T.Text where
type OneItem T.Text = Char
one :: OneItem Text -> Text
one = Char -> Text
T.singleton
{-# INLINE one #-}
instance One TL.Text where
type OneItem TL.Text = Char
one :: OneItem Text -> Text
one = Char -> Text
TL.singleton
{-# INLINE one #-}
instance One BS.ByteString where
type OneItem BS.ByteString = Word8
one :: OneItem ByteString -> ByteString
one = Word8 -> ByteString
BS.singleton
{-# INLINE one #-}
instance One BSL.ByteString where
type OneItem BSL.ByteString = Word8
one :: OneItem ByteString -> ByteString
one = Word8 -> ByteString
BSL.singleton
{-# INLINE one #-}
instance One (M.Map k v) where
type OneItem (M.Map k v) = (k, v)
one :: OneItem (Map k v) -> Map k v
one = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall k a. k -> a -> Map k a
M.singleton
{-# INLINE one #-}
instance Hashable k => One (HM.HashMap k v) where
type OneItem (HM.HashMap k v) = (k, v)
one :: OneItem (HashMap k v) -> HashMap k v
one = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton
{-# INLINE one #-}
instance One (IM.IntMap v) where
type OneItem (IM.IntMap v) = (Int, v)
one :: OneItem (IntMap v) -> IntMap v
one = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Key -> a -> IntMap a
IM.singleton
{-# INLINE one #-}
instance One (Set v) where
type OneItem (Set v) = v
one :: OneItem (Set v) -> Set v
one = forall a. a -> Set a
Set.singleton
{-# INLINE one #-}
instance Hashable v => One (HashSet v) where
type OneItem (HashSet v) = v
one :: OneItem (HashSet v) -> HashSet v
one = forall a. Hashable a => a -> HashSet a
HashSet.singleton
{-# INLINE one #-}
instance One IntSet where
type OneItem IntSet = Int
one :: OneItem IntSet -> IntSet
one = Key -> IntSet
IS.singleton
{-# INLINE one #-}
instance One (Vector a) where
type OneItem (Vector a) = a
one :: OneItem (Vector a) -> Vector a
one = forall a. a -> Vector a
V.singleton
{-# INLINE one #-}
instance VU.Unbox a => One (VU.Vector a) where
type OneItem (VU.Vector a) = a
one :: OneItem (Vector a) -> Vector a
one = forall a. Unbox a => a -> Vector a
VU.singleton
{-# INLINE one #-}
instance VP.Prim a => One (VP.Vector a) where
type OneItem (VP.Vector a) = a
one :: OneItem (Vector a) -> Vector a
one = forall a. Prim a => a -> Vector a
VP.singleton
{-# INLINE one #-}
instance VS.Storable a => One (VS.Vector a) where
type OneItem (VS.Vector a) = a
one :: OneItem (Vector a) -> Vector a
one = forall a. Storable a => a -> Vector a
VS.singleton
{-# INLINE one #-}
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c)
#. :: forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
(#.) b -> c
_f = coerce :: forall a b. Coercible a b => a -> b
coerce
{-# INLINE (#.) #-}