compactable-0.1.1.1: A typeclass for structures which can be catMaybed, filtered, and partitioned.

Safe HaskellNone
LanguageHaskell2010

Control.Compactable

Contents

Synopsis

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.

Methods

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 #

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 #

Instances

Compactable [] Source # 

Methods

compact :: [Maybe a] -> [a] Source #

separate :: [Either l r] -> ([l], [r]) Source #

filter :: (a -> Bool) -> [a] -> [a] Source #

fmapMaybe :: Functor [] => (a -> Maybe b) -> [a] -> [b] Source #

fmapEither :: Functor [] => (a -> Either l r) -> [a] -> ([l], [r]) Source #

applyMaybe :: Applicative [] => [a -> Maybe b] -> [a] -> [b] Source #

applyEither :: Applicative [] => [a -> Either l r] -> [a] -> ([l], [r]) Source #

bindMaybe :: Monad [] => [a] -> (a -> [Maybe b]) -> [b] Source #

bindEither :: Monad [] => [a] -> (a -> [Either l r]) -> ([l], [r]) Source #

traverseMaybe :: (Applicative g, Traversable []) => (a -> g (Maybe b)) -> [a] -> g [b] Source #

traverseEither :: (Applicative g, Traversable []) => (a -> g (Either l r)) -> [a] -> g ([l], [r]) Source #

Compactable Maybe Source # 

Methods

compact :: Maybe (Maybe a) -> Maybe a Source #

separate :: Maybe (Either l r) -> (Maybe l, Maybe r) Source #

filter :: (a -> Bool) -> Maybe a -> Maybe a Source #

fmapMaybe :: Functor Maybe => (a -> Maybe b) -> Maybe a -> Maybe b Source #

fmapEither :: Functor Maybe => (a -> Either l r) -> Maybe a -> (Maybe l, Maybe r) Source #

applyMaybe :: Applicative Maybe => Maybe (a -> Maybe b) -> Maybe a -> Maybe b Source #

applyEither :: Applicative Maybe => Maybe (a -> Either l r) -> Maybe a -> (Maybe l, Maybe r) Source #

bindMaybe :: Monad Maybe => Maybe a -> (a -> Maybe (Maybe b)) -> Maybe b Source #

bindEither :: Monad Maybe => Maybe a -> (a -> Maybe (Either l r)) -> (Maybe l, Maybe r) Source #

traverseMaybe :: (Applicative g, Traversable Maybe) => (a -> g (Maybe b)) -> Maybe a -> g (Maybe b) Source #

traverseEither :: (Applicative g, Traversable Maybe) => (a -> g (Either l r)) -> Maybe a -> g (Maybe l, Maybe r) Source #

Compactable IO Source # 

Methods

compact :: IO (Maybe a) -> IO a Source #

separate :: IO (Either l r) -> (IO l, IO r) Source #

filter :: (a -> Bool) -> IO a -> IO a Source #

fmapMaybe :: Functor IO => (a -> Maybe b) -> IO a -> IO b Source #

fmapEither :: Functor IO => (a -> Either l r) -> IO a -> (IO l, IO r) Source #

applyMaybe :: Applicative IO => IO (a -> Maybe b) -> IO a -> IO b Source #

applyEither :: Applicative IO => IO (a -> Either l r) -> IO a -> (IO l, IO r) Source #

bindMaybe :: Monad IO => IO a -> (a -> IO (Maybe b)) -> IO b Source #

bindEither :: Monad IO => IO a -> (a -> IO (Either l r)) -> (IO l, IO r) Source #

traverseMaybe :: (Applicative g, Traversable IO) => (a -> g (Maybe b)) -> IO a -> g (IO b) Source #

traverseEither :: (Applicative g, Traversable IO) => (a -> g (Either l r)) -> IO a -> g (IO l, IO r) Source #

Compactable Option Source # 

Methods

compact :: Option (Maybe a) -> Option a Source #

separate :: Option (Either l r) -> (Option l, Option r) Source #

filter :: (a -> Bool) -> Option a -> Option a Source #

