planet-mitchell-0.1.0: Planet Mitchell

Safe HaskellNone
LanguageHaskell2010

Compactable

Synopsis

Documentation

class Compactable (f :: * -> *) where #

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 #

separate :: f (Either l r) -> (f l, f r) #

filter :: (a -> Bool) -> f a -> f a #

partition :: (a -> Bool) -> f a -> (f a, f a) #

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

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

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

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

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

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

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

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

Instances
Compactable [] 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> [a] -> ([a], [a]) #

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

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

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

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

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

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

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

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

Compactable Maybe 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Maybe a -> (Maybe a, Maybe a) #

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

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

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

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

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

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

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

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

Compactable IO 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> IO a -> (IO a, IO a) #

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

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

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

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

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

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

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

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

Compactable Option 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Option a -> (Option a, Option a) #

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

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

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

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

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

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

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

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

Compactable ZipList 
Instance details

Defined in Control.Compactable

Methods

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

separate :: ZipList (Either l r) -> (ZipList l, ZipList r) #

filter :: (a -> Bool) -> ZipList a -> ZipList a #

partition :: (a -> Bool) -> ZipList a -> (ZipList a, ZipList a) #

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

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

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

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

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

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

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

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

Compactable STM 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> STM a -> (STM a, STM a) #

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

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

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

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

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

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

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

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

Compactable ReadPrec 
Instance details

Defined in Control.Compactable

Methods

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

separate :: ReadPrec (Either l r) -> (ReadPrec l, ReadPrec r) #

filter :: (a -> Bool) -> ReadPrec a -> ReadPrec a #

partition :: (a -> Bool) -> ReadPrec a -> (ReadPrec a, ReadPrec a) #

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

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

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

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

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

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

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

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

Compactable ReadP 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> ReadP a -> (ReadP a, ReadP a) #

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

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

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

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

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

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

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

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

Compactable IntMap 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a) #

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

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

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

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

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

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

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

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

Compactable Seq 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a) #

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

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

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

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

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

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

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

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

Compactable Set 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Set a -> (Set a, Set a) #

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

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

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

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

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

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

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

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

Compactable Vector 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a) #

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

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

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

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

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

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

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

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

Monoid m => Compactable (Either m) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Either m a -> (Either m a, Either m a) #

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

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

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

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

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

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

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

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

Compactable (U1 :: * -> *) 
Instance details

Defined in Control.Compactable

Methods

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

separate :: U1 (Either l r) -> (U1 l, U1 r) #

filter :: (a -> Bool) -> U1 a -> U1 a #

partition :: (a -> Bool) -> U1 a -> (U1 a, U1 a) #

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

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

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

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

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

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

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

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

Compactable (Map k) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) #

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

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

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

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

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

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

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

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

Monad a => Compactable (WrappedMonad a) 
Instance details

Defined in Control.Compactable

Methods

compact :: WrappedMonad a (Maybe a0) -> WrappedMonad a a0 #

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

filter :: (a0 -> Bool) -> WrappedMonad a a0 -> WrappedMonad a a0 #

partition :: (a0 -> Bool) -> WrappedMonad a a0 -> (WrappedMonad a a0, WrappedMonad a a0) #

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

fmapEither :: Functor (WrappedMonad a) => (a0 -> Either l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) #

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

applyEither :: Applicative (WrappedMonad a) => WrappedMonad a (a0 -> Either l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) #

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

bindEither :: Monad (WrappedMonad a) => WrappedMonad a a0 -> (a0 -> WrappedMonad a (Either l r)) -> (WrappedMonad a l, WrappedMonad a r) #

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

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

(ArrowPlus a, ArrowApply a) => Compactable (ArrowMonad a) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a0 -> Bool) -> ArrowMonad a a0 -> (ArrowMonad a a0, ArrowMonad a a0) #

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

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

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

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

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

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

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

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

Compactable (Proxy :: * -> *) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Proxy a -> (Proxy a, Proxy a) #

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

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

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

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

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

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

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

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

