strict-tuple-lens-0.2: Optics for the `strict-tuple` library
Copyright(c) 2020-2021 Emily Pillmore
LicenseBSD-style
MaintainerEmily Pillmore <emilypi@cohomolo.gy>
StabilityExperimental
PortabilityFlexibleContexts, MPTC
Safe HaskellNone
LanguageHaskell2010

Data.Tuple.Strict.Lens.Field

Description

This module exports Field1 through Field19 instances for T1 through T19.

Synopsis
  • class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s where
  • class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s where

Documentation

class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to 1st field of a tuple.

Minimal complete definition

Nothing

Methods

_1 :: Lens s t a b #

Access the 1st field of a tuple (and possibly change its type).

>>> (1,2)^._1
1
>>> _1 .~ "hello" $ (1,2)
("hello",2)
>>> (1,2) & _1 .~ "hello"
("hello",2)
>>> _1 putStrLn ("hello","world")
hello
((),"world")

This can also be used on larger tuples as well:

>>> (1,2,3,4,5) & _1 +~ 41
(42,2,3,4,5)
_1 :: Lens (a,b) (a',b) a a'
_1 :: Lens (a,b,c) (a',b,c) a a'
_1 :: Lens (a,b,c,d) (a',b,c,d) a a'
...
_1 :: Lens (a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'

Instances

Instances details
Field1 (Identity a) (Identity b) a b 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (Identity a) (Identity b) a b #

Field1 (T1 a) (T1 a') a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T1 a) (T1 a') a a' #

Field1 (a, b) (a', b) a a'
_1 k ~(a,b) = (\a' -> (a',b)) <$> k a
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b) (a', b) a a' #

Field1 (Pair a b) (Pair a' b) a a'

Since: lens-4.20

Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (Pair a b) (Pair a' b) a a' #

Field1 (T2 a b) (T2 a' b) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T2 a b) (T2 a' b) a a' #

Field1 (a, b, c) (a', b, c) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c) (a', b, c) a a' #

Field1 (T3 a b c) (T3 a' b c) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T3 a b c) (T3 a' b c) a a' #

Field1 (a, b, c, d) (a', b, c, d) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d) (a', b, c, d) a a' #

Field1 (T4 a b c d) (T4 a' b c d) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T4 a b c d) (T4 a' b c d) a a' #

Field1 ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) #

Field1 (Product f g a) (Product f' g a) (f a) (f' a) 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (Product f g a) (Product f' g a) (f a) (f' a) #

Field1 (a, b, c, d, e) (a', b, c, d, e) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e) (a', b, c, d, e) a a' #

Field1 (T5 a b c d e) (T5 a' b c d e) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T5 a b c d e) (T5 a' b c d e) a a' #

Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f) (a', b, c, d, e, f) a a' #

Field1 (T6 a b c d e f) (T6 a' b c d e f) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T6 a b c d e f) (T6 a' b c d e f) a a' #

Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' #

Field1 (T7 a b c d e f g) (T7 a' b c d e f g) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T7 a b c d e f g) (T7 a' b c d e f g) a a' #

Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' #

Field1 (T8 a b c d e f g h) (T8 a' b c d e f g h) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T8 a b c d e f g h) (T8 a' b c d e f g h) a a' #

Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' #

Field1 (T9 a b c d e f g h i) (T9 a' b c d e f g h i) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T9 a b c d e f g h i) (T9 a' b c d e f g h i) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j) (a', b, c, d, e, f, g, h, i, j) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j) (a', b, c, d, e, f, g, h, i, j) a a' #

Field1 (T10 a b c d e f g h i j) (T10 a' b c d e f g h i j) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T10 a b c d e f g h i j) (T10 a' b c d e f g h i j) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk) (a', b, c, d, e, f, g, h, i, j, kk) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a', b, c, d, e, f, g, h, i, j, kk) a a' #

Field1 (T11 a b c d e f g h i j kk) (T11 a' b c d e f g h i j kk) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T11 a b c d e f g h i j kk) (T11 a' b c d e f g h i j kk) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l) (a', b, c, d, e, f, g, h, i, j, kk, l) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a', b, c, d, e, f, g, h, i, j, kk, l) a a' #

Field1 (T12 a b c d e f g h i j kk l) (T12 a' b c d e f g h i j kk l) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T12 a b c d e f g h i j kk l) (T12 a' b c d e f g h i j kk l) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a', b, c, d, e, f, g, h, i, j, kk, l, m) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a', b, c, d, e, f, g, h, i, j, kk, l, m) a a' #

Field1 (T13 a b c d e f g h i j kk l m) (T13 a' b c d e f g h i j kk l m) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a' b c d e f g h i j kk l m) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n) a a' #

Field1 (T14 a b c d e f g h i j kk l m n) (T14 a' b c d e f g h i j kk l m n) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a' b c d e f g h i j kk l m n) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o) a a' #

Field1 (T15 a b c d e f g h i j kk l m n o) (T15 a' b c d e f g h i j kk l m n o) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a' b c d e f g h i j kk l m n o) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) a a' #

Field1 (T16 a b c d e f g h i j kk l m n o p) (T16 a' b c d e f g h i j kk l m n o p) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a' b c d e f g h i j kk l m n o p) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) a a' #

Field1 (T17 a b c d e f g h i j kk l m n o p q) (T17 a' b c d e f g h i j kk l m n o p q) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a' b c d e f g h i j kk l m n o p q) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) a a' #

Field1 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a' b c d e f g h i j kk l m n o p q r) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a' b c d e f g h i j kk l m n o p q r) a a' #

Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) a a' 
Instance details

Defined in Control.Lens.Tuple

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) a a' #

Field1 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a' b c d e f g h i j kk l m n o p q r s) a a' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_1 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a' b c d e f g h i j kk l m n o p q r s) a a' #

class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 2nd field of a tuple.

Minimal complete definition

Nothing

Methods

_2 :: Lens s t a b #

Access the 2nd field of a tuple.

>>> _2 .~ "hello" $ (1,(),3,4)
(1,"hello",3,4)
>>> (1,2,3,4) & _2 *~ 3
(1,6,3,4)
>>> _2 print (1,2)
2
(1,())
anyOf _2 :: (s -> Bool) -> (a, s) -> Bool
traverse . _2 :: (Applicative f, Traversable t) => (a -> f b) -> t (s, a) -> f (t (s, b))
foldMapOf (traverse . _2) :: (Traversable t, Monoid m) => (s -> m) -> t (b, s) -> m

Instances

Instances details
Field2 (a, b) (a, b') b b'
_2 k ~(a,b) = (\b' -> (a,b')) <$> k b
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b) (a, b') b b' #

Field2 (Pair a b) (Pair a b') b b'

Since: lens-4.20

Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (Pair a b) (Pair a b') b b' #

Field2 (T2 a b) (T2 a b') b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T2 a b) (T2 a b') b b' #

Field2 (a, b, c) (a, b', c) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c) (a, b', c) b b' #

Field2 (T3 a b c) (T3 a b' c) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T3 a b c) (T3 a b' c) b b' #

Field2 (a, b, c, d) (a, b', c, d) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d) (a, b', c, d) b b' #

Field2 (T4 a b c d) (T4 a b' c d) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T4 a b c d) (T4 a b' c d) b b' #

Field2 ((f :*: g) p) ((f :*: g') p) (g p) (g' p) 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens ((f :*: g) p) ((f :*: g') p) (g p) (g' p) #

Field2 (Product f g a) (Product f g' a) (g a) (g' a) 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (Product f g a) (Product f g' a) (g a) (g' a) #

Field2 (a, b, c, d, e) (a, b', c, d, e) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e) (a, b', c, d, e) b b' #

Field2 (T5 a b c d e) (T5 a b' c d e) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T5 a b c d e) (T5 a b' c d e) b b' #

Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f) (a, b', c, d, e, f) b b' #

Field2 (T6 a b c d e f) (T6 a b' c d e f) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T6 a b c d e f) (T6 a b' c d e f) b b' #

Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' #

Field2 (T7 a b c d e f g) (T7 a b' c d e f g) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T7 a b c d e f g) (T7 a b' c d e f g) b b' #

Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' #

Field2 (T8 a b c d e f g h) (T8 a b' c d e f g h) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T8 a b c d e f g h) (T8 a b' c d e f g h) b b' #

Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' #

Field2 (T9 a b c d e f g h i) (T9 a b' c d e f g h i) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T9 a b c d e f g h i) (T9 a b' c d e f g h i) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j) (a, b', c, d, e, f, g, h, i, j) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b', c, d, e, f, g, h, i, j) b b' #

Field2 (T10 a b c d e f g h i j) (T10 a b' c d e f g h i j) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T10 a b c d e f g h i j) (T10 a b' c d e f g h i j) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk) (a, b', c, d, e, f, g, h, i, j, kk) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b', c, d, e, f, g, h, i, j, kk) b b' #

Field2 (T11 a b c d e f g h i j kk) (T11 a b' c d e f g h i j kk) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T11 a b c d e f g h i j kk) (T11 a b' c d e f g h i j kk) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b', c, d, e, f, g, h, i, j, kk, l) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b', c, d, e, f, g, h, i, j, kk, l) b b' #

Field2 (T12 a b c d e f g h i j kk l) (T12 a b' c d e f g h i j kk l) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b' c d e f g h i j kk l) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b', c, d, e, f, g, h, i, j, kk, l, m) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b', c, d, e, f, g, h, i, j, kk, l, m) b b' #

Field2 (T13 a b c d e f g h i j kk l m) (T13 a b' c d e f g h i j kk l m) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b' c d e f g h i j kk l m) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n) b b' #

