Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Compactable (f :: * -> *) where
- class Compactable f => CompactFold (f :: * -> *) where
- fforMaybe :: (Compactable f, Functor f) => f a -> (a -> Maybe b) -> f b
- fforFold :: (CompactFold f, Functor f, Foldable g) => f a -> (a -> g b) -> f b
- fforEither :: (Compactable f, Functor f) => f a -> (a -> Either l r) -> (f l, f r)
- fforBifold :: (CompactFold f, Functor f, Bifoldable g) => f a -> (a -> g l r) -> (f l, f r)
- mfold' :: (Foldable f, Alternative m) => f a -> m a
- mlefts :: (Bifoldable f, Alternative m) => f a b -> m a
- mrights :: (Bifoldable f, Alternative m) => f a b -> m b
- fmapMaybeM :: (Compactable f, Monad f) => (a -> MaybeT f b) -> f a -> f b
- fmapEitherM :: (Compactable f, Monad f) => (a -> ExceptT l f r) -> f a -> (f l, f r)
- fforMaybeM :: (Compactable f, Monad f) => f a -> (a -> MaybeT f b) -> f b
- fforEitherM :: (Compactable f, Monad f) => f a -> (a -> ExceptT l f r) -> (f l, f r)
- applyMaybeM :: (Compactable f, Monad f) => f (a -> MaybeT f b) -> f a -> f b
- bindMaybeM :: (Compactable f, Monad f) => f a -> (a -> f (MaybeT f b)) -> f b
- traverseMaybeM :: (Monad m, Compactable t, Traversable t) => (a -> MaybeT m b) -> t a -> m (t b)
- altDefaultCompact :: (Alternative f, Monad f) => f (Maybe a) -> f a
- altDefaultSeparate :: (Alternative f, Foldable f) => f (Either l r) -> (f l, f r)
Compact
class Compactable (f :: * -> *) where Source #
Class Compactable
provides two methods which can be writen in terms of each other, compact and separate.
is generalization of catMaybes as a new function. Compact has relations with Functor, Applicative, Monad, Alternative, and Traversable. In that we can use these class to provide the ability to operate on a data type by throwing away intermediate Nothings. This is useful for representing stripping out values or failure.
To be compactable alone, no laws must be satisfied other than the type signature.
If the data type is also a Functor the following should hold:
- Kleisli composition
fmapMaybe (l <=< r) = fmapMaybe l . fmapMaybe r
- Functor identity 1
compact . fmap Just = id
- Functor identity 2
fmapMaybe Just = id
- Functor relation
compact = fmapMaybe id
According to Kmett, (Compactable f, Functor f) is a functor from the
kleisli category of Maybe to the category of haskell data types.
Kleisli Maybe -> Hask
.
If the data type is also Applicative the following should hold:
- Applicative left identity
compact . (pure Just <*>) = id
- Applicative right identity
applyMaybe (pure Just) = id
- Applicative relation
compact = applyMaybe (pure id)
If the data type is also a Monad the following should hold:
- Monad left identity
flip bindMaybe (return . Just) = id
- Monad right identity
compact . (return . Just =<<) = id
- Monad relation
compact = flip bindMaybe return
If the data type is also Alternative the following should hold:
- Alternative identity
compact empty = empty
- Alternative annihilation
compact (const Nothing <$> xs) = empty
If the data type is also Traversable the following should hold:
- Traversable Applicative relation
traverseMaybe (pure . Just) = pure
- Traversable composition
Compose . fmap (traverseMaybe f) . traverseMaybe g = traverseMaybe (Compose . fmap (traverseMaybe f) . g)
- Traversable Functor relation
traverse f = traverseMaybe (fmap Just . f)
- Traversable naturality
t . traverseMaybe f = traverseMaybe (t . f)
Separate and filter
have recently elevated roles in this typeclass, and is not as well explored as compact. Here are the laws known today:
- Functor identity 3
fst . separate . fmap Right = id
- Functor identity 4
snd . separate . fmap Left = id
- Applicative left identity 2
snd . separate . (pure Right <*>) = id
- Applicative right identity 2
fst . separate . (pure Left <*>) = id
- Alternative annihilation left
snd . separate . fmap (const Left) = empty
- Alternative annihilation right
fst , separate . fmap (const Right) = empty
Docs for relationships between these functions and, a cleanup of laws will happen at some point.
If you know of more useful laws, or have better names for the ones above (especially those marked "name me"). Please let me know.
compact :: f (Maybe a) -> f a Source #
compact :: Functor f => f (Maybe a) -> f a Source #
separate :: f (Either l r) -> (f l, f r) Source #
separate :: Functor f => f (Either l r) -> (f l, f r) Source #
filter :: (a -> Bool) -> f a -> f a Source #
filter :: Functor f => (a -> Bool) -> f a -> f a Source #
partition :: (a -> Bool) -> f a -> (f a, f a) Source #
partition :: Functor f => (a -> Bool) -> f a -> (f a, f a) Source #
fmapMaybe :: Functor f => (a -> Maybe b) -> f a -> f b Source #
fmapEither :: Functor f => (a -> Either l r) -> f a -> (f l, f r) Source #
applyMaybe :: Applicative f => f (a -> Maybe b) -> f a -> f b Source #
applyEither :: Applicative f => f (a -> Either l r) -> f a -> (f l, f r) Source #
bindMaybe :: Monad f => f a -> (a -> f (Maybe b)) -> f b Source #
bindEither :: Monad f => f a -> (a -> f (Either l r)) -> (f l, f r) Source #
traverseMaybe :: (Applicative g, Traversable f) => (a -> g (Maybe b)) -> f a -> g (f b) Source #
traverseEither :: (Applicative g, Traversable f) => (a -> g (Either l r)) -> f a -> g (f l, f r) Source #
Compact Fold
class Compactable f => CompactFold (f :: * -> *) where Source #
class CompactFold
provides the same methods as Compactable
but generalized to work on any Foldable
.
When a type has Alternative (or similar) properties, we can extract the Maybe and the Either, and generalize to Foldable and Bifoldable.
Compactable can always be described in terms of CompactFold, because
compact = compactFold
and
separate = separateFold
as it's just a specialization. More exploration is needed on the relationship here.
compactFold :: Foldable g => f (g a) -> f a Source #
compactFold :: (Monad f, Alternative f, Foldable g) => f (g a) -> f a Source #
separateFold :: Bifoldable g => f (g a b) -> (f a, f b) Source #
separateFold :: (Monad f, Alternative f, Bifoldable g) => f (g a b) -> (f a, f b) Source #
fmapFold :: (Functor f, Foldable g) => (a -> g b) -> f a -> f b Source #
fmapBifold :: (Functor f, Bifoldable g) => (a -> g l r) -> f a -> (f l, f r) Source #
applyFold :: (Applicative f, Foldable g) => f (a -> g b) -> f a -> f b Source #
applyBifold :: (Applicative f, Bifoldable g) => f (a -> g l r) -> f a -> (f l, f r) Source #
bindFold :: (Monad f, Foldable g) => f a -> (a -> f (g b)) -> f b Source #
bindBifold :: (Monad f, Bifoldable g) => f a -> (a -> f (g l r)) -> (f l, f r) Source #
traverseFold :: (Applicative h, Foldable g, Traversable f) => (a -> h (g b)) -> f a -> h (f b) Source #
traverseBifold :: (Applicative h, Bifoldable g, Traversable f) => (a -> h (g l r)) -> f a -> h (f l, f r) Source #
CompactFold [] Source # | |
CompactFold Maybe Source # | |
CompactFold IO Source # | |
CompactFold Option Source # | |
CompactFold ZipList Source # | |
CompactFold STM Source # | |
CompactFold ReadPrec Source # | |
CompactFold ReadP Source # | |
CompactFold (U1 *) Source # | |
MonadPlus a => CompactFold (WrappedMonad a) Source # | |
(ArrowPlus a, ArrowApply a) => CompactFold (ArrowMonad a) Source # | |
CompactFold (Proxy *) Source # | |
(Alternative a, Monad a) => CompactFold (Rec1 * a) Source # | |
(Alternative a, Monad a) => CompactFold (Alt * a) Source # | |
(Alternative f, Monad f, Alternative g, Monad g) => CompactFold ((:*:) * f g) Source # | |
(Compactable f, Alternative f, Monad f, Compactable g, Alternative g, Monad g) => CompactFold (Product * f g) Source # | |
(Alternative f, Monad f) => CompactFold (M1 * i c f) Source # | |
Handly flips
fforEither :: (Compactable f, Functor f) => f a -> (a -> Either l r) -> (f l, f r) Source #
fforBifold :: (CompactFold f, Functor f, Bifoldable g) => f a -> (a -> g l r) -> (f l, f r) Source #
More general lefts and rights
mfold' :: (Foldable f, Alternative m) => f a -> m a Source #
mlefts :: (Bifoldable f, Alternative m) => f a b -> m a Source #
mrights :: (Bifoldable f, Alternative m) => f a b -> m b Source #
Monad Transformer utils
fmapMaybeM :: (Compactable f, Monad f) => (a -> MaybeT f b) -> f a -> f b Source #
fmapEitherM :: (Compactable f, Monad f) => (a -> ExceptT l f r) -> f a -> (f l, f r) Source #
fforMaybeM :: (Compactable f, Monad f) => f a -> (a -> MaybeT f b) -> f b Source #
fforEitherM :: (Compactable f, Monad f) => f a -> (a -> ExceptT l f r) -> (f l, f r) Source #
applyMaybeM :: (Compactable f, Monad f) => f (a -> MaybeT f b) -> f a -> f b Source #
bindMaybeM :: (Compactable f, Monad f) => f a -> (a -> f (MaybeT f b)) -> f b Source #
traverseMaybeM :: (Monad m, Compactable t, Traversable t) => (a -> MaybeT m b) -> t a -> m (t b) Source #
Alternative Defaults
altDefaultCompact :: (Alternative f, Monad f) => f (Maybe a) -> f a Source #
While more constrained, when available, this default is going to be faster than the one provided in the typeclass
altDefaultSeparate :: (Alternative f, Foldable f) => f (Either l r) -> (f l, f r) Source #
While more constrained, when available, this default is going to be faster than the one provided in the typeclass