Functor a => Compactable (Rec1 a) 
Instance details

Defined in Control.Compactable

Methods

compact :: Rec1 a (Maybe a0) -> Rec1 a a0 #

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

filter :: (a0 -> Bool) -> Rec1 a a0 -> Rec1 a a0 #

partition :: (a0 -> Bool) -> Rec1 a a0 -> (Rec1 a a0, Rec1 a a0) #

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

fmapEither :: Functor (Rec1 a) => (a0 -> Either l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) #

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

applyEither :: Applicative (Rec1 a) => Rec1 a (a0 -> Either l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) #

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

bindEither :: Monad (Rec1 a) => Rec1 a a0 -> (a0 -> Rec1 a (Either l r)) -> (Rec1 a l, Rec1 a r) #

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

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

Compactable (Const r :: * -> *) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Const r a -> (Const r a, Const r a) #

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

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

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

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

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

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

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

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

Functor a => Compactable (Alt a) 
Instance details

Defined in Control.Compactable

Methods

compact :: Alt a (Maybe a0) -> Alt a a0 #

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

filter :: (a0 -> Bool) -> Alt a a0 -> Alt a a0 #

partition :: (a0 -> Bool) -> Alt a a0 -> (Alt a a0, Alt a a0) #

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

fmapEither :: Functor (Alt a) => (a0 -> Either l r) -> Alt a a0 -> (Alt a l, Alt a r) #

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

applyEither :: Applicative (Alt a) => Alt a (a0 -> Either l r) -> Alt a a0 -> (Alt a l, Alt a r) #

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

bindEither :: Monad (Alt a) => Alt a a0 -> (a0 -> Alt a (Either l r)) -> (Alt a l, Alt a r) #

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

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

(Functor a, Functor b) => Compactable (a :*: b) 
Instance details

Defined in Control.Compactable

Methods

compact :: (a :*: b) (Maybe a0) -> (a :*: b) a0 #

separate :: (a :*: b) (Either l r) -> ((a :*: b) l, (a :*: b) r) #

filter :: (a0 -> Bool) -> (a :*: b) a0 -> (a :*: b) a0 #

partition :: (a0 -> Bool) -> (a :*: b) a0 -> ((a :*: b) a0, (a :*: b) a0) #

fmapMaybe :: Functor (a :*: b) => (a0 -> Maybe b0) -> (a :*: b) a0 -> (a :*: b) b0 #

fmapEither :: Functor (a :*: b) => (a0 -> Either l r) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) #

applyMaybe :: Applicative (a :*: b) => (a :*: b) (a0 -> Maybe b0) -> (a :*: b) a0 -> (a :*: b) b0 #

applyEither :: Applicative (a :*: b) => (a :*: b) (a0 -> Either l r) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) #

bindMaybe :: Monad (a :*: b) => (a :*: b) a0 -> (a0 -> (a :*: b) (Maybe b0)) -> (a :*: b) b0 #

bindEither :: Monad (a :*: b) => (a :*: b) a0 -> (a0 -> (a :*: b) (Either l r)) -> ((a :*: b) l, (a :*: b) r) #

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

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

(Functor f, Functor g, Compactable f, Compactable g) => Compactable (Product f g) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Product f g a -> (Product f g a, Product f g a) #

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

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

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

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

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

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

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

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

Functor f => Compactable (M1 i c f) 
Instance details

Defined in Control.Compactable

Methods

compact :: M1 i c f (Maybe a) -> M1 i c f a #

separate :: M1 i c f (Either l r) -> (M1 i c f l, M1 i c f r) #

filter :: (a -> Bool) -> M1 i c f a -> M1 i c f a #

partition :: (a -> Bool) -> M1 i c f a -> (M1 i c f a, M1 i c f a) #

fmapMaybe :: Functor (M1 i c f) => (a -> Maybe b) -> M1 i c f a -> M1 i c f b #

fmapEither :: Functor (M1 i c f) => (a -> Either l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) #