fmapMaybe :: Functor Option => (a -> Maybe b) -> Option a -> Option b Source #

fmapEither :: Functor Option => (a -> Either l r) -> Option a -> (Option l, Option r) Source #

applyMaybe :: Applicative Option => Option (a -> Maybe b) -> Option a -> Option b Source #

applyEither :: Applicative Option => Option (a -> Either l r) -> Option a -> (Option l, Option r) Source #

bindMaybe :: Monad Option => Option a -> (a -> Option (Maybe b)) -> Option b Source #

bindEither :: Monad Option => Option a -> (a -> Option (Either l r)) -> (Option l, Option r) Source #

traverseMaybe :: (Applicative g, Traversable Option) => (a -> g (Maybe b)) -> Option a -> g (Option b) Source #

traverseEither :: (Applicative g, Traversable Option) => (a -> g (Either l r)) -> Option a -> g (Option l, Option r) Source #

Compactable STM Source # 

Methods

compact :: STM (Maybe a) -> STM a Source #

separate :: STM (Either l r) -> (STM l, STM r) Source #

filter :: (a -> Bool) -> STM a -> STM a Source #

fmapMaybe :: Functor STM => (a -> Maybe b) -> STM a -> STM b Source #

fmapEither :: Functor STM => (a -> Either l r) -> STM a -> (STM l, STM r) Source #

applyMaybe :: Applicative STM => STM (a -> Maybe b) -> STM a -> STM b Source #

applyEither :: Applicative STM => STM (a -> Either l r) -> STM a -> (STM l, STM r) Source #

bindMaybe :: Monad STM => STM a -> (a -> STM (Maybe b)) -> STM b Source #

bindEither :: Monad STM => STM a -> (a -> STM (Either l r)) -> (STM l, STM r) Source #

traverseMaybe :: (Applicative g, Traversable STM) => (a -> g (Maybe b)) -> STM a -> g (STM b) Source #

traverseEither :: (Applicative g, Traversable STM) => (a -> g (Either l r)) -> STM a -> g (STM l, STM r) Source #

Compactable ReadPrec Source # 
Compactable ReadP Source # 

Methods

compact :: ReadP (Maybe a) -> ReadP a Source #

separate :: ReadP (Either l r) -> (ReadP l, ReadP r) Source #

filter :: (a -> Bool) -> ReadP a -> ReadP a Source #

fmapMaybe :: Functor ReadP => (a -> Maybe b) -> ReadP a -> ReadP b Source #

fmapEither :: Functor ReadP => (a -> Either l r) -> ReadP a -> (ReadP l, ReadP r) Source #

applyMaybe :: Applicative ReadP => ReadP (a -> Maybe b) -> ReadP a -> ReadP b Source #

applyEither :: Applicative ReadP => ReadP (a -> Either l r) -> ReadP a -> (ReadP l, ReadP r) Source #

bindMaybe :: Monad ReadP => ReadP a -> (a -> ReadP (Maybe b)) -> ReadP b Source #

bindEither :: Monad ReadP => ReadP a -> (a -> ReadP (Either l r)) -> (ReadP l, ReadP r) Source #

traverseMaybe :: (Applicative g, Traversable ReadP) => (a -> g (Maybe b)) -> ReadP a -> g (ReadP b) Source #

traverseEither :: (Applicative g, Traversable ReadP) => (a -> g (Either l r)) -> ReadP a -> g (ReadP l, ReadP r) Source #

Compactable IntMap Source # 

Methods

compact :: IntMap (Maybe a) -> IntMap a Source #

separate :: IntMap (Either l r) -> (IntMap l, IntMap r) Source #

filter :: (a -> Bool) -> IntMap a -> IntMap a Source #

fmapMaybe :: Functor IntMap => (a -> Maybe b) -> IntMap a -> IntMap b Source #

fmapEither :: Functor IntMap => (a -> Either l r) -> IntMap a -> (IntMap l, IntMap r) Source #

