compactable-0.2.0.0: A typeclass for structures which can be catMaybed, filtered, and partitioned.
Safe HaskellNone
LanguageHaskell2010

Control.Functor.Elastic

Synopsis

Documentation

class Expansive (f :: Type -> Type) Source #

Partial inverse of Compactable

expand (unite x y) = uniteDichotomy x y
unite = emapThese id
map Just = expand
(\x -> unite x x) = map (\x -> These x x)
emapThese f a b = map f (unite a b)
unite (f <$> x) (g <$> y) = bimap f g <$> unite x y
expand (unite x y) = swap <$> unite y x
emapThese f a b = f <$> unite a b
unite empty = map That
flip unite empty = map This
unite mempty = map That
flip unite mempty = map This

Minimal complete definition

unite | emapThese

Instances

Instances details
Expansive [] Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: [l] -> [r] -> [These l r] Source #

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

emapMaybe :: (Maybe b -> a) -> [b] -> [a] Source #

econtramapMaybe :: Contravariant [] => (a -> Maybe b) -> [b] -> [a] Source #

emapThese :: (These l r -> a) -> [l] -> [r] -> [a] Source #

econtramapThese :: Contravariant [] => (a -> These l r) -> [l] -> [r] -> [a] Source #

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

eapplyThese :: Applicative [] => [These l r -> a] -> [l] -> [r] -> [a] Source #

ebindMaybe :: Applicative [] => ([Maybe b] -> a) -> [b] -> [a] Source #

ebindThese :: Applicative [] => ([These l r] -> a) -> [l] -> [r] -> [a] Source #

