generic-lens-1.0.0.2: Generically derive traversals, lenses and prisms.

Copyright(C) 2017 Csongor Kiss
LicenseBSD3
MaintainerCsongor Kiss <kiss.csongor.kiss@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Generics.Internal.Profunctor.Prism

Description

Internal lens helpers. Only exported for Haddock

Documentation

type APrism s t a b = Market a b a b -> Market a b s t Source #

type Prism s t a b = forall p. Choice p => p a b -> p s t Source #

type Prism' s a = forall p. Choice p => p a a -> p s s Source #

left :: Prism ((a :+: c) x) ((b :+: c) x) (a x) (b x) Source #

right :: Prism ((a :+: b) x) ((a :+: c) x) (b x) (c x) Source #

prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b Source #

_Left :: Prism (Either a c) (Either b c) a b Source #

_Right :: Prism (Either c a) (Either c b) a b Source #

prismPRavel :: (Market a b a b -> Market a b s t) -> Prism s t a b Source #

build :: (Tagged b b -> Tagged t t) -> b -> t Source #

match :: Prism s t a b -> s -> Either t a Source #

without' :: Prism s t a b -> Prism s t c d -> Prism s t (Either a c) (Either b d) Source #

withPrism :: APrism s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r Source #

prism2prismp :: Market a b s t -> Prism s t a b Source #

idPrism :: Market a b a b Source #

gsum :: (a x -> c) -> (b x -> c) -> (a :+: b) x -> c Source #

plus :: (a -> b) -> (c -> d) -> Either a c -> Either b d Source #

data Market a b s t Source #

Constructors

Market (b -> t) (s -> Either t a) 
Instances
Choice (Market a b) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Prism

Methods

left' :: Market a b a0 b0 -> Market a b (Either a0 c) (Either b0 c) #

right' :: Market a b a0 b0 -> Market a b (Either c a0) (Either c b0) #

Profunctor (Market a b) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Prism

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b b0 c -> Market a b a0 d #

lmap :: (a0 -> b0) -> Market a b b0 c -> Market a b a0 c #

rmap :: (b0 -> c) -> Market a b a0 b0 -> Market a b a0 c #

(#.) :: Coercible c b0 => q b0 c -> Market a b a0 b0 -> Market a b a0 c #

(.#) :: Coercible b0 a0 => Market a b b0 c -> q a0 b0 -> Market a b a0 c #

Functor (Market a b s) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Prism

Methods

fmap :: (a0 -> b0) -> Market a b s a0 -> Market a b s b0 #

(<$) :: a0 -> Market a b s b0 -> Market a b s a0 #