applyMaybe :: Applicative IntMap => IntMap (a -> Maybe b) -> IntMap a -> IntMap b Source #

applyEither :: Applicative IntMap => IntMap (a -> Either l r) -> IntMap a -> (IntMap l, IntMap r) Source #

bindMaybe :: Monad IntMap => IntMap a -> (a -> IntMap (Maybe b)) -> IntMap b Source #

bindEither :: Monad IntMap => IntMap a -> (a -> IntMap (Either l r)) -> (IntMap l, IntMap r) Source #

traverseMaybe :: (Applicative g, Traversable IntMap) => (a -> g (Maybe b)) -> IntMap a -> g (IntMap b) Source #

traverseEither :: (Applicative g, Traversable IntMap) => (a -> g (Either l r)) -> IntMap a -> g (IntMap l, IntMap r) Source #

Compactable Seq Source # 

Methods

compact :: Seq (Maybe a) -> Seq a Source #

separate :: Seq (Either l r) -> (Seq l, Seq r) Source #

filter :: (a -> Bool) -> Seq a -> Seq a Source #

fmapMaybe :: Functor Seq => (a -> Maybe b) -> Seq a -> Seq b Source #

fmapEither :: Functor Seq => (a -> Either l r) -> Seq a -> (Seq l, Seq r) Source #

applyMaybe :: Applicative Seq => Seq (a -> Maybe b) -> Seq a -> Seq b Source #

applyEither :: Applicative Seq => Seq (a -> Either l r) -> Seq a -> (Seq l, Seq r) Source #

bindMaybe :: Monad Seq => Seq a -> (a -> Seq (Maybe b)) -> Seq b Source #

bindEither :: Monad Seq => Seq a -> (a -> Seq (Either l r)) -> (Seq l, Seq r) Source #

traverseMaybe :: (Applicative g, Traversable Seq) => (a -> g (Maybe b)) -> Seq a -> g (Seq b) Source #

traverseEither :: (Applicative g, Traversable Seq) => (a -> g (Either l r)) -> Seq a -> g (Seq l, Seq r) Source #

Compactable Set Source # 

Methods

compact :: Set (Maybe a) -> Set a Source #

separate :: Set (Either l r) -> (Set l, Set r) Source #

filter :: (a -> Bool) -> Set a -> Set a Source #

fmapMaybe :: Functor Set => (a -> Maybe b) -> Set a -> Set b Source #

fmapEither :: Functor Set => (a -> Either l r) -> Set a -> (Set l, Set r) Source #

applyMaybe :: Applicative Set => Set (a -> Maybe b) -> Set a -> Set b Source #

applyEither :: Applicative Set => Set (a -> Either l r) -> Set a -> (Set l, Set r) Source #

bindMaybe :: Monad Set => Set a -> (a -> Set (Maybe b)) -> Set b Source #

bindEither :: Monad Set => Set a -> (a -> Set (Either l r)) -> (Set l, Set r) Source #

traverseMaybe :: (Applicative g, Traversable Set) => (a -> g (Maybe b)) -> Set a -> g (Set b) Source #

traverseEither :: (Applicative g, Traversable Set) => (a -> g (Either l r)) -> Set a -> g (Set l, Set r) Source #

Compactable Vector Source # 

Methods

compact :: Vector (Maybe a) -> Vector a Source #

separate :: Vector (Either l r) -> (Vector l, Vector r) Source #

filter :: (a -> Bool) -> Vector a -> Vector a Source #

fmapMaybe :: Functor Vector => (a -> Maybe b) -> Vector a -> Vector b Source #

fmapEither :: Functor Vector => (a -> Either l r) -> Vector a -> (Vector l, Vector r) Source #

applyMaybe :: Applicative Vector => Vector (a -> Maybe b) -> Vector a -> Vector b Source #

applyEither :: Applicative Vector => Vector (a -> Either l r) -> Vector a -> (Vector l, Vector r) Source #

bindMaybe :: Monad Vector => Vector a -> (a -> Vector (Maybe b)) -> Vector b Source #

