universum-0.1.12: Custom prelude used in Serokell

Safe HaskellTrustworthy
LanguageHaskell2010

Containers

Synopsis

Documentation

type family Element t Source #

class Container t where Source #

Minimal complete definition

toList, null

Methods

toList :: t -> [Element t] Source #

null :: t -> Bool Source #

Instances

Container ByteString Source # 
Container ByteString Source # 
Container IntSet Source # 
Container Text Source # 
Container Text Source # 
Foldable f => Container (f a) Source # 

Methods

toList :: f a -> [Element (f a)] Source #

null :: f a -> Bool Source #

TypeError Constraint ((:<>:) (Text "Do not use 'Foldable' methods on ") (Text "tuples")) => Container (a, b) Source # 

Methods

toList :: (a, b) -> [Element (a, b)] Source #

null :: (a, b) -> Bool Source #

class Container t => NontrivialContainer t where Source #

A class for Containers that aren't trivial like Maybe (e.g. can hold more than one value)

Minimal complete definition

foldr, foldl, foldl', length, elem, maximum, minimum

Methods

foldMap :: Monoid m => (Element t -> m) -> t -> m Source #

fold :: Monoid (Element t) => t -> Element t Source #

foldr :: (Element t -> b -> b) -> b -> t -> b Source #

foldr' :: (Element t -> b -> b) -> b -> t -> b Source #

foldl :: (b -> Element t -> b) -> b -> t -> b Source #

foldl' :: (b -> Element t -> b) -> b -> t -> b Source #

foldr1 :: (Element t -> Element t -> Element t) -> t -> Element t Source #

foldl1 :: (Element t -> Element t -> Element t) -> t -> Element t Source #

length :: t -> Int Source #

elem :: Eq (Element t) => Element t -> t -> Bool Source #

maximum :: Ord (Element t) => t -> Element t Source #

minimum :: Ord (Element t) => t -> Element t Source #

all :: (Element t -> Bool) -> t -> Bool Source #

any :: (Element t -> Bool) -> t -> Bool Source #

and :: Element t ~ Bool => t -> Bool Source #

or :: Element t ~ Bool => t -> Bool Source #

find :: (Element t -> Bool) -> t -> Maybe (Element t) Source #

head :: t -> Maybe (Element t) Source #

Instances

NontrivialContainer ByteString Source # 
NontrivialContainer ByteString Source # 
NontrivialContainer IntSet Source # 
NontrivialContainer Text Source # 
NontrivialContainer Text Source # 
TypeError Constraint ((:<>:) (Text "Do not use 'Foldable' methods on ") (Text "Maybe")) => NontrivialContainer (Maybe a) Source # 

Methods

foldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m Source #

fold :: Maybe a -> Element (Maybe a) Source #

foldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b Source #

foldr' :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b Source #

foldl :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b Source #

foldl' :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b Source #

foldr1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) Source #

foldl1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) Source #

length :: Maybe a -> Int Source #

elem :: Element (Maybe a) -> Maybe a -> Bool Source #

maximum :: Maybe a -> Element (Maybe a) Source #

minimum :: Maybe a -> Element (Maybe a) Source #

all :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

any :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

and :: Maybe a -> Bool Source #

or :: Maybe a -> Bool Source #

find :: (Element (Maybe a) -> Bool) -> Maybe a -> Maybe (Element (Maybe a)) Source #

head :: Maybe a -> Maybe (Element (Maybe a)) Source #

Foldable f => NontrivialContainer (f a) Source # 

Methods

foldMap :: Monoid m => (Element (f a) -> m) -> f a -> m Source #

fold :: f a -> Element (f a) Source #

foldr :: (Element (f a) -> b -> b) -> b -> f a -> b Source #

foldr' :: (Element (f a) -> b -> b) -> b -> f a -> b Source #

foldl :: (b -> Element (f a) -> b) -> b -> f a -> b Source #

foldl' :: (b -> Element (f a) -> b) -> b -> f a -> b Source #

foldr1 :: (Element (f a) -> Element (f a) -> Element (f a)) -> f a -> Element (f a) Source #

foldl1 :: (Element (f a) -> Element (f a) -> Element (f a)) -> f a -> Element (f a) Source #

length :: f a -> Int Source #

elem :: Element (f a) -> f a -> Bool Source #

maximum :: f a -> Element (f a) Source #

minimum :: f a -> Element (f a) Source #

all :: (Element (f a) -> Bool) -> f a -> Bool Source #

any :: (Element (f a) -> Bool) -> f a -> Bool Source #

and :: f a -> Bool Source #

or :: f a -> Bool Source #

find :: (Element (f a) -> Bool) -> f a -> Maybe (Element (f a)) Source #

