aws-arn-0.3.1.0: Types and optics for manipulating Amazon Resource Names (ARNs)
Copyright(C) 2020-2022 Bellroy Pty Ltd
LicenseBSD-3-Clause
MaintainerBellroy Tech Team <haskell@bellroy.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.AWS.ARN.Internal.Lens

Description

Reimplement a few lens types and combinators to keep the dependency footprint down.

Documentation

type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s Source #

type Getting r s a = (a -> Const r a) -> s -> Const r s Source #

type Setter s a = (a -> Identity a) -> s -> Identity s Source #

set :: Setter s a -> a -> s -> s Source #

(.~) :: Setter s a -> a -> s -> s infixr 4 Source #

over :: Setter s a -> (a -> a) -> s -> s Source #

(^.) :: s -> Getting a s a -> a infixl 8 Source #

type Prism' s a = forall p f. (Choice p, Applicative f) => p a (f a) -> p s (f s) Source #

prism' :: forall s a. (a -> s) -> (s -> Maybe a) -> Prism' s a Source #

preview :: Prism' s a -> s -> Maybe a Source #

review :: Prism' s a -> a -> s Source #

(^?) :: s -> Prism' s a -> Maybe a infixl 8 Source #

type Traversal' s a = forall f. Applicative f => (a -> f a) -> s -> f s Source #

ix :: Int -> Traversal' [a] a Source #

type Iso' s a = forall p f. (Profunctor p, Functor f) => p a (f a) -> p s (f s) Source #

type AnIso' s a = Exchange a a a (Identity a) -> Exchange a a s (Identity s) Source #

data Exchange a b s t Source #

Constructors

Exchange (s -> a) (b -> t) 

Instances

Instances details
Profunctor (Exchange a b) Source # 
Instance details

Defined in Network.AWS.ARN.Internal.Lens

Methods

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

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

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

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

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

iso :: (s -> a) -> (a -> s) -> Iso' s a Source #

from :: AnIso' s a -> Iso' a s Source #