bindEither :: Monad Vector => Vector a -> (a -> Vector (Either l r)) -> (Vector l, Vector r) Source #

traverseMaybe :: (Applicative g, Traversable Vector) => (a -> g (Maybe b)) -> Vector a -> g (Vector b) Source #

traverseEither :: (Applicative g, Traversable Vector) => (a -> g (Either l r)) -> Vector a -> g (Vector l, Vector r) Source #

Monoid m => Compactable (Either m) Source # 

Methods

compact :: Either m (Maybe a) -> Either m a Source #

separate :: Either m (Either l r) -> (Either m l, Either m r) Source #

filter :: (a -> Bool) -> Either m a -> Either m a Source #

fmapMaybe :: Functor (Either m) => (a -> Maybe b) -> Either m a -> Either m b Source #

fmapEither :: Functor (Either m) => (a -> Either l r) -> Either m a -> (Either m l, Either m r) Source #

applyMaybe :: Applicative (Either m) => Either m (a -> Maybe b) -> Either m a -> Either m b Source #

applyEither :: Applicative (Either m) => Either m (a -> Either l r) -> Either m a -> (Either m l, Either m r) Source #

bindMaybe :: Monad (Either m) => Either m a -> (a -> Either m (Maybe b)) -> Either m b Source #

bindEither :: Monad (Either m) => Either m a -> (a -> Either m (Either l r)) -> (Either m l, Either m r) Source #

traverseMaybe :: (Applicative g, Traversable (Either m)) => (a -> g (Maybe b)) -> Either m a -> g (Either m b) Source #

traverseEither :: (Applicative g, Traversable (Either m)) => (a -> g (Either l r)) -> Either m a -> g (Either m l, Either m r) Source #

(ArrowApply a, ArrowPlus a) => Compactable (ArrowMonad a) Source # 

Methods

compact :: ArrowMonad a (Maybe a) -> ArrowMonad a a Source #

separate :: ArrowMonad a (Either l r) -> (ArrowMonad a l, ArrowMonad a r) Source #

filter :: (a -> Bool) -> ArrowMonad a a -> ArrowMonad a a Source #

fmapMaybe :: Functor (ArrowMonad a) => (a -> Maybe b) -> ArrowMonad a a -> ArrowMonad a b Source #

fmapEither :: Functor (ArrowMonad a) => (a -> Either l r) -> ArrowMonad a a -> (ArrowMonad a l, ArrowMonad a r) Source #

applyMaybe :: Applicative (ArrowMonad a) => ArrowMonad a (a -> Maybe b) -> ArrowMonad a a -> ArrowMonad a b Source #

applyEither :: Applicative (ArrowMonad a) => ArrowMonad a (a -> Either l r) -> ArrowMonad a a -> (ArrowMonad a l, ArrowMonad a r) Source #

bindMaybe :: Monad (ArrowMonad a) => ArrowMonad a a -> (a -> ArrowMonad a (Maybe b)) -> ArrowMonad a b Source #

bindEither :: Monad (ArrowMonad a) => ArrowMonad a a -> (a -> ArrowMonad a (Either l r)) -> (ArrowMonad a l, ArrowMonad a r) Source #

traverseMaybe :: (Applicative g, Traversable (ArrowMonad a)) => (a -> g (Maybe b)) -> ArrowMonad a a -> g (ArrowMonad a b) Source #

traverseEither :: (Applicative g, Traversable (ArrowMonad a)) => (a -> g (Either l r)) -> ArrowMonad a a -> g (ArrowMonad a l, ArrowMonad a r) Source #

Compactable (Proxy *) Source # 

Methods

compact :: Proxy * (Maybe a) -> Proxy * a Source #

separate :: Proxy * (Either l r) -> (Proxy * l, Proxy * r) Source #

filter :: (a -> Bool) -> Proxy * a -> Proxy * a Source #

fmapMaybe :: Functor (Proxy *) => (a -> Maybe b) -> Proxy * a -> Proxy * b Source #

fmapEither :: Functor (Proxy *) => (a -> Either l r) -> Proxy * a -> (Proxy * l, Proxy * r) Source #

