proton-0.0.4
Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Cont

Documentation

data ContP r a b Source #

Constructors

ContP 

Fields

Instances

Instances details
Profunctor (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

dimap :: (a -> b) -> (c -> d) -> ContP r b c -> ContP r a d #

lmap :: (a -> b) -> ContP r b c -> ContP r a c #

rmap :: (b -> c) -> ContP r a b -> ContP r a c #

(#.) :: forall a b c q. Coercible c b => q b c -> ContP r a b -> ContP r a c #

(.#) :: forall a b c q. Coercible b a => ContP r b c -> q a b -> ContP r a c #

Choice (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

left' :: ContP r a b -> ContP r (Either a c) (Either b c) #

right' :: ContP r a b -> ContP r (Either c a) (Either c b) #

Strong (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

first' :: ContP r a b -> ContP r (a, c) (b, c) #

second' :: ContP r a b -> ContP r (c, a) (c, b) #

ProfunctorApply (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

app :: ContP r (ContP r a b, a) b Source #

ProfunctorCont (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

callCC :: (ContP r a b -> ContP r x a) -> ContP r x a Source #

Category (ContP r :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

id :: forall (a :: k). ContP r a a #

(.) :: forall (b :: k) (c :: k) (a :: k). ContP r b c -> ContP r a b -> ContP r a c #

Functor (ContP r a) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

fmap :: (a0 -> b) -> ContP r a a0 -> ContP r a b #

(<$) :: a0 -> ContP r a b -> ContP r a a0 #

class Profunctor p => ProfunctorCont p where Source #

Methods

callCC :: (p a b -> p x a) -> p x a Source #

Instances

Instances details
ProfunctorCont (ContP r) Source # 
Instance details

Defined in Data.Profunctor.Cont

Methods

callCC :: (ContP r a b -> ContP r x a) -> ContP r x a Source #

evalContP :: ContP r a r -> a -> r Source #

reset :: ContP r a r -> ContP r' a r Source #

shift :: ContP r (ContP r (a -> r) r) a Source #

splitPred :: (a -> Bool) -> a -> Either a a Source #

unify :: Either a a -> a Source #