fresnel-0.0.0.0: high-powered optics in a small package
Safe HaskellNone
LanguageHaskell2010

Fresnel.Profunctor.Coexp

Synopsis

Coexponential profunctor

newtype Coexp s t b a Source #

Coexponentials are the dual of functions, consisting of an argument of type a (derived within an environment of type s) and a continuation from the return type b (extending to the eventual result type t). As such, they naturally have the shape of optics, relating the outer context s -> t to the inner a -> b.

Constructors

Coexp 

Fields

  • withCoexp :: forall r. ((s -> a) -> (b -> t) -> r) -> r
     

Instances

Instances details
Profunctor (Coexp s t) Source # 
Instance details

Defined in Fresnel.Profunctor.Coexp

Methods

dimap :: (a -> b) -> (c -> d) -> Coexp s t b c -> Coexp s t a d

lmap :: (a -> b) -> Coexp s t b c -> Coexp s t a c

rmap :: (b -> c) -> Coexp s t a b -> Coexp s t a c

(#.) :: forall a b c q. Coercible c b => q b c -> Coexp s t a b -> Coexp s t a c

(.#) :: forall a b c q. Coercible b a => Coexp s t b c -> q a b -> Coexp s t a c

IsIso (Coexp s t) Source # 
Instance details

Defined in Fresnel.Iso.Internal

Functor (Coexp s t b) Source # 
Instance details

Defined in Fresnel.Profunctor.Coexp

Methods

fmap :: (a -> b0) -> Coexp s t b a -> Coexp s t b b0 #

(<$) :: a -> Coexp s t b b0 -> Coexp s t b a #

Monoid t => Applicative (Coexp s t b) Source # 
Instance details

Defined in Fresnel.Profunctor.Coexp

Methods

pure :: a -> Coexp s t b a #

(<*>) :: Coexp s t b (a -> b0) -> Coexp s t b a -> Coexp s t b b0 #

liftA2 :: (a -> b0 -> c) -> Coexp s t b a -> Coexp s t b b0 -> Coexp s t b c #

(*>) :: Coexp s t b a -> Coexp s t b b0 -> Coexp s t b b0 #

(<*) :: Coexp s t b a -> Coexp s t b b0 -> Coexp s t b a #

Semigroup (Coexp a b b a) Source # 
Instance details

Defined in Fresnel.Profunctor.Coexp

Methods

(<>) :: Coexp a b b a -> Coexp a b b a -> Coexp a b b a #

sconcat :: NonEmpty (Coexp a b b a) -> Coexp a b b a #

stimes :: Integral b0 => b0 -> Coexp a b b a -> Coexp a b b a #

Monoid (Coexp a b b a) Source # 
Instance details

Defined in Fresnel.Profunctor.Coexp

Methods

mempty :: Coexp a b b a #

mappend :: Coexp a b b a -> Coexp a b b a -> Coexp a b b a #

mconcat :: [Coexp a b b a] -> Coexp a b b a #

Construction

coexp :: (s -> a) -> (b -> t) -> Coexp s t b a Source #

Elimination

recall :: Coexp s t b a -> s -> a Source #

forget :: Coexp s t b a -> b -> t Source #