applyMaybe :: Applicative (Proxy *) => Proxy * (a -> Maybe b) -> Proxy * a -> Proxy * b Source #

applyEither :: Applicative (Proxy *) => Proxy * (a -> Either l r) -> Proxy * a -> (Proxy * l, Proxy * r) Source #

bindMaybe :: Monad (Proxy *) => Proxy * a -> (a -> Proxy * (Maybe b)) -> Proxy * b Source #

bindEither :: Monad (Proxy *) => Proxy * a -> (a -> Proxy * (Either l r)) -> (Proxy * l, Proxy * r) Source #

traverseMaybe :: (Applicative g, Traversable (Proxy *)) => (a -> g (Maybe b)) -> Proxy * a -> g (Proxy * b) Source #

traverseEither :: (Applicative g, Traversable (Proxy *)) => (a -> g (Either l r)) -> Proxy * a -> g (Proxy * l, Proxy * r) Source #

Compactable (Map k) Source # 

Methods

compact :: Map k (Maybe a) -> Map k a Source #

separate :: Map k (Either l r) -> (Map k l, Map k r) Source #

filter :: (a -> Bool) -> Map k a -> Map k a Source #

fmapMaybe :: Functor (Map k) => (a -> Maybe b) -> Map k a -> Map k b Source #

fmapEither :: Functor (Map k) => (a -> Either l r) -> Map k a -> (Map k l, Map k r) Source #

applyMaybe :: Applicative (Map k) => Map k (a -> Maybe b) -> Map k a -> Map k b Source #

applyEither :: Applicative (Map k) => Map k (a -> Either l r) -> Map k a -> (Map k l, Map k r) Source #

bindMaybe :: Monad (Map k) => Map k a -> (a -> Map k (Maybe b)) -> Map k b Source #

bindEither :: Monad (Map k) => Map k a -> (a -> Map k (Either l r)) -> (Map k l, Map k r) Source #

traverseMaybe :: (Applicative g, Traversable (Map k)) => (a -> g (Maybe b)) -> Map k a -> g (Map k b) Source #

traverseEither :: (Applicative g, Traversable (Map k)) => (a -> g (Either l r)) -> Map k a -> g (Map k l, Map k r) Source #

Compactable (Const * r) Source # 

Methods

compact :: Const * r (Maybe a) -> Const * r a Source #

separate :: Const * r (Either l r) -> (Const * r l, Const * r r) Source #

filter :: (a -> Bool) -> Const * r a -> Const * r a Source #

fmapMaybe :: Functor (Const * r) => (a -> Maybe b) -> Const * r a -> Const * r b Source #

fmapEither :: Functor (Const * r) => (a -> Either l r) -> Const * r a -> (Const * r l, Const * r r) Source #

applyMaybe :: Applicative (Const * r) => Const * r (a -> Maybe b) -> Const * r a -> Const * r b Source #

applyEither :: Applicative (Const * r) => Const * r (a -> Either l r) -> Const * r a -> (Const * r l, Const * r r) Source #

bindMaybe :: Monad (Const * r) => Const * r a -> (a -> Const * r (Maybe b)) -> Const * r b Source #

bindEither :: Monad (Const * r) => Const * r a -> (a -> Const * r (Either l r)) -> (Const * r l, Const * r r) Source #

traverseMaybe :: (Applicative g, Traversable (Const * r)) => (a -> g (Maybe b)) -> Const * r a -> g (Const * r b) Source #

traverseEither :: (Applicative g, Traversable (Const * r)) => (a -> g (Either l r)) -> Const * r a -> g (Const * r l, Const * r r) Source #

(Functor f, Functor g, Compactable f, Compactable g) => Compactable (Product * f g) Source # 

Methods

compact :: Product * f g (Maybe a) -> Product * f g a Source #

separate :: Product * f g (Either l r) -> (Product * f g l, Product * f g r) Source #

filter :: (a -> Bool) -> Product * f g a -> Product * f g a Source #

