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

Control.Functor.Expansive

Contents

Synopsis

Expand

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

Methods

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

default expand :: Functor f => f a -> f (Maybe a) Source #

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

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

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

default emapMaybe :: Functor f => (Maybe b -> a) -> f b -> f a Source #

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

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

default emapThese :: Functor f => (These l r -> a) -> f l -> f r -> f a Source #

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

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

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

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

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

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 #

uniteDichotomy :: (Functor f, Expansive f, Dichotomous g) => f l -> f r -> f (Maybe (g l r)) Source #