applyMaybe :: Applicative (M1 i c f) => M1 i c f (a -> Maybe b) -> M1 i c f a -> M1 i c f b #

applyEither :: Applicative (M1 i c f) => M1 i c f (a -> Either l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) #

bindMaybe :: Monad (M1 i c f) => M1 i c f a -> (a -> M1 i c f (Maybe b)) -> M1 i c f b #

bindEither :: Monad (M1 i c f) => M1 i c f a -> (a -> M1 i c f (Either l r)) -> (M1 i c f l, M1 i c f r) #

traverseMaybe :: (Applicative g, Traversable (M1 i c f)) => (a -> g (Maybe b)) -> M1 i c f a -> g (M1 i c f b) #

traverseEither :: (Applicative g, Traversable (M1 i c f)) => (a -> g (Either l r)) -> M1 i c f a -> g (M1 i c f l, M1 i c f r) #

(Functor f, Functor g) => Compactable (f :.: g) 
Instance details

Defined in Control.Compactable

Methods

compact :: (f :.: g) (Maybe a) -> (f :.: g) a #

separate :: (f :.: g) (Either l r) -> ((f :.: g) l, (f :.: g) r) #

filter :: (a -> Bool) -> (f :.: g) a -> (f :.: g) a #

partition :: (a -> Bool) -> (f :.: g) a -> ((f :.: g) a, (f :.: g) a) #

fmapMaybe :: Functor (f :.: g) => (a -> Maybe b) -> (f :.: g) a -> (f :.: g) b #

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

applyMaybe :: Applicative (f :.: g) => (f :.: g) (a -> Maybe b) -> (f :.: g) a -> (f :.: g) b #

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

bindMaybe :: Monad (f :.: g) => (f :.: g) a -> (a -> (f :.: g) (Maybe b)) -> (f :.: g) b #

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

traverseMaybe :: (Applicative g0, Traversable (f :.: g)) => (a -> g0 (Maybe b)) -> (f :.: g) a -> g0 ((f :.: g) b) #

traverseEither :: (Applicative g0, Traversable (f :.: g)) => (a -> g0 (Either l r)) -> (f :.: g) a -> g0 ((f :.: g) l, (f :.: g) r) #

(Functor f, Functor g, Compactable g) => Compactable (Compose f g) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

partition :: (a -> Bool) -> Compose f g a -> (Compose f g a, Compose f g a) #

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

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

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

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

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

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

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

traverseEither :: (Applicative g0, Traversable (Compose f g)) => (a -> g0 (Either l r)) -> Compose f g a -> g0 (Compose f g l, Compose f g r) #

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

fforEither :: (Compactable f, Functor f) => f a -> (a -> Either l r) -> (f l, f r) #

class Compactable f => CompactFold (f :: * -> *) where #

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.

Methods

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

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

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

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

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

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

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

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

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

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

Instances
CompactFold [] 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold Maybe 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold IO 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => IO (g a) -> IO a #

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

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

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

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

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

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

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

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

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

CompactFold Option 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => Option (g a) -> Option a #

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

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

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

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

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

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

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

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

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

CompactFold ZipList 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => ZipList (g a) -> ZipList a #

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

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

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

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

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

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

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

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

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

CompactFold STM 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold ReadPrec 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold ReadP 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold (U1 :: * -> *) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => U1 (g a) -> U1 a #

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

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

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

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

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

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

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

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

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

MonadPlus a => CompactFold (WrappedMonad a) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => WrappedMonad a (g a0) -> WrappedMonad a a0 #

separateFold :: Bifoldable g => WrappedMonad a (g a0 b) -> (WrappedMonad a a0, WrappedMonad a b) #

fmapFold :: (Functor (WrappedMonad a), Foldable g) => (a0 -> g b) -> WrappedMonad a a0 -> WrappedMonad a b #

fmapBifold :: (Functor (WrappedMonad a), Bifoldable g) => (a0 -> g l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) #

