module Fresnel.Tuple
( -- * Lenses
  fst_
, snd_
) where

import Fresnel.Lens

-- Lenses

fst_ :: Lens (a, b) (a', b) a a'
fst_ :: Optic p (a, b) (a', b) a a'
fst_ = ((a, b) -> a)
-> ((a, b) -> a' -> (a', b)) -> Lens (a, b) (a', b) a a'
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (a, b) -> a
forall a b. (a, b) -> a
fst (\ (a, b)
s a'
a' -> (a'
a', (a, b) -> b
forall a b. (a, b) -> b
snd (a, b)
s))

snd_ :: Lens (a, b) (a, b') b b'
snd_ :: Optic p (a, b) (a, b') b b'
snd_ = ((a, b) -> b)
-> ((a, b) -> b' -> (a, b')) -> Lens (a, b) (a, b') b b'
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (a, b) -> b
forall a b. (a, b) -> b
snd (\ (a, b)
s b'
b' -> ((a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
s, b'
b'))