Field2 (T14 a b c d e f g h i j kk l m n) (T14 a b' c d e f g h i j kk l m n) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b' c d e f g h i j kk l m n) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o) b b' #

Field2 (T15 a b c d e f g h i j kk l m n o) (T15 a b' c d e f g h i j kk l m n o) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b' c d e f g h i j kk l m n o) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p) b b' #

Field2 (T16 a b c d e f g h i j kk l m n o p) (T16 a b' c d e f g h i j kk l m n o p) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b' c d e f g h i j kk l m n o p) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) b b' #

Field2 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b' c d e f g h i j kk l m n o p q) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b' c d e f g h i j kk l m n o p q) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) b b' #

Field2 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b' c d e f g h i j kk l m n o p q r) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b' c d e f g h i j kk l m n o p q r) b b' #

Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) b b' 
Instance details

Defined in Control.Lens.Tuple

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) b b' #

Field2 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b' c d e f g h i j kk l m n o p q r s) b b' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_2 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b' c d e f g h i j kk l m n o p q r s) b b' #

class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 3rd field of a tuple.

Minimal complete definition

Nothing

Methods

_3 :: Lens s t a b #

Access the 3rd field of a tuple.

Instances

Instances details
Field3 (a, b, c) (a, b, c') c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c) (a, b, c') c c' #

Field3 (T3 a b c) (T3 a b c') c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T3 a b c) (T3 a b c') c c' #

Field3 (a, b, c, d) (a, b, c', d) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d) (a, b, c', d) c c' #

Field3 (T4 a b c d) (T4 a b c' d) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T4 a b c d) (T4 a b c' d) c c' #

Field3 (a, b, c, d, e) (a, b, c', d, e) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e) (a, b, c', d, e) c c' #

Field3 (T5 a b c d e) (T5 a b c' d e) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T5 a b c d e) (T5 a b c' d e) c c' #

Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f) (a, b, c', d, e, f) c c' #

Field3 (T6 a b c d e f) (T6 a b c' d e f) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T6 a b c d e f) (T6 a b c' d e f) c c' #

Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' #

Field3 (T7 a b c d e f g) (T7 a b c' d e f g) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T7 a b c d e f g) (T7 a b c' d e f g) c c' #

Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' #

Field3 (T8 a b c d e f g h) (T8 a b c' d e f g h) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T8 a b c d e f g h) (T8 a b c' d e f g h) c c' #

Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' #

Field3 (T9 a b c d e f g h i) (T9 a b c' d e f g h i) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T9 a b c d e f g h i) (T9 a b c' d e f g h i) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j) (a, b, c', d, e, f, g, h, i, j) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c', d, e, f, g, h, i, j) c c' #

Field3 (T10 a b c d e f g h i j) (T10 a b c' d e f g h i j) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T10 a b c d e f g h i j) (T10 a b c' d e f g h i j) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c', d, e, f, g, h, i, j, kk) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c', d, e, f, g, h, i, j, kk) c c' #

Field3 (T11 a b c d e f g h i j kk) (T11 a b c' d e f g h i j kk) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c' d e f g h i j kk) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c', d, e, f, g, h, i, j, kk, l) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c', d, e, f, g, h, i, j, kk, l) c c' #

Field3 (T12 a b c d e f g h i j kk l) (T12 a b c' d e f g h i j kk l) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c' d e f g h i j kk l) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c', d, e, f, g, h, i, j, kk, l, m) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c', d, e, f, g, h, i, j, kk, l, m) c c' #

Field3 (T13 a b c d e f g h i j kk l m) (T13 a b c' d e f g h i j kk l m) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c' d e f g h i j kk l m) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n) c c' #

Field3 (T14 a b c d e f g h i j kk l m n) (T14 a b c' d e f g h i j kk l m n) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c' d e f g h i j kk l m n) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o) c c' #

Field3 (T15 a b c d e f g h i j kk l m n o) (T15 a b c' d e f g h i j kk l m n o) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c' d e f g h i j kk l m n o) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p) c c' #

Field3 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c' d e f g h i j kk l m n o p) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c' d e f g h i j kk l m n o p) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q) c c' #

Field3 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c' d e f g h i j kk l m n o p q) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c' d e f g h i j kk l m n o p q) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) c c' #

Field3 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c' d e f g h i j kk l m n o p q r) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c' d e f g h i j kk l m n o p q r) c c' #

Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) c c' 
Instance details

Defined in Control.Lens.Tuple

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) c c' #

Field3 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c' d e f g h i j kk l m n o p q r s) c c' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_3 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c' d e f g h i j kk l m n o p q r s) c c' #

class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 4th field of a tuple.

Minimal complete definition

Nothing

Methods

_4 :: Lens s t a b #

Access the 4th field of a tuple.

Instances

Instances details
Field4 (a, b, c, d) (a, b, c, d') d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d) (a, b, c, d') d d' #

Field4 (T4 a b c d) (T4 a b c d') d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T4 a b c d) (T4 a b c d') d d' #

Field4 (a, b, c, d, e) (a, b, c, d', e) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e) (a, b, c, d', e) d d' #

Field4 (T5 a b c d e) (T5 a b c d' e) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T5 a b c d e) (T5 a b c d' e) d d' #

Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f) (a, b, c, d', e, f) d d' #

Field4 (T6 a b c d e f) (T6 a b c d' e f) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T6 a b c d e f) (T6 a b c d' e f) d d' #

Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' #

Field4 (T7 a b c d e f g) (T7 a b c d' e f g) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T7 a b c d e f g) (T7 a b c d' e f g) d d' #

Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' #

Field4 (T8 a b c d e f g h) (T8 a b c d' e f g h) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T8 a b c d e f g h) (T8 a b c d' e f g h) d d' #

Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' #

Field4 (T9 a b c d e f g h i) (T9 a b c d' e f g h i) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T9 a b c d e f g h i) (T9 a b c d' e f g h i) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d', e, f, g, h, i, j) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d', e, f, g, h, i, j) d d' #

Field4 (T10 a b c d e f g h i j) (T10 a b c d' e f g h i j) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T10 a b c d e f g h i j) (T10 a b c d' e f g h i j) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d', e, f, g, h, i, j, kk) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d', e, f, g, h, i, j, kk) d d' #

Field4 (T11 a b c d e f g h i j kk) (T11 a b c d' e f g h i j kk) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d' e f g h i j kk) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d', e, f, g, h, i, j, kk, l) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d', e, f, g, h, i, j, kk, l) d d' #

Field4 (T12 a b c d e f g h i j kk l) (T12 a b c d' e f g h i j kk l) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d' e f g h i j kk l) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d', e, f, g, h, i, j, kk, l, m) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d', e, f, g, h, i, j, kk, l, m) d d' #

Field4 (T13 a b c d e f g h i j kk l m) (T13 a b c d' e f g h i j kk l m) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d' e f g h i j kk l m) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n) d d' #

Field4 (T14 a b c d e f g h i j kk l m n) (T14 a b c d' e f g h i j kk l m n) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d' e f g h i j kk l m n) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o) d d' #

Field4 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d' e f g h i j kk l m n o) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d' e f g h i j kk l m n o) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p) d d' #