applyFold :: (Applicative (WrappedMonad a), Foldable g) => WrappedMonad a (a0 -> g b) -> WrappedMonad a a0 -> WrappedMonad a b #

applyBifold :: (Applicative (WrappedMonad a), Bifoldable g) => WrappedMonad a (a0 -> g l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) #

bindFold :: (Monad (WrappedMonad a), Foldable g) => WrappedMonad a a0 -> (a0 -> WrappedMonad a (g b)) -> WrappedMonad a b #

bindBifold :: (Monad (WrappedMonad a), Bifoldable g) => WrappedMonad a a0 -> (a0 -> WrappedMonad a (g l r)) -> (WrappedMonad a l, WrappedMonad a r) #

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

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

(ArrowPlus a, ArrowApply a) => CompactFold (ArrowMonad a) 
Instance details

Defined in Control.Compactable

Methods

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

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

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

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

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

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

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

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

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

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

CompactFold (Proxy :: * -> *) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => Proxy (g a) -> Proxy a #

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

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

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

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

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

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

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

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

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

(Alternative a, Monad a) => CompactFold (Rec1 a) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => Rec1 a (g a0) -> Rec1 a a0 #

separateFold :: Bifoldable g => Rec1 a (g a0 b) -> (Rec1 a a0, Rec1 a b) #

fmapFold :: (Functor (Rec1 a), Foldable g) => (a0 -> g b) -> Rec1 a a0 -> Rec1 a b #

fmapBifold :: (Functor (Rec1 a), Bifoldable g) => (a0 -> g l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) #

applyFold :: (Applicative (Rec1 a), Foldable g) => Rec1 a (a0 -> g b) -> Rec1 a a0 -> Rec1 a b #

applyBifold :: (Applicative (Rec1 a), Bifoldable g) => Rec1 a (a0 -> g l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) #

bindFold :: (Monad (Rec1 a), Foldable g) => Rec1 a a0 -> (a0 -> Rec1 a (g b)) -> Rec1 a b #

bindBifold :: (Monad (Rec1 a), Bifoldable g) => Rec1 a a0 -> (a0 -> Rec1 a (g l r)) -> (Rec1 a l, Rec1 a r) #

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

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

(Alternative a, Monad a) => CompactFold (Alt a) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => Alt a (g a0) -> Alt a a0 #

separateFold :: Bifoldable g => Alt a (g a0 b) -> (Alt a a0, Alt a b) #

fmapFold :: (Functor (Alt a), Foldable g) => (a0 -> g b) -> Alt a a0 -> Alt a b #

fmapBifold :: (Functor (Alt a), Bifoldable g) => (a0 -> g l r) -> Alt a a0 -> (Alt a l, Alt a r) #

applyFold :: (Applicative (Alt a), Foldable g) => Alt a (a0 -> g b) -> Alt a a0 -> Alt a b #

applyBifold :: (Applicative (Alt a), Bifoldable g) => Alt a (a0 -> g l r) -> Alt a a0 -> (Alt a l, Alt a r) #

bindFold :: (Monad (Alt a), Foldable g) => Alt a a0 -> (a0 -> Alt a (g b)) -> Alt a b #

bindBifold :: (Monad (Alt a), Bifoldable g) => Alt a a0 -> (a0 -> Alt a (g l r)) -> (Alt a l, Alt a r) #

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

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

(Alternative f, Monad f, Alternative g, Monad g) => CompactFold (f :*: g) 
Instance details

Defined in Control.Compactable

Methods

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

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

fmapFold :: (Functor (f :*: g), Foldable g0) => (a -> g0 b) -> (f :*: g) a -> (f :*: g) b #

fmapBifold :: (Functor (f :*: g), Bifoldable g0) => (a -> g0 l r) -> (f :*: g) a -> ((f :*: g) l, (f :*: g) r) #

applyFold :: (Applicative (f :*: g), Foldable g0) => (f :*: g) (a -> g0 b) -> (f :*: g) a -> (f :*: g) b #