head :: f a -> Maybe (Element (f a)) Source #

TypeError Constraint ((:<>:) (Text "Do not use 'Foldable' methods on ") (Text "Identity")) => NontrivialContainer (Identity a) Source # 

Methods

foldMap :: Monoid m => (Element (Identity a) -> m) -> Identity a -> m Source #

fold :: Identity a -> Element (Identity a) Source #

foldr :: (Element (Identity a) -> b -> b) -> b -> Identity a -> b Source #

foldr' :: (Element (Identity a) -> b -> b) -> b -> Identity a -> b Source #

foldl :: (b -> Element (Identity a) -> b) -> b -> Identity a -> b Source #

foldl' :: (b -> Element (Identity a) -> b) -> b -> Identity a -> b Source #

foldr1 :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) Source #

foldl1 :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) Source #

length :: Identity a -> Int Source #

elem :: Element (Identity a) -> Identity a -> Bool Source #

maximum :: Identity a -> Element (Identity a) Source #

minimum :: Identity a -> Element (Identity a) Source #

all :: (Element (Identity a) -> Bool) -> Identity a -> Bool Source #

any :: (Element (Identity a) -> Bool) -> Identity a -> Bool Source #

and :: Identity a -> Bool Source #

or :: Identity a -> Bool Source #

find :: (Element (Identity a) -> Bool) -> Identity a -> Maybe (Element (Identity a)) Source #

head :: Identity a -> Maybe (Element (Identity a)) Source #

TypeError Constraint ((:<>:) (Text "Do not use 'Foldable' methods on ") (Text "Either")) => NontrivialContainer (Either a b) Source # 

Methods

foldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m Source #

fold :: Either a b -> Element (Either a b) Source #

foldr :: (Element (Either a b) -> b -> b) -> b -> Either a b -> b Source #

foldr' :: (Element (Either a b) -> b -> b) -> b -> Either a b -> b Source #

foldl :: (b -> Element (Either a b) -> b) -> b -> Either a b -> b Source #

foldl' :: (b -> Element (Either a b) -> b) -> b -> Either a b -> b Source #

foldr1 :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) Source #

foldl1 :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) Source #

length :: Either a b -> Int Source #

elem :: Element (Either a b) -> Either a b -> Bool Source #

maximum :: Either a b -> Element (Either a b) Source #

minimum :: Either a b -> Element (Either a b) Source #

all :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

any :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

and :: Either a b -> Bool Source #

or :: Either a b -> Bool Source #

find :: (Element (Either a b) -> Bool) -> Either a b -> Maybe (Element (Either a b)) Source #

head :: Either a b -> Maybe (Element (Either a b)) Source #

TypeError Constraint ((:<>:) (Text "Do not use 'Foldable' methods on ") (Text "tuples")) => NontrivialContainer (a, b) Source # 

Methods

foldMap :: Monoid m => (Element (a, b) -> m) -> (a, b) -> m Source #

fold :: (a, b) -> Element (a, b) Source #

foldr :: (Element (a, b) -> b -> b) -> b -> (a, b) -> b Source #

foldr' :: (Element (a, b) -> b -> b) -> b -> (a, b) -> b Source #

foldl :: (b -> Element (a, b) -> b) -> b -> (a, b) -> b Source #

foldl' :: (b -> Element (a, b) -> b) -> b -> (a, b) -> b Source #

foldr1 :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Element (a, b) Source #

foldl1 :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Element (a, b) Source #

length :: (a, b) -> Int Source #

elem :: Element (a, b) -> (a, b) -> Bool Source #

maximum :: (a, b) -> Element (a, b) Source #

minimum :: (a, b) -> Element (a, b) Source #

all :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

any :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

and :: (a, b) -> Bool Source #

or :: (a, b) -> Bool Source #

find :: (Element (a, b) -> Bool) -> (a, b) -> Maybe (Element (a, b)) Source #

head :: (a, b) -> Maybe (Element (a, b)) Source #

mapM_ :: (NontrivialContainer t, Monad m) => (Element t -> m b) -> t -> m () Source #

forM_ :: (NontrivialContainer t, Monad m) => t -> (Element t -> m b) -> m () Source #

traverse_ :: (NontrivialContainer t, Applicative f) => (Element t -> f b) -> t -> f () Source #

for_ :: (NontrivialContainer t, Applicative f) => t -> (Element t -> f b) -> f () Source #

sequenceA_ :: (NontrivialContainer t, Applicative f, Element t ~ f a) => t -> f () Source #

sequence_ :: (NontrivialContainer t, Monad m, Element t ~ m a) => t -> m () Source #

asum :: (NontrivialContainer t, Alternative f, Element t ~ f a) => t -> f a Source #