Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Reimagined approach for Foldable
type hierarchy. Forbids usages
of Container
function and similar over Maybe
and other potentially unsafe
data types. It was proposed to use -XTypeApplication
for such cases.
But this approach is not robust enough because programmers are human and can
easily forget to do this. For discussion see this topic:
Suggest explicit type application for Foldable length and friends
Synopsis
- class ToPairs t where
- class Container t where
- type Element t :: *
- toList :: t -> [Element t]
- null :: t -> Bool
- foldr :: (Element t -> b -> b) -> b -> t -> b
- foldl :: (b -> Element t -> b) -> b -> t -> b
- foldl' :: (b -> Element t -> b) -> b -> t -> b
- length :: t -> Int
- elem :: Eq (Element t) => Element t -> t -> Bool
- maximum :: Ord (Element t) => t -> Element t
- minimum :: Ord (Element t) => t -> Element t
- foldMap :: Monoid m => (Element t -> m) -> t -> m
- fold :: Monoid (Element t) => t -> Element t
- foldr' :: (Element t -> b -> b) -> b -> t -> b
- foldr1 :: (Element t -> Element t -> Element t) -> t -> Element t
- foldl1 :: (Element t -> Element t -> Element t) -> t -> Element t
- notElem :: Eq (Element t) => Element t -> t -> Bool
- all :: (Element t -> Bool) -> t -> Bool
- any :: (Element t -> Bool) -> t -> Bool
- and :: Element t ~ Bool => t -> Bool
- or :: Element t ~ Bool => t -> Bool
- find :: (Element t -> Bool) -> t -> Maybe (Element t)
- safeHead :: t -> Maybe (Element t)
- flipfoldl' :: (Container t, Element t ~ a) => (a -> b -> b) -> b -> t -> b
- sum :: (Container t, Num (Element t)) => t -> Element t
- product :: (Container t, Num (Element t)) => t -> Element t
- mapM_ :: (Container t, Monad m) => (Element t -> m b) -> t -> m ()
- forM_ :: (Container t, Monad m) => t -> (Element t -> m b) -> m ()
- traverse_ :: (Container t, Applicative f) => (Element t -> f b) -> t -> f ()
- for_ :: (Container t, Applicative f) => t -> (Element t -> f b) -> f ()
- sequenceA_ :: (Container t, Applicative f, Element t ~ f a) => t -> f ()
- sequence_ :: (Container t, Monad m, Element t ~ m a) => t -> m ()
- asum :: (Container t, Alternative f, Element t ~ f a) => t -> f a
- class One x where
Foldable-like classes and methods
class ToPairs t where Source #
Type class for data types that can be converted to List of Pairs.
You can define ToPairs
by just defining toPairs
function.
But the following laws should be met:
toPairs
m ≡zip
(keys
m) (elems
m)keys
≡map
fst
.toPairs
elems
≡map
snd
.toPairs
Type of keys of the mapping.
Type of value of the mapping.
toPairs :: t -> [(Key t, Val t)] Source #
Converts the structure to the list of the key-value pairs.
>>> toPairs (HashMap.fromList [(a
, "xxx"), (b
, "yyy")])
[(a
,"xxx"),(b
,"yyy")]
Converts the structure to the list of the keys.
>>>
keys (HashMap.fromList [('a', "xxx"), ('b', "yyy")])
"ab"
elems :: t -> [Val t] Source #
Converts the structure to the list of the values.
>>>
elems (HashMap.fromList [('a', "xxx"), ('b', "yyy")])
["xxx","yyy"]
class Container t where Source #
Very similar to Foldable
but also allows instances for monomorphic types
like Text
but forbids instances for Maybe
and similar. This class is used as
a replacement for Foldable
type class. It solves the following problems:
Container
,foldr
and other functions work on more types for which it makes sense.- You can't accidentally use
Container
on polymorphicFoldable
(like list), replace list withMaybe
and then debug error for two days. - More efficient implementaions of functions for polymorphic types (like
elem
forSet
).
The drawbacks:
- Type signatures of polymorphic functions look more scary.
- Orphan instances are involved if you want to use
foldr
(and similar) on types from libraries.
Nothing
Type of element for some container. Implemented as an asscociated type family because
some containers are monomorphic over element type (like Text
, IntSet
, etc.)
so we can't implement nice interface using old higher-kinded types
approach. Implementing this as an associated type family instead of
top-level family gives you more control over element types.
toList :: t -> [Element t] Source #
Convert container to list of elements.
>>>
toList @Text "aba"
"aba">>>
:t toList @Text "aba"
toList @Text "aba" :: [Char]
toList :: (Foldable f, t ~ f a, Element t ~ a) => t -> [Element t] Source #
Convert container to list of elements.
>>>
toList @Text "aba"
"aba">>>
:t toList @Text "aba"
toList @Text "aba" :: [Char]
Checks whether container is empty.
>>>
null @Text ""
True>>>
null @Text "aba"
False
null :: (Foldable f, t ~ f a, Element t ~ a) => t -> Bool Source #
Checks whether container is empty.
>>>
null @Text ""
True>>>
null @Text "aba"
False
foldr :: (Element t -> b -> b) -> b -> t -> b Source #
foldr :: (Foldable f, t ~ f a, Element t ~ a) => (Element t -> b -> b) -> b -> t -> b Source #
foldl :: (b -> Element t -> b) -> b -> t -> b Source #
foldl :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b Source #
foldl' :: (b -> Element t -> b) -> b -> t -> b Source #
foldl' :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b Source #
length :: (Foldable f, t ~ f a, Element t ~ a) => t -> Int Source #
elem :: Eq (Element t) => Element t -> t -> Bool Source #
elem :: (Foldable f, t ~ f a, Element t ~ a, Eq a) => Element t -> t -> Bool Source #
maximum :: Ord (Element t) => t -> Element t Source #
maximum :: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t)) => t -> Element t Source #
minimum :: Ord (Element t) => t -> Element t Source #
minimum :: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t)) => t -> Element t Source #
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 #
foldr1 :: (Element t -> Element t -> Element t) -> t -> Element t Source #
foldl1 :: (Element t -> Element t -> Element t) -> t -> Element t Source #
notElem :: Eq (Element t) => Element t -> t -> Bool 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 #
Instances
flipfoldl' :: (Container t, Element t ~ a) => (a -> b -> b) -> b -> t -> b Source #
Similar to foldl'
but takes a function with its arguments flipped.
>>>
flipfoldl' (/) 5 [2,3] :: Rational
15 % 2
sum :: (Container t, Num (Element t)) => t -> Element t Source #
Stricter version of sum
.
>>>
sum [1..10]
55>>>
sum (Just 3)
... • Do not use 'Foldable' methods on Maybe Suggestions: Instead of for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () use whenJust :: Applicative f => Maybe a -> (a -> f ()) -> f () whenRight :: Applicative f => Either l r -> (r -> f ()) -> f () ... Instead of fold :: (Foldable t, Monoid m) => t m -> m use maybeToMonoid :: Monoid m => Maybe m -> m ...
product :: (Container t, Num (Element t)) => t -> Element t Source #
Stricter version of product
.
>>>
product [1..10]
3628800>>>
product (Right 3)
... • Do not use 'Foldable' methods on Either Suggestions: Instead of for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () use whenJust :: Applicative f => Maybe a -> (a -> f ()) -> f () whenRight :: Applicative f => Either l r -> (r -> f ()) -> f () ... Instead of fold :: (Foldable t, Monoid m) => t m -> m use maybeToMonoid :: Monoid m => Maybe m -> m ...
sequenceA_ :: (Container t, Applicative f, Element t ~ f a) => t -> f () Source #
Constrained to Container
version of sequenceA_
.
>>>
sequenceA_ [putTextLn "foo", print True]
foo True
Others
Type class for types that can be created from one element. singleton
is lone name for this function. Also constructions of different type differ:
:[]
for lists, two arguments for Maps. Also some data types are monomorphic.
>>>
one True :: [Bool]
[True]>>>
one 'a' :: Text
"a">>>
one (3, "hello") :: HashMap Int String
fromList [(3,"hello")]
Instances
One ByteString Source # | |
Defined in Universum.Container.Class type OneItem ByteString :: Type Source # one :: OneItem ByteString -> ByteString Source # | |
One ByteString Source # | |
Defined in Universum.Container.Class type OneItem ByteString :: Type Source # one :: OneItem ByteString -> ByteString Source # | |
One IntSet Source # | |
One Text Source # | |
One Text Source # | |
One [a] Source # | |
One (NonEmpty a) Source # | |
One (IntMap v) Source # | |
One (Seq a) Source # | |
One (Set v) Source # | |
Hashable v => One (HashSet v) Source # | |
Unbox a => One (Vector a) Source # | |
Storable a => One (Vector a) Source # | |
Prim a => One (Vector a) Source # | |
One (Vector a) Source # | |
One (Map k v) Source # | |
Hashable k => One (HashMap k v) Source # | |