Field4 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d' e f g h i j kk l m n o p) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d' e f g h i j kk l m n o p) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q) d d' #

Field4 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d' e f g h i j kk l m n o p q) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d' e f g h i j kk l m n o p q) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r) d d' #

Field4 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d' e f g h i j kk l m n o p q r) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d' e f g h i j kk l m n o p q r) d d' #

Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) d d' 
Instance details

Defined in Control.Lens.Tuple

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) d d' #

Field4 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d' e f g h i j kk l m n o p q r s) d d' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_4 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d' e f g h i j kk l m n o p q r s) d d' #

class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 5th field of a tuple.

Minimal complete definition

Nothing

Methods

_5 :: Lens s t a b #

Access the 5th field of a tuple.

Instances

Instances details
Field5 (a, b, c, d, e) (a, b, c, d, e') e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e) (a, b, c, d, e') e e' #

Field5 (T5 a b c d e) (T5 a b c d e') e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T5 a b c d e) (T5 a b c d e') e e' #

Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f) (a, b, c, d, e', f) e e' #

Field5 (T6 a b c d e f) (T6 a b c d e' f) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T6 a b c d e f) (T6 a b c d e' f) e e' #

Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' #

Field5 (T7 a b c d e f g) (T7 a b c d e' f g) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T7 a b c d e f g) (T7 a b c d e' f g) e e' #

Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' #

Field5 (T8 a b c d e f g h) (T8 a b c d e' f g h) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T8 a b c d e f g h) (T8 a b c d e' f g h) e e' #

Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' #

Field5 (T9 a b c d e f g h i) (T9 a b c d e' f g h i) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T9 a b c d e f g h i) (T9 a b c d e' f g h i) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e', f, g, h, i, j) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e', f, g, h, i, j) e e' #

Field5 (T10 a b c d e f g h i j) (T10 a b c d e' f g h i j) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e' f g h i j) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e', f, g, h, i, j, kk) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e', f, g, h, i, j, kk) e e' #

Field5 (T11 a b c d e f g h i j kk) (T11 a b c d e' f g h i j kk) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e' f g h i j kk) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e', f, g, h, i, j, kk, l) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e', f, g, h, i, j, kk, l) e e' #

Field5 (T12 a b c d e f g h i j kk l) (T12 a b c d e' f g h i j kk l) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e' f g h i j kk l) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e', f, g, h, i, j, kk, l, m) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e', f, g, h, i, j, kk, l, m) e e' #

Field5 (T13 a b c d e f g h i j kk l m) (T13 a b c d e' f g h i j kk l m) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e' f g h i j kk l m) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n) e e' #

Field5 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e' f g h i j kk l m n) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e' f g h i j kk l m n) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o) e e' #

Field5 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e' f g h i j kk l m n o) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e' f g h i j kk l m n o) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p) e e' #

Field5 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e' f g h i j kk l m n o p) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e' f g h i j kk l m n o p) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q) e e' #

Field5 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e' f g h i j kk l m n o p q) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e' f g h i j kk l m n o p q) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r) e e' #

Field5 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e' f g h i j kk l m n o p q r) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e' f g h i j kk l m n o p q r) e e' #

Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r, s) e e' 
Instance details

Defined in Control.Lens.Tuple

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r, s) e e' #

Field5 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e' f g h i j kk l m n o p q r s) e e' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_5 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e' f g h i j kk l m n o p q r s) e e' #

class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 6th element of a tuple.

Minimal complete definition

Nothing

Methods

_6 :: Lens s t a b #

Access the 6th field of a tuple.

Instances

Instances details
Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f) (a, b, c, d, e, f') f f' #

Field6 (T6 a b c d e f) (T6 a b c d e f') f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T6 a b c d e f) (T6 a b c d e f') f f' #

Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' #

Field6 (T7 a b c d e f g) (T7 a b c d e f' g) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T7 a b c d e f g) (T7 a b c d e f' g) f f' #

Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' #

Field6 (T8 a b c d e f g h) (T8 a b c d e f' g h) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T8 a b c d e f g h) (T8 a b c d e f' g h) f f' #

Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' #

Field6 (T9 a b c d e f g h i) (T9 a b c d e f' g h i) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f' g h i) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f', g, h, i, j) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f', g, h, i, j) f f' #

Field6 (T10 a b c d e f g h i j) (T10 a b c d e f' g h i j) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f' g h i j) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f', g, h, i, j, kk) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f', g, h, i, j, kk) f f' #

Field6 (T11 a b c d e f g h i j kk) (T11 a b c d e f' g h i j kk) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f' g h i j kk) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f', g, h, i, j, kk, l) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f', g, h, i, j, kk, l) f f' #

Field6 (T12 a b c d e f g h i j kk l) (T12 a b c d e f' g h i j kk l) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f' g h i j kk l) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f', g, h, i, j, kk, l, m) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f', g, h, i, j, kk, l, m) f f' #

Field6 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f' g h i j kk l m) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f' g h i j kk l m) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n) f f' #

Field6 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f' g h i j kk l m n) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f' g h i j kk l m n) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o) f f' #

Field6 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f' g h i j kk l m n o) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f' g h i j kk l m n o) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p) f f' #

Field6 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f' g h i j kk l m n o p) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f' g h i j kk l m n o p) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q) f f' #

Field6 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f' g h i j kk l m n o p q) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f' g h i j kk l m n o p q) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r) f f' #

Field6 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f' g h i j kk l m n o p q r) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f' g h i j kk l m n o p q r) f f' #

Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r, s) f f' 
Instance details

Defined in Control.Lens.Tuple

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r, s) f f' #

Field6 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f' g h i j kk l m n o p q r s) f f' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_6 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f' g h i j kk l m n o p q r s) f f' #

class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 7th field of a tuple.

Minimal complete definition

Nothing

Methods

_7 :: Lens s t a b #

Access the 7th field of a tuple.

Instances

Instances details
Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' #

Field7 (T7 a b c d e f g) (T7 a b c d e f g') g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T7 a b c d e f g) (T7 a b c d e f g') g g' #

Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' #

Field7 (T8 a b c d e f g h) (T8 a b c d e f g' h) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T8 a b c d e f g h) (T8 a b c d e f g' h) g g' #

Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' #

Field7 (T9 a b c d e f g h i) (T9 a b c d e f g' h i) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g' h i) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g', h, i, j) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g', h, i, j) g g' #

Field7 (T10 a b c d e f g h i j) (T10 a b c d e f g' h i j) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g' h i j) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g', h, i, j, kk) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g', h, i, j, kk) g g' #

Field7 (T11 a b c d e f g h i j kk) (T11 a b c d e f g' h i j kk) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g' h i j kk) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g', h, i, j, kk, l) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g', h, i, j, kk, l) g g' #

Field7 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g' h i j kk l) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g' h i j kk l) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g', h, i, j, kk, l, m) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g', h, i, j, kk, l, m) g g' #

Field7 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g' h i j kk l m) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g' h i j kk l m) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n) g g' #

Field7 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g' h i j kk l m n) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g' h i j kk l m n) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o) g g' #

Field7 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g' h i j kk l m n o) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g' h i j kk l m n o) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p) g g' #

Field7 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g' h i j kk l m n o p) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g' h i j kk l m n o p) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q) g g' #

Field7 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g' h i j kk l m n o p q) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g' h i j kk l m n o p q) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r) g g' #

Field7 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g' h i j kk l m n o p q r) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g' h i j kk l m n o p q r) g g' #

Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r, s) g g' 
Instance details

Defined in Control.Lens.Tuple

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r, s) g g' #

Field7 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g' h i j kk l m n o p q r s) g g' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_7 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g' h i j kk l m n o p q r s) g g' #

class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 8th field of a tuple.

Minimal complete definition

Nothing

Methods

_8 :: Lens s t a b #

Access the 8th field of a tuple.

Instances

Instances details
Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' #

Field8 (T8 a b c d e f g h) (T8 a b c d e f g h') h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T8 a b c d e f g h) (T8 a b c d e f g h') h h' #

Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' #

Field8 (T9 a b c d e f g h i) (T9 a b c d e f g h' i) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g h' i) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h', i, j) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h', i, j) h h' #

Field8 (T10 a b c d e f g h i j) (T10 a b c d e f g h' i j) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h' i j) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h', i, j, kk) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h', i, j, kk) h h' #

Field8 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h' i j kk) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h' i j kk) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h', i, j, kk, l) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h', i, j, kk, l) h h' #

