fudgets-0.18.4: The Fudgets Library
Safe HaskellSafe-Inferred
LanguageHaskell98

ConnectF

Documentation

tagF :: (o -> h) -> F i o -> TagF i o h (FUN 'Many i :: TYPE LiftedRep -> Type) Source #

data TagF i o h t Source #

Constructors

TagF (F i o) (o -> h) (t i) 

(>&<) :: forall {f2 :: Type -> Type} {f1 :: Type -> Type} {i} {a} {h} {b} {b}. (Tag f2, Tag f1) => TagF i a h f1 -> TagF b b h f2 -> TagF (Either i b) (Either a b) h (Tags f1 f2) infixl 9 Source #

compTagF :: forall {f2 :: Type -> Type} {f1 :: Type -> Type} {i} {a} {b} {b} {h}. (Tag f2, Tag f1) => (F i a -> F b b -> F (Either i b) (Either a b)) -> TagF i a h f1 -> TagF b b h f2 -> TagF (Either i b) (Either a b) h (Tags f1 f2) Source #

mapTF :: forall {i} {o} {h} {t :: Type -> Type}. (F i o -> F i o) -> TagF i o h t -> TagF i o h t Source #

ltr :: forall {f2 :: Type -> Type} {b} {c} {b} {a} {b}. Tag f2 => (b -> c) -> TagF b a c f2 -> (F b a, Either a b -> c, Tags (FUN 'Many b :: TYPE LiftedRep -> Type) f2 (Either b b)) Source #

class Tag f where Source #

Methods

extend :: (b -> c) -> f b -> f c Source #

Instances

Instances details
(Tag f1, Tag f2) => Tag (Tags f1 f2) Source # 
Instance details

Defined in ConnectF

Methods

extend :: (b -> c) -> Tags f1 f2 b -> Tags f1 f2 c Source #

Tag ((->) a) Source # 
Instance details

Defined in ConnectF

Methods

extend :: (b -> c) -> (a -> b) -> a -> c Source #

data Tags f1 f2 a Source #

Constructors

(f1 a) :&: (f2 a) infixl 9 

Instances

Instances details
(Tag f1, Tag f2) => Tag (Tags f1 f2) Source # 
Instance details

Defined in ConnectF

Methods

extend :: (b -> c) -> Tags f1 f2 b -> Tags f1 f2 c Source #

no :: p -> Maybe a Source #

yes :: a -> Maybe a Source #

left :: (a -> Maybe a) -> Either a b -> Maybe a Source #

right :: (b -> Maybe a) -> Either a b -> Maybe a Source #

leftleft :: (a -> Maybe a) -> Either (Either a b) b -> Maybe a Source #