Expansive Maybe Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Maybe l -> Maybe r -> Maybe (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Maybe b -> Maybe a Source #

econtramapMaybe :: Contravariant Maybe => (a -> Maybe b) -> Maybe b -> Maybe a Source #

emapThese :: (These l r -> a) -> Maybe l -> Maybe r -> Maybe a Source #

econtramapThese :: Contravariant Maybe => (a -> These l r) -> Maybe l -> Maybe r -> Maybe a Source #

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

eapplyThese :: Applicative Maybe => Maybe (These l r -> a) -> Maybe l -> Maybe r -> Maybe a Source #

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

ebindThese :: Applicative Maybe => (Maybe (These l r) -> a) -> Maybe l -> Maybe r -> Maybe a Source #

Expansive Option Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Option l -> Option r -> Option (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Option b -> Option a Source #

econtramapMaybe :: Contravariant Option => (a -> Maybe b) -> Option b -> Option a Source #

emapThese :: (These l r -> a) -> Option l -> Option r -> Option a Source #

econtramapThese :: Contravariant Option => (a -> These l r) -> Option l -> Option r -> Option a Source #

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

eapplyThese :: Applicative Option => Option (These l r -> a) -> Option l -> Option r -> Option a Source #

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

ebindThese :: Applicative Option => (Option (These l r) -> a) -> Option l -> Option r -> Option a Source #

Expansive ZipList Source # 
Instance details

Defined in Control.Functor.Expansive

Expansive IntMap Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: IntMap l -> IntMap r -> IntMap (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> IntMap b -> IntMap a Source #

econtramapMaybe :: Contravariant IntMap => (a -> Maybe b) -> IntMap b -> IntMap a Source #

emapThese :: (These l r -> a) -> IntMap l -> IntMap r -> IntMap a Source #

econtramapThese :: Contravariant IntMap => (a -> These l r) -> IntMap l -> IntMap r -> IntMap a Source #

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

eapplyThese :: Applicative IntMap => IntMap (These l r -> a) -> IntMap l -> IntMap r -> IntMap a Source #

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

ebindThese :: Applicative IntMap => (IntMap (These l r) -> a) -> IntMap l -> IntMap r -> IntMap a Source #

Expansive Seq Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Seq l -> Seq r -> Seq (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Seq b -> Seq a Source #

econtramapMaybe :: Contravariant Seq => (a -> Maybe b) -> Seq b -> Seq a Source #

emapThese :: (These l r -> a) -> Seq l -> Seq r -> Seq a Source #

econtramapThese :: Contravariant Seq => (a -> These l r) -> Seq l -> Seq r -> Seq a Source #

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

eapplyThese :: Applicative Seq => Seq (These l r -> a) -> Seq l -> Seq r -> Seq a Source #

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

ebindThese :: Applicative Seq => (Seq (These l r) -> a) -> Seq l -> Seq r -> Seq a Source #

Expansive Vector Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Vector l -> Vector r -> Vector (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Vector b -> Vector a Source #

econtramapMaybe :: Contravariant Vector => (a -> Maybe b) -> Vector b -> Vector a Source #

emapThese :: (These l r -> a) -> Vector l -> Vector r -> Vector a Source #

econtramapThese :: Contravariant Vector => (a -> These l r) -> Vector l -> Vector r -> Vector a Source #

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

eapplyThese :: Applicative Vector => Vector (These l r -> a) -> Vector l -> Vector r -> Vector a Source #

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

ebindThese :: Applicative Vector => (Vector (These l r) -> a) -> Vector l -> Vector r -> Vector a Source #

Ord k => Expansive (Map k) Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Map k l -> Map k r -> Map k (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Map k b -> Map k a Source #

econtramapMaybe :: Contravariant (Map k) => (a -> Maybe b) -> Map k b -> Map k a Source #

emapThese :: (These l r -> a) -> Map k l -> Map k r -> Map k a Source #

econtramapThese :: Contravariant (Map k) => (a -> These l r) -> Map k l -> Map k r -> Map k a Source #

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

eapplyThese :: Applicative (Map k) => Map k (These l r -> a) -> Map k l -> Map k r -> Map k a Source #

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

ebindThese :: Applicative (Map k) => (Map k (These l r) -> a) -> Map k l -> Map k r -> Map k a Source #

Expansive (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

expand :: Proxy a -> Proxy (Maybe a) Source #

unite :: Proxy l -> Proxy r -> Proxy (These l r) Source #

unfilter :: (Bool -> a) -> Proxy a -> Proxy a Source #

emapMaybe :: (Maybe b -> a) -> Proxy b -> Proxy a Source #

econtramapMaybe :: Contravariant Proxy => (a -> Maybe b) -> Proxy b -> Proxy a Source #

emapThese :: (These l r -> a) -> Proxy l -> Proxy r -> Proxy a Source #

econtramapThese :: Contravariant Proxy => (a -> These l r) -> Proxy l -> Proxy r -> Proxy a Source #

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

eapplyThese :: Applicative Proxy => Proxy (These l r -> a) -> Proxy l -> Proxy r -> Proxy a Source #

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

ebindThese :: Applicative Proxy => (Proxy (These l r) -> a) -> Proxy l -> Proxy r -> Proxy a Source #

Monad m => Expansive (Stream m) Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

expand :: Stream m a -> Stream m (Maybe a) Source #

unite :: Stream m l -> Stream m r -> Stream m (These l r) Source #

unfilter :: (Bool -> a) -> Stream m a -> Stream m a Source #

emapMaybe :: (Maybe b -> a) -> Stream m b -> Stream m a Source #

econtramapMaybe :: Contravariant (Stream m) => (a -> Maybe b) -> Stream m b -> Stream m a Source #

emapThese :: (These l r -> a) -> Stream m l -> Stream m r -> Stream m a Source #

econtramapThese :: Contravariant (Stream m) => (a -> These l r) -> Stream m l -> Stream m r -> Stream m a Source #

eapplyMaybe :: Applicative (Stream m) => Stream m (Maybe a -> b) -> Stream m a -> Stream m b Source #

eapplyThese :: Applicative (Stream m) => Stream m (These l r -> a) -> Stream m l -> Stream m r -> Stream m a Source #

ebindMaybe :: Applicative (Stream m) => (Stream m (Maybe b) -> a) -> Stream m b -> Stream m a Source #

ebindThese :: Applicative (Stream m) => (Stream m (These l r) -> a) -> Stream m l -> Stream m r -> Stream m a Source #

Monad m => Expansive (Bundle m v) Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

expand :: Bundle m v a -> Bundle m v (Maybe a) Source #

unite :: Bundle m v l -> Bundle m v r -> Bundle m v (These l r) Source #

unfilter :: (Bool -> a) -> Bundle m v a -> Bundle m v a Source #

emapMaybe :: (Maybe b -> a) -> Bundle m v b -> Bundle m v a Source #

econtramapMaybe :: Contravariant (Bundle m v) => (a -> Maybe b) -> Bundle m v b -> Bundle m v a Source #

emapThese :: (These l r -> a) -> Bundle m v l -> Bundle m v r -> Bundle m v a Source #

econtramapThese :: Contravariant (Bundle m v) => (a -> These l r) -> Bundle m v l -> Bundle m v r -> Bundle m v a Source #

eapplyMaybe :: Applicative (Bundle m v) => Bundle m v (Maybe a -> b) -> Bundle m v a -> Bundle m v b Source #

eapplyThese :: Applicative (Bundle m v) => Bundle m v (These l r -> a) -> Bundle m v l -> Bundle m v r -> Bundle m v a Source #

ebindMaybe :: Applicative (Bundle m v) => (Bundle m v (Maybe b) -> a) -> Bundle m v b -> Bundle m v a Source #

ebindThese :: Applicative (Bundle m v) => (Bundle m v (These l r) -> a) -> Bundle m v l -> Bundle m v r -> Bundle m v a Source #

(Functor f, Functor g, Expansive f, Expansive g) => Expansive (Product f g) Source # 
Instance details

Defined in Control.Functor.Expansive

Methods

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

unite :: Product f g l -> Product f g r -> Product f g (These l r) Source #

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

emapMaybe :: (Maybe b -> a) -> Product f g b -> Product f g a Source #

econtramapMaybe :: Contravariant (Product f g) => (a -> Maybe b) -> Product f g b -> Product f g a Source #

emapThese :: (These l r -> a) -> Product f g l -> Product f g r -> Product f g a Source #

econtramapThese :: Contravariant (Product f g) => (a -> These l r) -> Product f g l -> Product f g r -> Product f g a Source #

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

eapplyThese :: Applicative (Product f g) => Product f g (These l r -> a) -> Product f g l -> Product f g r -> Product f g a Source #

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

ebindThese :: Applicative (Product f g) => (Product f g (These l r) -> a) -> Product f g l -> Product f g r -> Product f g a Source #

class Compactable (f :: Type -> Type) 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

Minimal complete definition

compact | separateThese

Instances

Instances details
Compactable [] Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: [These l r] -> ([l], [r]) Source #

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

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

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

contramapMaybe :: Contravariant [] => (Maybe b -> a) -> [a] -> [b] Source #

mapThese :: Functor [] => (a -> These l r) -> [a] -> ([l], [r]) Source #

contramapThese :: Contravariant [] => (These l r -> a) -> [a] -> ([l], [r]) Source #

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

applyThese :: Applicative [] => [a -> These l r] -> [a] -> ([l], [r]) Source #

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

bindThese :: Monad [] => (a -> [These l r]) -> [a] -> ([l], [r]) Source #

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

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

Compactable Maybe Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Maybe (These l r) -> (Maybe l, Maybe r) Source #

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

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

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

contramapMaybe :: Contravariant Maybe => (Maybe b -> a) -> Maybe a -> Maybe b Source #

mapThese :: Functor Maybe => (a -> These l r) -> Maybe a -> (Maybe l, Maybe r) Source #

contramapThese :: Contravariant Maybe => (These l r -> a) -> Maybe a -> (Maybe l, Maybe r) Source #

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

applyThese :: Applicative Maybe => Maybe (a -> These l r) -> Maybe a -> (Maybe l, Maybe r) Source #

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

bindThese :: Monad Maybe => (a -> Maybe (These l r)) -> Maybe a -> (Maybe l, Maybe r) Source #

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

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

Compactable IO Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: IO (These l r) -> (IO l, IO r) Source #

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

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

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

contramapMaybe :: Contravariant IO => (Maybe b -> a) -> IO a -> IO b Source #

mapThese :: Functor IO => (a -> These l r) -> IO a -> (IO l, IO r) Source #

contramapThese :: Contravariant IO => (These l r -> a) -> IO a -> (IO l, IO r) Source #

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

applyThese :: Applicative IO => IO (a -> These l r) -> IO a -> (IO l, IO r) Source #

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

bindThese :: Monad IO => (a -> IO (These l r)) -> IO a -> (IO l, IO r) Source #

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

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

Compactable Option Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Option (These l r) -> (Option l, Option r) Source #

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

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

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

contramapMaybe :: Contravariant Option => (Maybe b -> a) -> Option a -> Option b Source #

mapThese :: Functor Option => (a -> These l r) -> Option a -> (Option l, Option r) Source #

contramapThese :: Contravariant Option => (These l r -> a) -> Option a -> (Option l, Option r) Source #

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

applyThese :: Applicative Option => Option (a -> These l r) -> Option a -> (Option l, Option r) Source #

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

bindThese :: Monad Option => (a -> Option (These l r)) -> Option a -> (Option l, Option r) Source #

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

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

Compactable ZipList Source # 
Instance details

Defined in Control.Functor.Compactable

Compactable STM Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: STM (These l r) -> (STM l, STM r) Source #

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

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

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

contramapMaybe :: Contravariant STM => (Maybe b -> a) -> STM a -> STM b Source #

mapThese :: Functor STM => (a -> These l r) -> STM a -> (STM l, STM r) Source #

contramapThese :: Contravariant STM => (These l r -> a) -> STM a -> (STM l, STM r) Source #

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

applyThese :: Applicative STM => STM (a -> These l r) -> STM a -> (STM l, STM r) Source #

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

bindThese :: Monad STM => (a -> STM (These l r)) -> STM a -> (STM l, STM r) Source #

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

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

Compactable IntMap Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: IntMap (These l r) -> (IntMap l, IntMap r) Source #

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

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

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

contramapMaybe :: Contravariant IntMap => (Maybe b -> a) -> IntMap a -> IntMap b Source #

mapThese :: Functor IntMap => (a -> These l r) -> IntMap a -> (IntMap l, IntMap r) Source #

contramapThese :: Contravariant IntMap => (These l r -> a) -> IntMap a -> (IntMap l, IntMap r) Source #

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

applyThese :: Applicative IntMap => IntMap (a -> These l r) -> IntMap a -> (IntMap l, IntMap r) Source #

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

bindThese :: Monad IntMap => (a -> IntMap (These l r)) -> IntMap a -> (IntMap l, IntMap r) Source #

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

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

Compactable Seq Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Seq (These l r) -> (Seq l, Seq r) Source #

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

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

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

contramapMaybe :: Contravariant Seq => (Maybe b -> a) -> Seq a -> Seq b Source #

mapThese :: Functor Seq => (a -> These l r) -> Seq a -> (Seq l, Seq r) Source #

contramapThese :: Contravariant Seq => (These l r -> a) -> Seq a -> (Seq l, Seq r) Source #

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

applyThese :: Applicative Seq => Seq (a -> These l r) -> Seq a -> (Seq l, Seq r) Source #

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

bindThese :: Monad Seq => (a -> Seq (These l r)) -> Seq a -> (Seq l, Seq r) Source #

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

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

Compactable Set Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Set (These l r) -> (Set l, Set r) Source #

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

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

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

contramapMaybe :: Contravariant Set => (Maybe b -> a) -> Set a -> Set b Source #

mapThese :: Functor Set => (a -> These l r) -> Set a -> (Set l, Set r) Source #

contramapThese :: Contravariant Set => (These l r -> a) -> Set a -> (Set l, Set r) Source #

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

applyThese :: Applicative Set => Set (a -> These l r) -> Set a -> (Set l, Set r) Source #

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

bindThese :: Monad Set => (a -> Set (These l r)) -> Set a -> (Set l, Set r) Source #

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

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

Compactable Vector Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Vector (These l r) -> (Vector l, Vector r) Source #

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

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

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

contramapMaybe :: Contravariant Vector => (Maybe b -> a) -> Vector a -> Vector b Source #

mapThese :: Functor Vector => (a -> These l r) -> Vector a -> (Vector l, Vector r) Source #

contramapThese :: Contravariant Vector => (These l r -> a) -> Vector a -> (Vector l, Vector r) Source #

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

applyThese :: Applicative Vector => Vector (a -> These l r) -> Vector a -> (Vector l, Vector r) Source #

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

bindThese :: Monad Vector => (a -> Vector (These l r)) -> Vector a -> (Vector l, Vector r) Source #

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

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

Monoid m => Compactable (Either m) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

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

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

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

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

contramapMaybe :: Contravariant (Either m) => (Maybe b -> a) -> Either m a -> Either m b Source #

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

contramapThese :: Contravariant (Either m) => (These l r -> a) -> 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 #

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

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

bindThese :: Monad (Either m) => (a -> Either m (These l r)) -> Either m a -> (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 #

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

Compactable (U1 :: Type -> Type) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: U1 (These l r) -> (U1 l, U1 r) Source #

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

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

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

contramapMaybe :: Contravariant U1 => (Maybe b -> a) -> U1 a -> U1 b Source #

mapThese :: Functor U1 => (a -> These l r) -> U1 a -> (U1 l, U1 r) Source #

contramapThese :: Contravariant U1 => (These l r -> a) -> U1 a -> (U1 l, U1 r) Source #

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

applyThese :: Applicative U1 => U1 (a -> These l r) -> U1 a -> (U1 l, U1 r) Source #

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

bindThese :: Monad U1 => (a -> U1 (These l r)) -> U1 a -> (U1 l, U1 r) Source #

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

traverseThese :: (Applicative g, Traversable U1) => (a -> g (These l r)) -> U1 a -> g (U1 l, U1 r) Source #

Compactable (Map k) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Map k (These l r) -> (Map k l, Map k r) Source #

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

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

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

contramapMaybe :: Contravariant (Map k) => (Maybe b -> a) -> Map k a -> Map k b Source #

mapThese :: Functor (Map k) => (a -> These l r) -> Map k a -> (Map k l, Map k r) Source #

contramapThese :: Contravariant (Map k) => (These l r -> a) -> 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 #

applyThese :: Applicative (Map k) => Map k (a -> These l r) -> Map k a -> (Map k l, Map k r) Source #

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

bindThese :: Monad (Map k) => (a -> Map k (These l r)) -> Map k a -> (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 #

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

(Compactable a, Monad a) => Compactable (WrappedMonad a) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: WrappedMonad a (These l r) -> (WrappedMonad a l, WrappedMonad a r) Source #

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

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

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

contramapMaybe :: Contravariant (WrappedMonad a) => (Maybe b -> a0) -> WrappedMonad a a0 -> WrappedMonad a b Source #

mapThese :: Functor (WrappedMonad a) => (a0 -> These l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) Source #

contramapThese :: Contravariant (WrappedMonad a) => (These l r -> a0) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) Source #

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

applyThese :: Applicative (WrappedMonad a) => WrappedMonad a (a0 -> These l r) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) Source #

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

bindThese :: Monad (WrappedMonad a) => (a0 -> WrappedMonad a (These l r)) -> WrappedMonad a a0 -> (WrappedMonad a l, WrappedMonad a r) Source #

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

traverseThese :: (Applicative g, Traversable (WrappedMonad a)) => (a0 -> g (These l r)) -> WrappedMonad a a0 -> g (WrappedMonad a l, WrappedMonad a r) Source #

Compactable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Proxy (These l r) -> (Proxy l, Proxy r) Source #

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

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

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

contramapMaybe :: Contravariant Proxy => (Maybe b -> a) -> Proxy a -> Proxy b Source #

mapThese :: Functor Proxy => (a -> These l r) -> Proxy a -> (Proxy l, Proxy r) Source #

contramapThese :: Contravariant Proxy => (These l r -> a) -> Proxy a -> (Proxy l, Proxy r) Source #

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

applyThese :: Applicative Proxy => Proxy (a -> These l r) -> Proxy a -> (Proxy l, Proxy r) Source #

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

bindThese :: Monad Proxy => (a -> Proxy (These l r)) -> Proxy a -> (Proxy l, Proxy r) Source #

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

traverseThese :: (Applicative g, Traversable Proxy) => (a -> g (These l r)) -> Proxy a -> g (Proxy l, Proxy r) Source #

Monoid m => Compactable (These m) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: These m (These l r) -> (These m l, These m r) Source #

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

partition :: (a -> Bool) -> These m a -> (These m a, These m a) Source #

mapMaybe :: Functor (These m) => (a -> Maybe b) -> These m a -> These m b Source #

contramapMaybe :: Contravariant (These m) => (Maybe b -> a) -> These m a -> These m b Source #

mapThese :: Functor (These m) => (a -> These l r) -> These m a -> (These m l, These m r) Source #

contramapThese :: Contravariant (These m) => (These l r -> a) -> These m a -> (These m l, These m r) Source #

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

applyThese :: Applicative (These m) => These m (a -> These l r) -> These m a -> (These m l, These m r) Source #

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

bindThese :: Monad (These m) => (a -> These m (These l r)) -> These m a -> (These m l, These m r) Source #

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

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

(Compactable a, Functor a) => Compactable (Rec1 a) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Rec1 a (These l r) -> (Rec1 a l, Rec1 a r) Source #

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

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

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

contramapMaybe :: Contravariant (Rec1 a) => (Maybe b -> a0) -> Rec1 a a0 -> Rec1 a b Source #

mapThese :: Functor (Rec1 a) => (a0 -> These l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) Source #

contramapThese :: Contravariant (Rec1 a) => (These l r -> a0) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) Source #

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

applyThese :: Applicative (Rec1 a) => Rec1 a (a0 -> These l r) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) Source #

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

bindThese :: Monad (Rec1 a) => (a0 -> Rec1 a (These l r)) -> Rec1 a a0 -> (Rec1 a l, Rec1 a r) Source #

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

traverseThese :: (Applicative g, Traversable (Rec1 a)) => (a0 -> g (These l r)) -> Rec1 a a0 -> g (Rec1 a l, Rec1 a r) Source #

Compactable (Const r :: Type -> Type) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Const r (These l r0) -> (Const r l, Const r r0) Source #

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

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

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

contramapMaybe :: Contravariant (Const r) => (Maybe b -> a) -> Const r a -> Const r b Source #

mapThese :: Functor (Const r) => (a -> These l r0) -> Const r a -> (Const r l, Const r r0) Source #

contramapThese :: Contravariant (Const r) => (These l r0 -> a) -> Const r a -> (Const r l, Const r r0) Source #

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

applyThese :: Applicative (Const r) => Const r (a -> These l r0) -> Const r a -> (Const r l, Const r r0) Source #

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

bindThese :: Monad (Const r) => (a -> Const r (These l r0)) -> Const r a -> (Const r l, Const r r0) Source #

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

traverseThese :: (Applicative g, Traversable (Const r)) => (a -> g (These l r0)) -> Const r a -> g (Const r l, Const r r0) Source #

(Compactable a, Functor a) => Compactable (Alt a) Source # 
Instance details

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Alt a (These l r) -> (Alt a l, Alt a r) Source #

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

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

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

contramapMaybe :: Contravariant (Alt a) => (Maybe b -> a0) -> Alt a a0 -> Alt a b Source #

mapThese :: Functor (Alt a) => (a0 -> These l r) -> Alt a a0 -> (Alt a l, Alt a r) Source #

contramapThese :: Contravariant (Alt a) => (These l r -> a0) -> Alt a a0 -> (Alt a l, Alt a r) Source #

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

applyThese :: Applicative (Alt a) => Alt a (a0 -> These l r) -> Alt a a0 -> (Alt a l, Alt a r) Source #

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

bindThese :: Monad (Alt a) => (a0 -> Alt a (These l r)) -> Alt a a0 -> (Alt a l, Alt a r) Source #

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

traverseThese :: (Applicative g, Traversable (Alt a)) => (a0 -> g (These l r)) -> Alt a a0 -> g (Alt a l, Alt a r) Source #

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

Defined in Control.Functor.Compactable

Methods

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

separateThese :: (a :*: b) (These l r) -> ((a :*: b) l, (a :*: b) r) Source #

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

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

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

contramapMaybe :: Contravariant (a :*: b) => (Maybe b0 -> a0) -> (a :*: b) a0 -> (a :*: b) b0 Source #

mapThese :: Functor (a :*: b) => (a0 -> These l r) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) Source #

contramapThese :: Contravariant (a :*: b) => (These l r -> a0) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) Source #

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

applyThese :: Applicative (a :*: b) => (a :*: b) (a0 -> These l r) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) Source #

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

bindThese :: Monad (a :*: b) => (a0 -> (a :*: b) (These l r)) -> (a :*: b) a0 -> ((a :*: b) l, (a :*: b) r) Source #

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

traverseThese :: (Applicative g, Traversable (a :*: b)) => (a0 -> g (These l r)) -> (a :*: b) a0 -> g ((a :*: b) l, (a :*: b) r) Source #

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

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Product f g (These l r) -> (Product f g l, Product f g r) Source #

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

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

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

contramapMaybe :: Contravariant (Product f g) => (Maybe b -> a) -> Product f g a -> Product f g b Source #

mapThese :: Functor (Product f g) => (a -> These l r) -> Product f g a -> (Product f g l, Product f g r) Source #

contramapThese :: Contravariant (Product f g) => (These l r -> a) -> 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 #

applyThese :: Applicative (Product f g) => Product f g (a -> These l r) -> Product f g a -> (Product f g l, Product f g r) Source #

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

bindThese :: Monad (Product f g) => (a -> Product f g (These l r)) -> Product f g a -> (Product f g l, Product f g r) Source #

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

traverseThese :: (Applicative g0, Traversable (Product f g)) => (a -> g0 (These l r)) -> Product f g a -> g0 (Product f g l, Product f g r) Source #

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

Defined in Control.Functor.Compactable

Methods

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

separateThese :: M1 i c f (These l r) -> (M1 i c f l, M1 i c f r) Source #

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

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

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

contramapMaybe :: Contravariant (M1 i c f) => (Maybe b -> a) -> M1 i c f a -> M1 i c f b Source #

mapThese :: Functor (M1 i c f) => (a -> These l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) Source #

contramapThese :: Contravariant (M1 i c f) => (These l r -> a) -> M1 i c f a -> (M1 i c f l, M1 i c f r) Source #

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

applyThese :: Applicative (M1 i c f) => M1 i c f (a -> These l r) -> M1 i c f a -> (M1 i c f l, M1 i c f r) Source #

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

bindThese :: Monad (M1 i c f) => (a -> M1 i c f (These l r)) -> M1 i c f a -> (M1 i c f l, M1 i c f r) Source #

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

traverseThese :: (Applicative g, Traversable (M1 i c f)) => (a -> g (These l r)) -> M1 i c f a -> g (M1 i c f l, M1 i c f r) Source #

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

Defined in Control.Functor.Compactable

Methods

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

separateThese :: (f :.: g) (These l r) -> ((f :.: g) l, (f :.: g) r) Source #

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

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

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

contramapMaybe :: Contravariant (f :.: g) => (Maybe b -> a) -> (f :.: g) a -> (f :.: g) b Source #

mapThese :: Functor (f :.: g) => (a -> These l r) -> (f :.: g) a -> ((f :.: g) l, (f :.: g) r) Source #

contramapThese :: Contravariant (f :.: g) => (These l r -> a) -> (f :.: g) a -> ((f :.: g) l, (f :.: g) r) Source #

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

applyThese :: Applicative (f :.: g) => (f :.: g) (a -> These l r) -> (f :.: g) a -> ((f :.: g) l, (f :.: g) r) Source #

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

bindThese :: Monad (f :.: g) => (a -> (f :.: g) (These l r)) -> (f :.: g) a -> ((f :.: g) l, (f :.: g) r) Source #

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

traverseThese :: (Applicative g0, Traversable (f :.: g)) => (a -> g0 (These l r)) -> (f :.: g) a -> g0 ((f :.: g) l, (f :.: g) r) Source #

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

Defined in Control.Functor.Compactable

Methods

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

separateThese :: Compose f g (These l r) -> (Compose f g l, Compose f g r) Source #

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

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

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

contramapMaybe :: Contravariant (Compose f g) => (Maybe b -> a) -> Compose f g a -> Compose f g b Source #

mapThese :: Functor (Compose f g) => (a -> These l r) -> Compose f g a -> (Compose f g l, Compose f g r) Source #

contramapThese :: Contravariant (Compose f g) => (These l r -> a) -> 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 #

applyThese :: Applicative (Compose f g) => Compose f g (a -> These l r) -> Compose f g a -> (Compose f g l, Compose f g r) Source #

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

bindThese :: Monad (Compose f g) => (a -> Compose f g (These l r)) -> Compose f g a -> (Compose f g l, Compose f g r) Source #

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

traverseThese :: (Applicative g0, Traversable (Compose f g)) => (a -> g0 (These l r)) -> Compose f g a -> g0 (Compose f g l, Compose f g r) Source #

class (Compactable f, Expansive f) => Elastic f Source #

Instances

Instances details
Elastic Maybe Source # 
Instance details

Defined in Control.Functor.Elastic

Elastic IntMap Source # 
Instance details

Defined in Control.Functor.Elastic

Ord k => Elastic (Map k) Source # 
Instance details

Defined in Control.Functor.Elastic