Field8 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h' i j kk l) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h' i j kk l) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h', i, j, kk, l, m) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h', i, j, kk, l, m) h h' #

Field8 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h' i j kk l m) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h' i j kk l m) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n) h h' #

Field8 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h' i j kk l m n) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h' i j kk l m n) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o) h h' #

Field8 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h' i j kk l m n o) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h' i j kk l m n o) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p) h h' #

Field8 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h' i j kk l m n o p) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h' i j kk l m n o p) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q) h h' #

Field8 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h' i j kk l m n o p q) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h' i j kk l m n o p q) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r) h h' #

Field8 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h' i j kk l m n o p q r) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h' i j kk l m n o p q r) h h' #

Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r, s) h h' 
Instance details

Defined in Control.Lens.Tuple

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r, s) h h' #

Field8 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h' i j kk l m n o p q r s) h h' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_8 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h' i j kk l m n o p q r s) h h' #

class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 9th field of a tuple.

Minimal complete definition

Nothing

Methods

_9 :: Lens s t a b #

Access the 9th field of a tuple.

Instances

Instances details
Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' #

Field9 (T9 a b c d e f g h i) (T9 a b c d e f g h i') i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g h i') i i' #

Field9 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i', j) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i', j) i i' #

Field9 (T10 a b c d e f g h i j) (T10 a b c d e f g h i' j) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h i' j) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i', j, kk) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i', j, kk) i i' #

Field9 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i' j kk) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i' j kk) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i', j, kk, l) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i', j, kk, l) i i' #

Field9 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i' j kk l) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i' j kk l) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i', j, kk, l, m) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i', j, kk, l, m) i i' #

Field9 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i' j kk l m) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i' j kk l m) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n) i i' #

Field9 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i' j kk l m n) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i' j kk l m n) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o) i i' #

Field9 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i' j kk l m n o) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i' j kk l m n o) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p) i i' #

Field9 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i' j kk l m n o p) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i' j kk l m n o p) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q) i i' #

Field9 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i' j kk l m n o p q) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i' j kk l m n o p q) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r) i i' #

Field9 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i' j kk l m n o p q r) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i' j kk l m n o p q r) i i' #

Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r, s) i i' 
Instance details

Defined in Control.Lens.Tuple

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r, s) i i' #

Field9 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i' j kk l m n o p q r s) i i' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_9 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i' j kk l m n o p q r s) i i' #

class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 10th field of a tuple.

Minimal complete definition

Nothing

Methods

_10 :: Lens s t a b #

Access the 10th field of a tuple.

Instances

Instances details
Field10 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i, j') j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i, j') j j' #

Field10 (T10 a b c d e f g h i j) (T10 a b c d e f g h i j') j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h i j') j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j', kk) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j', kk) j j' #

Field10 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j' kk) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j' kk) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j', kk, l) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j', kk, l) j j' #

Field10 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j' kk l) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j' kk l) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j', kk, l, m) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j', kk, l, m) j j' #

Field10 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j' kk l m) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j' kk l m) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n) j j' #

Field10 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j' kk l m n) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j' kk l m n) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o) j j' #

Field10 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j' kk l m n o) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j' kk l m n o) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p) j j' #

Field10 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j' kk l m n o p) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j' kk l m n o p) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q) j j' #

Field10 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j' kk l m n o p q) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j' kk l m n o p q) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r) j j' #

Field10 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j' kk l m n o p q r) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j' kk l m n o p q r) j j' #

Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r, s) j j' 
Instance details

Defined in Control.Lens.Tuple

Methods

_10 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r, s) j j' #

Field10 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j' kk l m n o p q r s) j j' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_10 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j' kk l m n o p q r s) j j' #

class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 11th field of a tuple.

Minimal complete definition

Nothing

Methods

_11 :: Lens s t a b #

Access the 11th field of a tuple.

Instances

Instances details
Field11 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j, kk') kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j, kk') kk kk' #

Field11 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j kk') kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j kk') kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk', l) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk', l) kk kk' #

Field11 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk' l) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk' l) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk', l, m) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk', l, m) kk kk' #

Field11 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk' l m) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk' l m) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n) kk kk' #

Field11 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk' l m n) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk' l m n) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o) kk kk' #

Field11 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk' l m n o) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk' l m n o) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p) kk kk' #

Field11 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk' l m n o p) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk' l m n o p) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q) kk kk' #

Field11 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk' l m n o p q) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk' l m n o p q) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r) kk kk' #

Field11 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk' l m n o p q r) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk' l m n o p q r) kk kk' #

Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r, s) kk kk' 
Instance details

Defined in Control.Lens.Tuple

Methods

_11 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r, s) kk kk' #

Field11 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk' l m n o p q r s) kk kk' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_11 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk' l m n o p q r s) kk kk' #

class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 12th field of a tuple.

Minimal complete definition

Nothing

Methods

_12 :: Lens s t a b #

Access the 12th field of a tuple.

Instances

Instances details
Field12 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk, l') l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk, l') l l' #

Field12 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk l') l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk l') l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l', m) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l', m) l l' #

Field12 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l' m) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l' m) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n) l l' #

Field12 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l' m n) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l' m n) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o) l l' #

Field12 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l' m n o) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l' m n o) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p) l l' #

Field12 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l' m n o p) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l' m n o p) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q) l l' #

Field12 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l' m n o p q) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l' m n o p q) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r) l l' #

Field12 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l' m n o p q r) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l' m n o p q r) l l' #

Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r, s) l l' 
Instance details

Defined in Control.Lens.Tuple

Methods

_12 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r, s) l l' #

Field12 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l' m n o p q r s) l l' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_12 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l' m n o p q r s) l l' #

class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 13th field of a tuple.

Minimal complete definition

Nothing

Methods

_13 :: Lens s t a b #

Access the 13th field of a tuple.

Instances

Instances details
Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l, m') m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l, m') m m' #

Field13 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l m') m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l m') m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n) m m' #

Field13 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m' n) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m' n) m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o) m m' #

Field13 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m' n o) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m' n o) m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p) m m' #

Field13 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m' n o p) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m' n o p) m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q) m m' #

Field13 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m' n o p q) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m' n o p q) m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r) m m' #

Field13 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m' n o p q r) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m' n o p q r) m m' #

Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r, s) m m' 
Instance details

Defined in Control.Lens.Tuple

Methods

_13 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r, s) m m' #

Field13 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m' n o p q r s) m m' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_13 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m' n o p q r s) m m' #

class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 14th field of a tuple.

Minimal complete definition

Nothing

Methods

_14 :: Lens s t a b #

Access the 14th field of a tuple.

Instances

Instances details
Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n') n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n') n n' #

Field14 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m n') n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m n') n n' #

Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o) n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o) n n' #

Field14 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n' o) n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n' o) n n' #

Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p) n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p) n n' #

Field14 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n' o p) n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n' o p) n n' #

Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q) n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q) n n' #

Field14 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n' o p q) n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n' o p q) n n' #

Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r) n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r) n n' #

Field14 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n' o p q r) n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n' o p q r) n n' #

Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r, s) n n' 
Instance details

Defined in Control.Lens.Tuple

Methods

_14 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r, s) n n' #

Field14 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n' o p q r s) n n' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_14 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n' o p q r s) n n' #

class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 15th field of a tuple.

Minimal complete definition

Nothing

Methods

_15 :: Lens s t a b #

Access the 15th field of a tuple.

Instances

Instances details
Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o') o o' 
Instance details

Defined in Control.Lens.Tuple

Methods

_15 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o') o o' #

Field15 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n o') o o' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_15 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n o') o o' #

Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p) o o' 
Instance details

Defined in Control.Lens.Tuple

Methods

_15 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p) o o' #

Field15 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o' p) o o' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_15 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o' p) o o' #

Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q) o o' 
Instance details

Defined in Control.Lens.Tuple

Methods

_15 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q) o o' #

Field15 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o' p q) o o' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_15 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o' p q) o o' #

Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r) o o' 
Instance details

Defined in Control.Lens.Tuple

Methods

_15 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r) o o' #

Field15 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o' p q r) o o' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_15 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o' p q r) o o' #

Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r, s) o o' 
Instance details

Defined in Control.Lens.Tuple

Methods

_15 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r, s) o o' #

Field15 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o' p q r s) o o' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_15 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o' p q r s) o o' #

class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 16th field of a tuple.

Minimal complete definition

Nothing

Methods

_16 :: Lens s t a b #