fmapMaybe :: Functor (Product * f g) => (a -> Maybe b) -> Product * f g a -> Product * f g b Source #

fmapEither :: Functor (Product * f g) => (a -> Either l r) -> Product * f g a -> (Product * f g l, Product * f g r) Source #

applyMaybe :: Applicative (Product * f g) => Product * f g (a -> Maybe b) -> Product * f g a -> Product * f g b Source #

applyEither :: Applicative (Product * f g) => Product * f g (a -> Either l r) -> Product * f g a -> (Product * f g l, Product * f g r) Source #

bindMaybe :: Monad (Product * f g) => Product * f g a -> (a -> Product * f g (Maybe b)) -> Product * f g b Source #

bindEither :: Monad (Product * f g) => Product * f g a -> (a -> Product * f g (Either l r)) -> (Product * f g l, Product * f g r) Source #

traverseMaybe :: (Applicative g, Traversable (Product * f g)) => (a -> g (Maybe b)) -> Product * f g a -> g (Product * f g b) Source #

traverseEither :: (Applicative g, Traversable (Product * f g)) => (a -> g (Either l r)) -> Product * f g a -> g (Product * f g l, Product * f g r) Source #

(Functor f, Functor g, Compactable g) => Compactable (Compose * * f g) Source # 

Methods

compact :: Compose * * f g (Maybe a) -> Compose * * f g a Source #

separate :: Compose * * f g (Either l r) -> (Compose * * f g l, Compose * * f g r) Source #

filter :: (a -> Bool) -> Compose * * f g a -> Compose * * f g a Source #

fmapMaybe :: Functor (Compose * * f g) => (a -> Maybe b) -> Compose * * f g a -> Compose * * f g b Source #

fmapEither :: Functor (Compose * * f g) => (a -> Either l r) -> Compose * * f g a -> (Compose * * f g l, Compose * * f g r) Source #

applyMaybe :: Applicative (Compose * * f g) => Compose * * f g (a -> Maybe b) -> Compose * * f g a -> Compose * * f g b Source #

applyEither :: Applicative (Compose * * f g) => Compose * * f g (a -> Either l r) -> Compose * * f g a -> (Compose * * f g l, Compose * * f g r) Source #

bindMaybe :: Monad (Compose * * f g) => Compose * * f g a -> (a -> Compose * * f g (Maybe b)) -> Compose * * f g b Source #

bindEither :: Monad (Compose * * f g) => Compose * * f g a -> (a -> Compose * * f g (Either l r)) -> (Compose * * f g l, Compose * * f g r) Source #

traverseMaybe :: (Applicative g, Traversable (Compose * * f g)) => (a -> g (Maybe b)) -> Compose * * f g a -> g (Compose * * f g b) Source #

