Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Compactable (f :: Type -> Type) where
- compact :: f (Maybe a) -> f a
- separateThese :: f (These l r) -> (f l, f r)
- filter :: (a -> Bool) -> f a -> f a
- partition :: (a -> Bool) -> f a -> (f a, f a)
- mapMaybe :: Functor f => (a -> Maybe b) -> f a -> f b
- contramapMaybe :: Contravariant f => (Maybe b -> a) -> f a -> f b
- mapThese :: Functor f => (a -> These l r) -> f a -> (f l, f r)
- contramapThese :: Contravariant f => (These l r -> a) -> f a -> (f l, f r)
- applyMaybe :: Applicative f => f (a -> Maybe b) -> f a -> f b
- applyThese :: Applicative f => f (a -> These l r) -> f a -> (f l, f r)
- bindMaybe :: Monad f => (a -> f (Maybe b)) -> f a -> f b
- bindThese :: Monad f => (a -> f (These l r)) -> f a -> (f l, f r)
- traverseMaybe :: (Applicative g, Traversable f) => (a -> g (Maybe b)) -> f a -> g (f b)
- traverseThese :: (Applicative g, Traversable f) => (a -> g (These l r)) -> f a -> g (f l, f r)
- separate :: (Dichotomous g, Functor f, Compactable f) => f (g l r) -> (f l, f r)
- fforMaybe :: (Compactable f, Functor f) => f a -> (a -> Maybe b) -> f b
- fforThese :: (Compactable f, Functor f) => f a -> (a -> These 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
- mapMaybeM :: (Compactable f, Monad f) => (a -> MaybeT f b) -> f a -> f b
- mapTheseM :: (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
- fforTheseM :: (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 :: (Dichotomous d, Alternative f, Foldable f) => f (d l r) -> (f l, f r)
Compact
class Compactable (f :: Type -> Type) where Source #
A generalization of catMaybes
compact . map Just = id
compact . mapMaybe id
compact (pure Just <*> a) = a
applyMaybe (pure Just) = id
applyMaybe (pure id) = compact
bindMaybe (return . Just) = id
bindMaybe return = compact
compact (return . Just =<< a) = a
mapMaybe (l <=< r) = mapMaybe l . mapMaybe r
compact (Nothing <$ a) = empty
compact (Nothing <$ a) = mempty
compact empty = empty
compact mempty = mempty
traverseMaybe (Just . Just) = Just
traverseMaybe (map Just . f) = traverse f
compact :: f (Maybe a) -> f a Source #
separateThese :: f (These l r) -> (f l, f r) Source #
default separateThese :: Functor f => f (These l r) -> (f l, f r) Source #
filter :: (a -> Bool) -> f a -> f a Source #
partition :: (a -> Bool) -> f a -> (f a, f a) Source #
mapMaybe :: Functor f => (a -> Maybe b) -> f a -> f b Source #
contramapMaybe :: Contravariant f => (Maybe b -> a) -> f a -> f b Source #
mapThese :: Functor f => (a -> These l r) -> f a -> (f l, f r) Source #
contramapThese :: Contravariant f => (These l r -> a) -> f a -> (f l, f r) Source #
applyMaybe :: Applicative f => f (a -> Maybe b) -> f a -> f b Source #
applyThese :: Applicative f => f (a -> These l r) -> f a -> (f l, f r) Source #
bindMaybe :: Monad f => (a -> f (Maybe b)) -> f a -> f b Source #
bindThese :: Monad f => (a -> f (These l r)) -> f a -> (f l, f r) Source #
traverseMaybe :: (Applicative g, Traversable f) => (a -> g (Maybe b)) -> f a -> g (f b) Source #
traverseThese :: (Applicative g, Traversable f) => (a -> g (These l r)) -> f a -> g (f l, f r) Source #
Instances
separate :: (Dichotomous g, Functor f, Compactable f) => f (g l r) -> (f l, f r) Source #
Handly flips
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
fforMaybeM :: (Compactable f, Monad f) => f a -> (a -> MaybeT f b) -> f b Source #
fforTheseM :: (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 :: (Dichotomous d, Alternative f, Foldable f) => f (d 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