Access the 16th field of a tuple.

Instances

Instances details
Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p') p p' 
Instance details

Defined in Control.Lens.Tuple

Methods

_16 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p') p p' #

Field16 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o p') p p' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_16 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o p') p p' #

Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q) p p' 
Instance details

Defined in Control.Lens.Tuple

Methods

_16 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q) p p' #

Field16 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p' q) p p' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_16 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p' q) p p' #

Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r) p p' 
Instance details

Defined in Control.Lens.Tuple

Methods

_16 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r) p p' #

Field16 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p' q r) p p' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_16 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p' q r) p p' #

Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r, s) p p' 
Instance details

Defined in Control.Lens.Tuple

Methods

_16 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r, s) p p' #

Field16 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p' q r s) p p' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_16 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p' q r s) p p' #

class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 17th field of a tuple.

Minimal complete definition

Nothing

Methods

_17 :: Lens s t a b #

Access the 17th field of a tuple.

Instances

Instances details
Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q') q q' 
Instance details

Defined in Control.Lens.Tuple

Methods

_17 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q') q q' #

Field17 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p q') q q' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_17 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p q') q q' #

Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r) q q' 
Instance details

Defined in Control.Lens.Tuple

Methods

_17 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r) q q' #

Field17 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q' r) q q' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_17 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q' r) q q' #

Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r, s) q q' 
Instance details

Defined in Control.Lens.Tuple

Methods

_17 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r, s) q q' #

Field17 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q' r s) q q' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_17 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q' r s) q q' #

class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 18th field of a tuple.

Minimal complete definition

Nothing

Methods

_18 :: Lens s t a b #

Access the 18th field of a tuple.

Instances

Instances details
Field18 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r') r r' 
Instance details

Defined in Control.Lens.Tuple

Methods

_18 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r') r r' #

Field18 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q r') r r' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_18 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q r') r r' #

Field18 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r', s) r r' 
Instance details

Defined in Control.Lens.Tuple

Methods

_18 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r', s) r r' #

Field18 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r' s) r r' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_18 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r' s) r r' #

class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 19th field of a tuple.

Minimal complete definition

Nothing

Methods

_19 :: Lens s t a b #

Access the 19th field of a tuple.

Instances

Instances details
Field19 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s') s s' 
Instance details

Defined in Control.Lens.Tuple

Methods

