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.Lens

Description

Internal lens helpers. Only exported for Haddock

Synopsis

Documentation

type Lens s t a b = forall p. Strong p => p a b -> p s t Source #

type LensLike p s t a b = p a b -> p s t Source #

ravel :: (ALens a b a b -> ALens a b s t) -> Lens s t a b Source #

set :: ((a -> b) -> s -> t) -> (s, b) -> t Source #

Setting

view :: Lens s s a a -> s -> a Source #

withLensPrim :: Lens s t a b -> (forall c. (s -> (c, a)) -> ((c, b) -> t) -> r) -> r Source #

idLens :: ALens a b a b Source #

first :: Lens ((a :*: b) x) ((a' :*: b) x) (a x) (a' x) Source #

Lens focusing on the first element of a product

second :: Lens ((a :*: b) x) ((a :*: b') x) (b x) (b' x) Source #

Lens focusing on the second element of a product

fork :: (a -> b) -> (a -> c) -> a -> (b, c) Source #

swap :: (a, b) -> (b, a) Source #

cross :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) Source #

data Coyoneda f b Source #

Constructors

Coyoneda (a -> b) (f a) 
Instances
Functor (Coyoneda f) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

fmap :: (a -> b) -> Coyoneda f a -> Coyoneda f b #

(<$) :: a -> Coyoneda f b -> Coyoneda f a #

inj :: Functor f => Coyoneda f a -> f a Source #

proj :: Functor f => f a -> Coyoneda f a Source #

newtype Alongside p s t a b Source #

Constructors

Alongside 

Fields

Instances
Strong p => Strong (Alongside p c d) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

first' :: Alongside p c d a b -> Alongside p c d (a, c0) (b, c0) #

second' :: Alongside p c d a b -> Alongside p c d (c0, a) (c0, b) #

Profunctor p => Profunctor (Alongside p c d) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

dimap :: (a -> b) -> (c0 -> d0) -> Alongside p c d b c0 -> Alongside p c d a d0 #

lmap :: (a -> b) -> Alongside p c d b c0 -> Alongside p c d a c0 #

rmap :: (b -> c0) -> Alongside p c d a b -> Alongside p c d a c0 #

(#.) :: Coercible c0 b => q b c0 -> Alongside p c d a b -> Alongside p c d a c0 #

(.#) :: Coercible b a => Alongside p c d b c0 -> q a b -> Alongside p c d a c0 #

(??) :: Functor f => f (a -> b) -> a -> f b Source #

alongside :: Profunctor p => LensLike (Alongside p s' t') s t a b -> LensLike (Alongside p a b) s' t' a' b' -> LensLike p (s, s') (t, t') (a, a') (b, b') Source #

assoc3L :: Lens ((a, b), c) ((a', b'), c') (a, (b, c)) (a', (b', c')) Source #

stron :: (Either s s', b) -> Either (s, b) (s', b) Source #

choosing :: forall s t a b s' t'. Lens s t a b -> Lens s' t' a b -> Lens (Either s s') (Either t t') a b Source #

lens :: (s -> (c, a)) -> ((c, b) -> t) -> Lens s t a b Source #

data ALens a b s t Source #

Constructors

ALens (s -> (c, a)) ((c, b) -> t) 
Instances
Strong (ALens a b) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

first' :: ALens a b a0 b0 -> ALens a b (a0, c) (b0, c) #

second' :: ALens a b a0 b0 -> ALens a b (c, a0) (c, b0) #

Profunctor (ALens a b) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

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

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

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

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

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

Functor (ALens a b s) Source # 
Instance details

Defined in Data.Generics.Internal.Profunctor.Lens

Methods

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

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

mLens :: Lens (M1 i c f p) (M1 i c g p) (f p) (g p) Source #

repLens :: (Generic a, Generic b) => Lens a b (Rep a x) (Rep b x) Source #

prodL :: Lens ((a :*: b) x) ((a' :*: b') x) (a x, b x) (a' x, b' x) Source #

prodR :: Lens (a' x, b' x) (a x, b x) ((a' :*: b') x) ((a :*: b) x) Source #

assoc3R :: Lens (a', (b', c')) (a, (b, c)) ((a', b'), c') ((a, b), c) Source #