fudgets-0.18.3.1: The Fudgets Library
Safe HaskellNone
LanguageHaskell98

ConnectF

Documentation

tagF :: (o -> h) -> F i o -> TagF i o h ((->) i :: Type -> 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 o1 h b o2. (Tag f2, Tag f1) => TagF i o1 h f1 -> TagF b o2 h f2 -> TagF (Either i b) (Either o1 o2) h (Tags f1 f2) infixl 9 Source #

compTagF :: forall (f2 :: Type -> Type) (f1 :: Type -> Type) i o1 b o2 h. (Tag f2, Tag f1) => (F i o1 -> F b o2 -> F (Either i b) (Either o1 o2)) -> TagF i o1 h f1 -> TagF b o2 h f2 -> TagF (Either i b) (Either o1 o2) 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) b1 c a o b2. Tag f2 => (b1 -> c) -> TagF a o c f2 -> (F a o, Either o b1 -> c, Tags ((->) b2 :: Type -> Type) f2 (Either a b2)) 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 :: Type -> Type) 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 :: (a1 -> Maybe a2) -> Either a1 p -> Maybe a2 Source #

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

leftleft :: (a1 -> Maybe a2) -> Either (Either a1 p1) p2 -> Maybe a2 Source #