applyBifold :: (Applicative (f :*: g), Bifoldable g0) => (f :*: g) (a -> g0 l r) -> (f :*: g) a -> ((f :*: g) l, (f :*: g) r) #

bindFold :: (Monad (f :*: g), Foldable g0) => (f :*: g) a -> (a -> (f :*: g) (g0 b)) -> (f :*: g) b #

bindBifold :: (Monad (f :*: g), Bifoldable g0) => (f :*: g) a -> (a -> (f :*: g) (g0 l r)) -> ((f :*: g) l, (f :*: g) r) #

traverseFold :: (Applicative h, Foldable g0, Traversable (f :*: g)) => (a -> h (g0 b)) -> (f :*: g) a -> h ((f :*: g) b) #

traverseBifold :: (Applicative h, Bifoldable g0, Traversable (f :*: g)) => (a -> h (g0 l r)) -> (f :*: g) a -> h ((f :*: g) l, (f :*: g) r) #

(Compactable f, Alternative f, Monad f, Compactable g, Alternative g, Monad g) => CompactFold (Product f g) 
Instance details

Defined in Control.Compactable

Methods

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

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

fmapFold :: (Functor (Product f g), Foldable g0) => (a -> g0 b) -> Product f g a -> Product f g b #

fmapBifold :: (Functor (Product f g), Bifoldable g0) => (a -> g0 l r) -> Product f g a -> (Product f g l, Product f g r) #

applyFold :: (Applicative (Product f g), Foldable g0) => Product f g (a -> g0 b) -> Product f g a -> Product f g b #

applyBifold :: (Applicative (Product f g), Bifoldable g0) => Product f g (a -> g0 l r) -> Product f g a -> (Product f g l, Product f g r) #

bindFold :: (Monad (Product f g), Foldable g0) => Product f g a -> (a -> Product f g (g0 b)) -> Product f g b #

bindBifold :: (Monad (Product f g), Bifoldable g0) => Product f g a -> (a -> Product f g (g0 l r)) -> (Product f g l, Product f g r) #

traverseFold :: (Applicative h, Foldable g0, Traversable (Product f g)) => (a -> h (g0 b)) -> Product f g a -> h (Product f g b) #

traverseBifold :: (Applicative h, Bifoldable g0, Traversable (Product f g)) => (a -> h (g0 l r)) -> Product f g a -> h (Product f g l, Product f g r) #

(Alternative f, Monad f) => CompactFold (M1 i c f) 
Instance details

Defined in Control.Compactable

Methods

compactFold :: Foldable g => M1 i c f (g a) -> M1 i c f a #

separateFold :: Bifoldable g => M1 i c f (g a b) -> (M1 i c f a, M1 i c f b) #

fmapFold :: (Functor (M1 i c f), Foldable g) => (a -> g b) -> M1 i c f a -> M1 i c f b #

fmapBifold :: (Functor (M1 i c f), Bifoldable g) => (a -> g l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) #

applyFold :: (Applicative (M1 i c f), Foldable g) => M1 i c f (a -> g b) -> M1 i c f a -> M1 i c f b #

applyBifold :: (Applicative (M1 i c f), Bifoldable g) => M1 i c f (a -> g l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) #

bindFold :: (Monad (M1 i c f), Foldable g) => M1 i c f a -> (a -> M1 i c f (g b)) -> M1 i c f b #

bindBifold :: (Monad (M1 i c f), Bifoldable g) => M1 i c f a -> (a -> M1 i c f (g l r)) -> (M1 i c f l, M1 i c f r) #

traverseFold :: (Applicative h, Foldable g, Traversable (M1 i c f)) => (a -> h (g b)) -> M1 i c f a -> h (M1 i c f b) #

traverseBifold :: (Applicative h, Bifoldable g, Traversable (M1 i c f)) => (a -> h (g l r)) -> M1 i c f a -> h (M1 i c f l, M1 i c f r) #

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

fforBifold :: (CompactFold f, Functor f, Bifoldable g) => f a -> (a -> g l r) -> (f l, f r) #