_19 :: Lens (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s') s s' #

Field19 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r s') s s' Source # 
Instance details

Defined in Data.Tuple.Strict.Lens.Field

Methods

_19 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r s') s s' #

Orphan instances

Field1 (T1 a) (T1 a') a a' Source # 
Instance details

Methods

_1 :: Lens (T1 a) (T1 a') a a' #

Field1 (T2 a b) (T2 a' b) a a' Source # 
Instance details

Methods

_1 :: Lens (T2 a b) (T2 a' b) a a' #

Field2 (T2 a b) (T2 a b') b b' Source # 
Instance details

Methods

_2 :: Lens (T2 a b) (T2 a b') b b' #

Field1 (T3 a b c) (T3 a' b c) a a' Source # 
Instance details

Methods

_1 :: Lens (T3 a b c) (T3 a' b c) a a' #

Field2 (T3 a b c) (T3 a b' c) b b' Source # 
Instance details

Methods

_2 :: Lens (T3 a b c) (T3 a b' c) b b' #

Field3 (T3 a b c) (T3 a b c') c c' Source # 
Instance details

Methods

_3 :: Lens (T3 a b c) (T3 a b c') c c' #

Field1 (T4 a b c d) (T4 a' b c d) a a' Source # 
Instance details

Methods

_1 :: Lens (T4 a b c d) (T4 a' b c d) a a' #

Field2 (T4 a b c d) (T4 a b' c d) b b' Source # 
Instance details

Methods

_2 :: Lens (T4 a b c d) (T4 a b' c d) b b' #

Field3 (T4 a b c d) (T4 a b c' d) c c' Source # 
Instance details

Methods

_3 :: Lens (T4 a b c d) (T4 a b c' d) c c' #

Field4 (T4 a b c d) (T4 a b c d') d d' Source # 
Instance details

Methods

_4 :: Lens (T4 a b c d) (T4 a b c d') d d' #

Field1 (T5 a b c d e) (T5 a' b c d e) a a' Source # 
Instance details

Methods

_1 :: Lens (T5 a b c d e) (T5 a' b c d e) a a' #

Field2 (T5 a b c d e) (T5 a b' c d e) b b' Source # 
Instance details

Methods

_2 :: Lens (T5 a b c d e) (T5 a b' c d e) b b' #

Field3 (T5 a b c d e) (T5 a b c' d e) c c' Source # 
Instance details

Methods

_3 :: Lens (T5 a b c d e) (T5 a b c' d e) c c' #

Field4 (T5 a b c d e) (T5 a b c d' e) d d' Source # 
Instance details

Methods

_4 :: Lens (T5 a b c d e) (T5 a b c d' e) d d' #

Field5 (T5 a b c d e) (T5 a b c d e') e e' Source # 
Instance details

Methods

_5 :: Lens (T5 a b c d e) (T5 a b c d e') e e' #

Field1 (T6 a b c d e f) (T6 a' b c d e f) a a' Source # 
Instance details

Methods

_1 :: Lens (T6 a b c d e f) (T6 a' b c d e f) a a' #

Field2 (T6 a b c d e f) (T6 a b' c d e f) b b' Source # 
Instance details

Methods

_2 :: Lens (T6 a b c d e f) (T6 a b' c d e f) b b' #

Field3 (T6 a b c d e f) (T6 a b c' d e f) c c' Source # 
Instance details

Methods

_3 :: Lens (T6 a b c d e f) (T6 a b c' d e f) c c' #

Field4 (T6 a b c d e f) (T6 a b c d' e f) d d' Source # 
Instance details

Methods

_4 :: Lens (T6 a b c d e f) (T6 a b c d' e f) d d' #

Field5 (T6 a b c d e f) (T6 a b c d e' f) e e' Source # 
Instance details

Methods

_5 :: Lens (T6 a b c d e f) (T6 a b c d e' f) e e' #

Field6 (T6 a b c d e f) (T6 a b c d e f') f f' Source # 
Instance details

Methods

_6 :: Lens (T6 a b c d e f) (T6 a b c d e f') f f' #

Field1 (T7 a b c d e f g) (T7 a' b c d e f g) a a' Source # 
Instance details

Methods

_1 :: Lens (T7 a b c d e f g) (T7 a' b c d e f g) a a' #

Field2 (T7 a b c d e f g) (T7 a b' c d e f g) b b' Source # 
Instance details

Methods

_2 :: Lens (T7 a b c d e f g) (T7 a b' c d e f g) b b' #

Field3 (T7 a b c d e f g) (T7 a b c' d e f g) c c' Source # 
Instance details

Methods

_3 :: Lens (T7 a b c d e f g) (T7 a b c' d e f g) c c' #

Field4 (T7 a b c d e f g) (T7 a b c d' e f g) d d' Source # 
Instance details

Methods

_4 :: Lens (T7 a b c d e f g) (T7 a b c d' e f g) d d' #

Field5 (T7 a b c d e f g) (T7 a b c d e' f g) e e' Source # 
Instance details

Methods

_5 :: Lens (T7 a b c d e f g) (T7 a b c d e' f g) e e' #

Field6 (T7 a b c d e f g) (T7 a b c d e f' g) f f' Source # 
Instance details

Methods

_6 :: Lens (T7 a b c d e f g) (T7 a b c d e f' g) f f' #

Field7 (T7 a b c d e f g) (T7 a b c d e f g') g g' Source # 
Instance details

Methods

_7 :: Lens (T7 a b c d e f g) (T7 a b c d e f g') g g' #

Field1 (T8 a b c d e f g h) (T8 a' b c d e f g h) a a' Source # 
Instance details

Methods

_1 :: Lens (T8 a b c d e f g h) (T8 a' b c d e f g h) a a' #

Field2 (T8 a b c d e f g h) (T8 a b' c d e f g h) b b' Source # 
Instance details

Methods

_2 :: Lens (T8 a b c d e f g h) (T8 a b' c d e f g h) b b' #

Field3 (T8 a b c d e f g h) (T8 a b c' d e f g h) c c' Source # 
Instance details

Methods

_3 :: Lens (T8 a b c d e f g h) (T8 a b c' d e f g h) c c' #

Field4 (T8 a b c d e f g h) (T8 a b c d' e f g h) d d' Source # 
Instance details

Methods

_4 :: Lens (T8 a b c d e f g h) (T8 a b c d' e f g h) d d' #

Field5 (T8 a b c d e f g h) (T8 a b c d e' f g h) e e' Source # 
Instance details

Methods

_5 :: Lens (T8 a b c d e f g h) (T8 a b c d e' f g h) e e' #

Field6 (T8 a b c d e f g h) (T8 a b c d e f' g h) f f' Source # 
Instance details

Methods

_6 :: Lens (T8 a b c d e f g h) (T8 a b c d e f' g h) f f' #

Field7 (T8 a b c d e f g h) (T8 a b c d e f g' h) g g' Source # 
Instance details

Methods

_7 :: Lens (T8 a b c d e f g h) (T8 a b c d e f g' h) g g' #

Field8 (T8 a b c d e f g h) (T8 a b c d e f g h') h h' Source # 
Instance details

Methods

_8 :: Lens (T8 a b c d e f g h) (T8 a b c d e f g h') h h' #

Field1 (T9 a b c d e f g h i) (T9 a' b c d e f g h i) a a' Source # 
Instance details

Methods

_1 :: Lens (T9 a b c d e f g h i) (T9 a' b c d e f g h i) a a' #

Field2 (T9 a b c d e f g h i) (T9 a b' c d e f g h i) b b' Source # 
Instance details

Methods

_2 :: Lens (T9 a b c d e f g h i) (T9 a b' c d e f g h i) b b' #

Field3 (T9 a b c d e f g h i) (T9 a b c' d e f g h i) c c' Source # 
Instance details

Methods

_3 :: Lens (T9 a b c d e f g h i) (T9 a b c' d e f g h i) c c' #

Field4 (T9 a b c d e f g h i) (T9 a b c d' e f g h i) d d' Source # 
Instance details

Methods

_4 :: Lens (T9 a b c d e f g h i) (T9 a b c d' e f g h i) d d' #

Field5 (T9 a b c d e f g h i) (T9 a b c d e' f g h i) e e' Source # 
Instance details

Methods

_5 :: Lens (T9 a b c d e f g h i) (T9 a b c d e' f g h i) e e' #

Field6 (T9 a b c d e f g h i) (T9 a b c d e f' g h i) f f' Source # 
Instance details

Methods

_6 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f' g h i) f f' #

Field7 (T9 a b c d e f g h i) (T9 a b c d e f g' h i) g g' Source # 
Instance details

Methods

_7 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g' h i) g g' #

Field8 (T9 a b c d e f g h i) (T9 a b c d e f g h' i) h h' Source # 
Instance details

Methods

_8 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g h' i) h h' #

Field9 (T9 a b c d e f g h i) (T9 a b c d e f g h i') i i' Source # 
Instance details

Methods

_9 :: Lens (T9 a b c d e f g h i) (T9 a b c d e f g h i') i i' #

Field1 (T10 a b c d e f g h i j) (T10 a' b c d e f g h i j) a a' Source # 
Instance details

Methods

_1 :: Lens (T10 a b c d e f g h i j) (T10 a' b c d e f g h i j) a a' #

Field2 (T10 a b c d e f g h i j) (T10 a b' c d e f g h i j) b b' Source # 
Instance details

Methods

_2 :: Lens (T10 a b c d e f g h i j) (T10 a b' c d e f g h i j) b b' #

Field3 (T10 a b c d e f g h i j) (T10 a b c' d e f g h i j) c c' Source # 
Instance details

Methods

_3 :: Lens (T10 a b c d e f g h i j) (T10 a b c' d e f g h i j) c c' #

Field4 (T10 a b c d e f g h i j) (T10 a b c d' e f g h i j) d d' Source # 
Instance details

Methods

_4 :: Lens (T10 a b c d e f g h i j) (T10 a b c d' e f g h i j) d d' #

Field5 (T10 a b c d e f g h i j) (T10 a b c d e' f g h i j) e e' Source # 
Instance details

Methods

_5 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e' f g h i j) e e' #

Field6 (T10 a b c d e f g h i j) (T10 a b c d e f' g h i j) f f' Source # 
Instance details

Methods

_6 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f' g h i j) f f' #

Field7 (T10 a b c d e f g h i j) (T10 a b c d e f g' h i j) g g' Source # 
Instance details

Methods

_7 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g' h i j) g g' #

Field8 (T10 a b c d e f g h i j) (T10 a b c d e f g h' i j) h h' Source # 
Instance details

Methods

_8 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h' i j) h h' #

Field9 (T10 a b c d e f g h i j) (T10 a b c d e f g h i' j) i i' Source # 
Instance details

Methods

_9 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h i' j) i i' #

Field10 (T10 a b c d e f g h i j) (T10 a b c d e f g h i j') j j' Source # 
Instance details

Methods

_10 :: Lens (T10 a b c d e f g h i j) (T10 a b c d e f g h i j') j j' #

Field1 (T11 a b c d e f g h i j kk) (T11 a' b c d e f g h i j kk) a a' Source # 
Instance details

Methods

_1 :: Lens (T11 a b c d e f g h i j kk) (T11 a' b c d e f g h i j kk) a a' #

Field2 (T11 a b c d e f g h i j kk) (T11 a b' c d e f g h i j kk) b b' Source # 
Instance details

Methods

_2 :: Lens (T11 a b c d e f g h i j kk) (T11 a b' c d e f g h i j kk) b b' #

Field3 (T11 a b c d e f g h i j kk) (T11 a b c' d e f g h i j kk) c c' Source # 
Instance details

Methods

_3 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c' d e f g h i j kk) c c' #

Field4 (T11 a b c d e f g h i j kk) (T11 a b c d' e f g h i j kk) d d' Source # 
Instance details

Methods

_4 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d' e f g h i j kk) d d' #

Field5 (T11 a b c d e f g h i j kk) (T11 a b c d e' f g h i j kk) e e' Source # 
Instance details

Methods

_5 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e' f g h i j kk) e e' #

Field6 (T11 a b c d e f g h i j kk) (T11 a b c d e f' g h i j kk) f f' Source # 
Instance details

Methods

_6 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f' g h i j kk) f f' #

Field7 (T11 a b c d e f g h i j kk) (T11 a b c d e f g' h i j kk) g g' Source # 
Instance details

Methods

_7 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g' h i j kk) g g' #

Field8 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h' i j kk) h h' Source # 
Instance details

Methods

_8 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h' i j kk) h h' #

Field9 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i' j kk) i i' Source # 
Instance details

Methods

_9 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i' j kk) i i' #

Field10 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j' kk) j j' Source # 
Instance details

Methods

_10 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j' kk) j j' #

Field11 (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j kk') kk kk' Source # 
Instance details

Methods

_11 :: Lens (T11 a b c d e f g h i j kk) (T11 a b c d e f g h i j kk') kk kk' #

Field1 (T12 a b c d e f g h i j kk l) (T12 a' b c d e f g h i j kk l) a a' Source # 
Instance details

Methods

_1 :: Lens (T12 a b c d e f g h i j kk l) (T12 a' b c d e f g h i j kk l) a a' #

Field2 (T12 a b c d e f g h i j kk l) (T12 a b' c d e f g h i j kk l) b b' Source # 
Instance details

Methods

_2 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b' c d e f g h i j kk l) b b' #

Field3 (T12 a b c d e f g h i j kk l) (T12 a b c' d e f g h i j kk l) c c' Source # 
Instance details

Methods

_3 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c' d e f g h i j kk l) c c' #

Field4 (T12 a b c d e f g h i j kk l) (T12 a b c d' e f g h i j kk l) d d' Source # 
Instance details

Methods

_4 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d' e f g h i j kk l) d d' #

Field5 (T12 a b c d e f g h i j kk l) (T12 a b c d e' f g h i j kk l) e e' Source # 
Instance details

Methods

_5 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e' f g h i j kk l) e e' #

Field6 (T12 a b c d e f g h i j kk l) (T12 a b c d e f' g h i j kk l) f f' Source # 
Instance details

Methods

_6 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f' g h i j kk l) f f' #

Field7 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g' h i j kk l) g g' Source # 
Instance details

Methods

_7 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g' h i j kk l) g g' #

Field8 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h' i j kk l) h h' Source # 
Instance details

Methods

_8 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h' i j kk l) h h' #

Field9 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i' j kk l) i i' Source # 
Instance details

Methods

_9 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i' j kk l) i i' #

Field10 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j' kk l) j j' Source # 
Instance details

Methods

_10 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j' kk l) j j' #

Field11 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk' l) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk' l) kk kk' #

Field12 (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk l') l l' Source # 
Instance details

Methods

_12 :: Lens (T12 a b c d e f g h i j kk l) (T12 a b c d e f g h i j kk l') l l' #

Field1 (T13 a b c d e f g h i j kk l m) (T13 a' b c d e f g h i j kk l m) a a' Source # 
Instance details

Methods

_1 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a' b c d e f g h i j kk l m) a a' #

Field2 (T13 a b c d e f g h i j kk l m) (T13 a b' c d e f g h i j kk l m) b b' Source # 
Instance details

Methods

_2 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b' c d e f g h i j kk l m) b b' #

Field3 (T13 a b c d e f g h i j kk l m) (T13 a b c' d e f g h i j kk l m) c c' Source # 
Instance details

Methods

_3 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c' d e f g h i j kk l m) c c' #

Field4 (T13 a b c d e f g h i j kk l m) (T13 a b c d' e f g h i j kk l m) d d' Source # 
Instance details

Methods

_4 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d' e f g h i j kk l m) d d' #

Field5 (T13 a b c d e f g h i j kk l m) (T13 a b c d e' f g h i j kk l m) e e' Source # 
Instance details

Methods

_5 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e' f g h i j kk l m) e e' #

Field6 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f' g h i j kk l m) f f' Source # 
Instance details

Methods

_6 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f' g h i j kk l m) f f' #

Field7 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g' h i j kk l m) g g' Source # 
Instance details

Methods

_7 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g' h i j kk l m) g g' #

Field8 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h' i j kk l m) h h' Source # 
Instance details

Methods

_8 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h' i j kk l m) h h' #

Field9 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i' j kk l m) i i' Source # 
Instance details

Methods

_9 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i' j kk l m) i i' #

Field10 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j' kk l m) j j' Source # 
Instance details

Methods

_10 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j' kk l m) j j' #

Field11 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk' l m) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk' l m) kk kk' #

Field12 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l' m) l l' Source # 
Instance details

Methods

_12 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l' m) l l' #

Field13 (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l m') m m' Source # 
Instance details

Methods

_13 :: Lens (T13 a b c d e f g h i j kk l m) (T13 a b c d e f g h i j kk l m') m m' #

Field1 (T14 a b c d e f g h i j kk l m n) (T14 a' b c d e f g h i j kk l m n) a a' Source # 
Instance details

Methods

_1 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a' b c d e f g h i j kk l m n) a a' #

Field2 (T14 a b c d e f g h i j kk l m n) (T14 a b' c d e f g h i j kk l m n) b b' Source # 
Instance details

Methods

_2 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b' c d e f g h i j kk l m n) b b' #

Field3 (T14 a b c d e f g h i j kk l m n) (T14 a b c' d e f g h i j kk l m n) c c' Source # 
Instance details

Methods

_3 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c' d e f g h i j kk l m n) c c' #

Field4 (T14 a b c d e f g h i j kk l m n) (T14 a b c d' e f g h i j kk l m n) d d' Source # 
Instance details

Methods

_4 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d' e f g h i j kk l m n) d d' #

Field5 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e' f g h i j kk l m n) e e' Source # 
Instance details

Methods

_5 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e' f g h i j kk l m n) e e' #

Field6 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f' g h i j kk l m n) f f' Source # 
Instance details

Methods

_6 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f' g h i j kk l m n) f f' #

Field7 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g' h i j kk l m n) g g' Source # 
Instance details

Methods

_7 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g' h i j kk l m n) g g' #

Field8 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h' i j kk l m n) h h' Source # 
Instance details

Methods

_8 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h' i j kk l m n) h h' #

Field9 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i' j kk l m n) i i' Source # 
Instance details

Methods

_9 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i' j kk l m n) i i' #

Field10 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j' kk l m n) j j' Source # 
Instance details

Methods

_10 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j' kk l m n) j j' #

Field11 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk' l m n) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk' l m n) kk kk' #

Field12 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l' m n) l l' Source # 
Instance details

Methods

_12 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l' m n) l l' #

Field13 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m' n) m m' Source # 
Instance details

Methods

_13 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m' n) m m' #

Field14 (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m n') n n' Source # 
Instance details

Methods

_14 :: Lens (T14 a b c d e f g h i j kk l m n) (T14 a b c d e f g h i j kk l m n') n n' #

Field1 (T15 a b c d e f g h i j kk l m n o) (T15 a' b c d e f g h i j kk l m n o) a a' Source # 
Instance details

Methods

_1 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a' b c d e f g h i j kk l m n o) a a' #

Field2 (T15 a b c d e f g h i j kk l m n o) (T15 a b' c d e f g h i j kk l m n o) b b' Source # 
Instance details

Methods

_2 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b' c d e f g h i j kk l m n o) b b' #

Field3 (T15 a b c d e f g h i j kk l m n o) (T15 a b c' d e f g h i j kk l m n o) c c' Source # 
Instance details

Methods

_3 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c' d e f g h i j kk l m n o) c c' #

Field4 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d' e f g h i j kk l m n o) d d' Source # 
Instance details

Methods

_4 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d' e f g h i j kk l m n o) d d' #

Field5 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e' f g h i j kk l m n o) e e' Source # 
Instance details

Methods

_5 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e' f g h i j kk l m n o) e e' #

Field6 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f' g h i j kk l m n o) f f' Source # 
Instance details

Methods

_6 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f' g h i j kk l m n o) f f' #

Field7 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g' h i j kk l m n o) g g' Source # 
Instance details

Methods

_7 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g' h i j kk l m n o) g g' #

Field8 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h' i j kk l m n o) h h' Source # 
Instance details

Methods

_8 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h' i j kk l m n o) h h' #

Field9 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i' j kk l m n o) i i' Source # 
Instance details

Methods

_9 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i' j kk l m n o) i i' #

Field10 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j' kk l m n o) j j' Source # 
Instance details

Methods

_10 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j' kk l m n o) j j' #

Field11 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk' l m n o) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk' l m n o) kk kk' #

Field12 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l' m n o) l l' Source # 
Instance details

Methods

_12 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l' m n o) l l' #

Field13 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m' n o) m m' Source # 
Instance details

Methods

_13 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m' n o) m m' #

Field14 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n' o) n n' Source # 
Instance details

Methods

_14 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n' o) n n' #

Field15 (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n o') o o' Source # 
Instance details

Methods

_15 :: Lens (T15 a b c d e f g h i j kk l m n o) (T15 a b c d e f g h i j kk l m n o') o o' #

Field1 (T16 a b c d e f g h i j kk l m n o p) (T16 a' b c d e f g h i j kk l m n o p) a a' Source # 
Instance details

Methods

_1 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a' b c d e f g h i j kk l m n o p) a a' #

Field2 (T16 a b c d e f g h i j kk l m n o p) (T16 a b' c d e f g h i j kk l m n o p) b b' Source # 
Instance details

Methods

_2 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b' c d e f g h i j kk l m n o p) b b' #

Field3 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c' d e f g h i j kk l m n o p) c c' Source # 
Instance details

Methods

_3 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c' d e f g h i j kk l m n o p) c c' #

Field4 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d' e f g h i j kk l m n o p) d d' Source # 
Instance details

Methods

_4 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d' e f g h i j kk l m n o p) d d' #

Field5 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e' f g h i j kk l m n o p) e e' Source # 
Instance details

Methods

_5 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e' f g h i j kk l m n o p) e e' #

Field6 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f' g h i j kk l m n o p) f f' Source # 
Instance details

Methods

_6 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f' g h i j kk l m n o p) f f' #

Field7 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g' h i j kk l m n o p) g g' Source # 
Instance details

Methods

_7 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g' h i j kk l m n o p) g g' #

Field8 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h' i j kk l m n o p) h h' Source # 
Instance details

Methods

_8 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h' i j kk l m n o p) h h' #

Field9 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i' j kk l m n o p) i i' Source # 
Instance details

Methods

_9 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i' j kk l m n o p) i i' #

Field10 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j' kk l m n o p) j j' Source # 
Instance details

Methods

_10 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j' kk l m n o p) j j' #

Field11 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk' l m n o p) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk' l m n o p) kk kk' #

Field12 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l' m n o p) l l' Source # 
Instance details

Methods

_12 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l' m n o p) l l' #

Field13 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m' n o p) m m' Source # 
Instance details

Methods

_13 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m' n o p) m m' #

Field14 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n' o p) n n' Source # 
Instance details

Methods

_14 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n' o p) n n' #

Field15 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o' p) o o' Source # 
Instance details

Methods

_15 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o' p) o o' #

Field16 (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o p') p p' Source # 
Instance details

Methods

_16 :: Lens (T16 a b c d e f g h i j kk l m n o p) (T16 a b c d e f g h i j kk l m n o p') p p' #

Field1 (T17 a b c d e f g h i j kk l m n o p q) (T17 a' b c d e f g h i j kk l m n o p q) a a' Source # 
Instance details

Methods

_1 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a' b c d e f g h i j kk l m n o p q) a a' #

Field2 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b' c d e f g h i j kk l m n o p q) b b' Source # 
Instance details

Methods

_2 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b' c d e f g h i j kk l m n o p q) b b' #

Field3 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c' d e f g h i j kk l m n o p q) c c' Source # 
Instance details

Methods

_3 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c' d e f g h i j kk l m n o p q) c c' #

Field4 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d' e f g h i j kk l m n o p q) d d' Source # 
Instance details

Methods

_4 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d' e f g h i j kk l m n o p q) d d' #

Field5 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e' f g h i j kk l m n o p q) e e' Source # 
Instance details

Methods

_5 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e' f g h i j kk l m n o p q) e e' #

Field6 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f' g h i j kk l m n o p q) f f' Source # 
Instance details

Methods

_6 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f' g h i j kk l m n o p q) f f' #

Field7 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g' h i j kk l m n o p q) g g' Source # 
Instance details

Methods

_7 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g' h i j kk l m n o p q) g g' #

Field8 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h' i j kk l m n o p q) h h' Source # 
Instance details

Methods

_8 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h' i j kk l m n o p q) h h' #

Field9 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i' j kk l m n o p q) i i' Source # 
Instance details

Methods

_9 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i' j kk l m n o p q) i i' #

Field10 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j' kk l m n o p q) j j' Source # 
Instance details

Methods

_10 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j' kk l m n o p q) j j' #

Field11 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk' l m n o p q) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk' l m n o p q) kk kk' #

Field12 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l' m n o p q) l l' Source # 
Instance details

Methods

_12 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l' m n o p q) l l' #

Field13 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m' n o p q) m m' Source # 
Instance details

Methods

_13 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m' n o p q) m m' #

Field14 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n' o p q) n n' Source # 
Instance details

Methods

_14 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n' o p q) n n' #

Field15 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o' p q) o o' Source # 
Instance details

Methods

_15 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o' p q) o o' #

Field16 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p' q) p p' Source # 
Instance details

Methods

_16 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p' q) p p' #

Field17 (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p q') q q' Source # 
Instance details

Methods

_17 :: Lens (T17 a b c d e f g h i j kk l m n o p q) (T17 a b c d e f g h i j kk l m n o p q') q q' #

Field1 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a' b c d e f g h i j kk l m n o p q r) a a' Source # 
Instance details

Methods

_1 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a' b c d e f g h i j kk l m n o p q r) a a' #

Field2 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b' c d e f g h i j kk l m n o p q r) b b' Source # 
Instance details

Methods

_2 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b' c d e f g h i j kk l m n o p q r) b b' #

Field3 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c' d e f g h i j kk l m n o p q r) c c' Source # 
Instance details

Methods

_3 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c' d e f g h i j kk l m n o p q r) c c' #

Field4 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d' e f g h i j kk l m n o p q r) d d' Source # 
Instance details

Methods

_4 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d' e f g h i j kk l m n o p q r) d d' #

Field5 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e' f g h i j kk l m n o p q r) e e' Source # 
Instance details

Methods

_5 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e' f g h i j kk l m n o p q r) e e' #

Field6 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f' g h i j kk l m n o p q r) f f' Source # 
Instance details

Methods

_6 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f' g h i j kk l m n o p q r) f f' #

Field7 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g' h i j kk l m n o p q r) g g' Source # 
Instance details

Methods

_7 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g' h i j kk l m n o p q r) g g' #

Field8 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h' i j kk l m n o p q r) h h' Source # 
Instance details

Methods

_8 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h' i j kk l m n o p q r) h h' #

Field9 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i' j kk l m n o p q r) i i' Source # 
Instance details

Methods

_9 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i' j kk l m n o p q r) i i' #

Field10 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j' kk l m n o p q r) j j' Source # 
Instance details

Methods

_10 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j' kk l m n o p q r) j j' #

Field11 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk' l m n o p q r) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk' l m n o p q r) kk kk' #

Field12 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l' m n o p q r) l l' Source # 
Instance details

Methods

_12 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l' m n o p q r) l l' #

Field13 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m' n o p q r) m m' Source # 
Instance details

Methods

_13 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m' n o p q r) m m' #

Field14 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n' o p q r) n n' Source # 
Instance details

Methods

_14 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n' o p q r) n n' #

Field15 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o' p q r) o o' Source # 
Instance details

Methods

_15 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o' p q r) o o' #

Field16 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p' q r) p p' Source # 
Instance details

Methods

_16 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p' q r) p p' #

Field17 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q' r) q q' Source # 
Instance details

Methods

_17 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q' r) q q' #

Field18 (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q r') r r' Source # 
Instance details

Methods

_18 :: Lens (T18 a b c d e f g h i j kk l m n o p q r) (T18 a b c d e f g h i j kk l m n o p q r') r r' #

Field1 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a' b c d e f g h i j kk l m n o p q r s) a a' Source # 
Instance details

Methods

_1 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a' b c d e f g h i j kk l m n o p q r s) a a' #

Field2 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b' c d e f g h i j kk l m n o p q r s) b b' Source # 
Instance details

Methods

_2 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b' c d e f g h i j kk l m n o p q r s) b b' #

Field3 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c' d e f g h i j kk l m n o p q r s) c c' Source # 
Instance details

Methods

_3 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c' d e f g h i j kk l m n o p q r s) c c' #

Field4 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d' e f g h i j kk l m n o p q r s) d d' Source # 
Instance details

Methods

_4 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d' e f g h i j kk l m n o p q r s) d d' #

Field5 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e' f g h i j kk l m n o p q r s) e e' Source # 
Instance details

Methods

_5 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e' f g h i j kk l m n o p q r s) e e' #

Field6 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f' g h i j kk l m n o p q r s) f f' Source # 
Instance details

Methods

_6 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f' g h i j kk l m n o p q r s) f f' #

Field7 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g' h i j kk l m n o p q r s) g g' Source # 
Instance details

Methods

_7 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g' h i j kk l m n o p q r s) g g' #

Field8 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h' i j kk l m n o p q r s) h h' Source # 
Instance details

Methods

_8 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h' i j kk l m n o p q r s) h h' #

Field9 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i' j kk l m n o p q r s) i i' Source # 
Instance details

Methods

_9 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i' j kk l m n o p q r s) i i' #

Field10 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j' kk l m n o p q r s) j j' Source # 
Instance details

Methods

_10 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j' kk l m n o p q r s) j j' #

Field11 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk' l m n o p q r s) kk kk' Source # 
Instance details

Methods

_11 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk' l m n o p q r s) kk kk' #

Field12 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l' m n o p q r s) l l' Source # 
Instance details

Methods

_12 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l' m n o p q r s) l l' #

Field13 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m' n o p q r s) m m' Source # 
Instance details

Methods

_13 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m' n o p q r s) m m' #

Field14 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n' o p q r s) n n' Source # 
Instance details

Methods

_14 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n' o p q r s) n n' #

Field15 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o' p q r s) o o' Source # 
Instance details

Methods

_15 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o' p q r s) o o' #

Field16 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p' q r s) p p' Source # 
Instance details

Methods

_16 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p' q r s) p p' #

Field17 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q' r s) q q' Source # 
Instance details

Methods

_17 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q' r s) q q' #

Field18 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r' s) r r' Source # 
Instance details

Methods

_18 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r' s) r r' #

Field19 (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r s') s s' Source # 
Instance details

Methods

_19 :: Lens (T19 a b c d e f g h i j kk l m n o p q r s) (T19 a b c d e f g h i j kk l m n o p q r s') s s' #