traverseEither :: (Applicative g, Traversable (Compose * * f g)) => (a -> g (Either l r)) -> Compose * * f g a -> g (Compose * * f g l, Compose * * f g 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 MonadPlus (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.

Methods

compactFold :: Foldable g => f (g a) -> f a Source #

compactFold :: (MonadPlus f, Foldable g) => f (g a) -> f a Source #

separateFold :: Bifoldable g => f (g a b) -> (f a, f b) Source #

separateFold :: (MonadPlus 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 #

Instances

CompactFold [] Source # 

Methods

compactFold :: Foldable g => [g a] -> [a] Source #

separateFold :: Bifoldable g => [g a b] -> ([a], [b]) Source #

fmapFold :: (Functor [], Foldable g) => (a -> g b) -> [a] -> [b] Source #

fmapBifold :: (Functor [], Bifoldable g) => (a -> g l r) -> [a] -> ([l], [r]) Source #

applyFold :: (Applicative [], Foldable g) => [a -> g b] -> [a] -> [b] Source #

applyBifold :: (Applicative [], Bifoldable g) => [a -> g l r] -> [a] -> ([l], [r]) Source #

bindFold :: (Monad [], Foldable g) => [a] -> (a -> [g b]) -> [b] Source #

bindBifold :: (Monad [], Bifoldable g) => [a] -> (a -> [g l r]) -> ([l], [r]) Source #

traverseFold :: (Applicative h, Foldable g, Traversable []) => (a -> h (g b)) -> [a] -> h [b] Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable []) => (a -> h (g l r)) -> [a] -> h ([l], [r]) Source #

CompactFold Maybe Source # 

Methods

compactFold :: Foldable g => Maybe (g a) -> Maybe a Source #

separateFold :: Bifoldable g => Maybe (g a b) -> (Maybe a, Maybe b) Source #

fmapFold :: (Functor Maybe, Foldable g) => (a -> g b) -> Maybe a -> Maybe b Source #

fmapBifold :: (Functor Maybe, Bifoldable g) => (a -> g l r) -> Maybe a -> (Maybe l, Maybe r) Source #

applyFold :: (Applicative Maybe, Foldable g) => Maybe (a -> g b) -> Maybe a -> Maybe b Source #

applyBifold :: (Applicative Maybe, Bifoldable g) => Maybe (a -> g l r) -> Maybe a -> (Maybe l, Maybe r) Source #

bindFold :: (Monad Maybe, Foldable g) => Maybe a -> (a -> Maybe (g b)) -> Maybe b Source #

bindBifold :: (Monad Maybe, Bifoldable g) => Maybe a -> (a -> Maybe (g l r)) -> (Maybe l, Maybe r) Source #

traverseFold :: (Applicative h, Foldable g, Traversable Maybe) => (a -> h (g b)) -> Maybe a -> h (Maybe b) Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable Maybe) => (a -> h (g l r)) -> Maybe a -> h (Maybe l, Maybe r) Source #

CompactFold STM Source # 

Methods

compactFold :: Foldable g => STM (g a) -> STM a Source #

separateFold :: Bifoldable g => STM (g a b) -> (STM a, STM b) Source #

fmapFold :: (Functor STM, Foldable g) => (a -> g b) -> STM a -> STM b Source #

fmapBifold :: (Functor STM, Bifoldable g) => (a -> g l r) -> STM a -> (STM l, STM r) Source #

applyFold :: (Applicative STM, Foldable g) => STM (a -> g b) -> STM a -> STM b Source #

applyBifold :: (Applicative STM, Bifoldable g) => STM (a -> g l r) -> STM a -> (STM l, STM r) Source #

bindFold :: (Monad STM, Foldable g) => STM a -> (a -> STM (g b)) -> STM b Source #

bindBifold :: (Monad STM, Bifoldable g) => STM a -> (a -> STM (g l r)) -> (STM l, STM r) Source #

traverseFold :: (Applicative h, Foldable g, Traversable STM) => (a -> h (g b)) -> STM a -> h (STM b) Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable STM) => (a -> h (g l r)) -> STM a -> h (STM l, STM r) Source #

CompactFold ReadPrec Source # 

Methods

compactFold :: Foldable g => ReadPrec (g a) -> ReadPrec a Source #

separateFold :: Bifoldable g => ReadPrec (g a b) -> (ReadPrec a, ReadPrec b) Source #

fmapFold :: (Functor ReadPrec, Foldable g) => (a -> g b) -> ReadPrec a -> ReadPrec b Source #

fmapBifold :: (Functor ReadPrec, Bifoldable g) => (a -> g l r) -> ReadPrec a -> (ReadPrec l, ReadPrec r) Source #

applyFold :: (Applicative ReadPrec, Foldable g) => ReadPrec (a -> g b) -> ReadPrec a -> ReadPrec b Source #

applyBifold :: (Applicative ReadPrec, Bifoldable g) => ReadPrec (a -> g l r) -> ReadPrec a -> (ReadPrec l, ReadPrec r) Source #

bindFold :: (Monad ReadPrec, Foldable g) => ReadPrec a -> (a -> ReadPrec (g b)) -> ReadPrec b Source #

bindBifold :: (Monad ReadPrec, Bifoldable g) => ReadPrec a -> (a -> ReadPrec (g l r)) -> (ReadPrec l, ReadPrec r) Source #

traverseFold :: (Applicative h, Foldable g, Traversable ReadPrec) => (a -> h (g b)) -> ReadPrec a -> h (ReadPrec b) Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable ReadPrec) => (a -> h (g l r)) -> ReadPrec a -> h (ReadPrec l, ReadPrec r) Source #

CompactFold ReadP Source # 

Methods

compactFold :: Foldable g => ReadP (g a) -> ReadP a Source #

separateFold :: Bifoldable g => ReadP (g a b) -> (ReadP a, ReadP b) Source #

fmapFold :: (Functor ReadP, Foldable g) => (a -> g b) -> ReadP a -> ReadP b Source #

fmapBifold :: (Functor ReadP, Bifoldable g) => (a -> g l r) -> ReadP a -> (ReadP l, ReadP r) Source #

applyFold :: (Applicative ReadP, Foldable g) => ReadP (a -> g b) -> ReadP a -> ReadP b Source #

applyBifold :: (Applicative ReadP, Bifoldable g) => ReadP (a -> g l r) -> ReadP a -> (ReadP l, ReadP r) Source #

bindFold :: (Monad ReadP, Foldable g) => ReadP a -> (a -> ReadP (g b)) -> ReadP b Source #

bindBifold :: (Monad ReadP, Bifoldable g) => ReadP a -> (a -> ReadP (g l r)) -> (ReadP l, ReadP r) Source #

traverseFold :: (Applicative h, Foldable g, Traversable ReadP) => (a -> h (g b)) -> ReadP a -> h (ReadP b) Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable ReadP) => (a -> h (g l r)) -> ReadP a -> h (ReadP l, ReadP r) Source #

(ArrowApply a, ArrowPlus a) => CompactFold (ArrowMonad a) Source # 

Methods

compactFold :: Foldable g => ArrowMonad a (g a) -> ArrowMonad a a Source #

separateFold :: Bifoldable g => ArrowMonad a (g a b) -> (ArrowMonad a a, ArrowMonad a b) Source #

fmapFold :: (Functor (ArrowMonad a), Foldable g) => (a -> g b) -> ArrowMonad a a -> ArrowMonad a b Source #

fmapBifold :: (Functor (ArrowMonad a), Bifoldable g) => (a -> g l r) -> ArrowMonad a a -> (ArrowMonad a l, ArrowMonad a r) Source #

applyFold :: (Applicative (ArrowMonad a), Foldable g) => ArrowMonad a (a -> g b) -> ArrowMonad a a -> ArrowMonad a b Source #

applyBifold :: (Applicative (ArrowMonad a), Bifoldable g) => ArrowMonad a (a -> g l r) -> ArrowMonad a a -> (ArrowMonad a l, ArrowMonad a r) Source #

bindFold :: (Monad (ArrowMonad a), Foldable g) => ArrowMonad a a -> (a -> ArrowMonad a (g b)) -> ArrowMonad a b Source #

bindBifold :: (Monad (ArrowMonad a), Bifoldable g) => ArrowMonad a a -> (a -> ArrowMonad a (g l r)) -> (ArrowMonad a l, ArrowMonad a r) Source #

traverseFold :: (Applicative h, Foldable g, Traversable (ArrowMonad a)) => (a -> h (g b)) -> ArrowMonad a a -> h (ArrowMonad a b) Source #

traverseBifold :: (Applicative h, Bifoldable g, Traversable (ArrowMonad a)) => (a -> h (g l r)) -> ArrowMonad a a -> h (ArrowMonad a l, ArrowMonad a r) Source #

Handly flips

fforMaybe :: (Compactable f, Functor f) => f a -> (a -> Maybe b) -> f b Source #

fforFold :: (CompactFold f, Functor f, Foldable g) => f a -> (a -> g b) -> f b Source #

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, MonadPlus m) => f a -> m a Source #

mlefts :: (Bifoldable f, MonadPlus m) => f a b -> m a Source #

mrights :: (Bifoldable f, MonadPlus 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