#ifdef TRUSTWORTHY
#endif
module Control.Lens.Tuple
(
Field1(..)
, Field2(..)
, Field3(..)
, Field4(..)
, Field5(..)
, Field6(..)
, Field7(..)
, Field8(..)
, Field9(..)
) where
import Control.Applicative
import Control.Lens.Combinators
import Control.Lens.Indexed
import Control.Lens.Type
import Data.Functor.Identity
class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_1 :: IndexedLens Int s t a b
instance Field1 (Identity a) (Identity b) a b where
_1 f (Identity a) = Identity <$> indexed f (0 :: Int) a
instance Field1 (a,b) (a',b) a a' where
_1 k ~(a,b) = indexed k (0 :: Int) a <&> \a' -> (a',b)
instance Field1 (a,b,c) (a',b,c) a a' where
_1 k ~(a,b,c) = indexed k (0 :: Int) a <&> \a' -> (a',b,c)
instance Field1 (a,b,c,d) (a',b,c,d) a a' where
_1 k ~(a,b,c,d) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d)
instance Field1 (a,b,c,d,e) (a',b,c,d,e) a a' where
_1 k ~(a,b,c,d,e) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d,e)
instance Field1 (a,b,c,d,e,f) (a',b,c,d,e,f) a a' where
_1 k ~(a,b,c,d,e,f) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d,e,f)
instance Field1 (a,b,c,d,e,f,g) (a',b,c,d,e,f,g) a a' where
_1 k ~(a,b,c,d,e,f,g) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d,e,f,g)
instance Field1 (a,b,c,d,e,f,g,h) (a',b,c,d,e,f,g,h) a a' where
_1 k ~(a,b,c,d,e,f,g,h) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d,e,f,g,h)
instance Field1 (a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a' where
_1 k ~(a,b,c,d,e,f,g,h,i) = indexed k (0 :: Int) a <&> \a' -> (a',b,c,d,e,f,g,h,i)
class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_2 :: IndexedLens Int s t a b
instance Field2 (a,b) (a,b') b b' where
_2 k ~(a,b) = indexed k (1 :: Int) b <&> \b' -> (a,b')
instance Field2 (a,b,c) (a,b',c) b b' where
_2 k ~(a,b,c) = indexed k (1 :: Int) b <&> \b' -> (a,b',c)
instance Field2 (a,b,c,d) (a,b',c,d) b b' where
_2 k ~(a,b,c,d) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d)
instance Field2 (a,b,c,d,e) (a,b',c,d,e) b b' where
_2 k ~(a,b,c,d,e) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d,e)
instance Field2 (a,b,c,d,e,f) (a,b',c,d,e,f) b b' where
_2 k ~(a,b,c,d,e,f) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d,e,f)
instance Field2 (a,b,c,d,e,f,g) (a,b',c,d,e,f,g) b b' where
_2 k ~(a,b,c,d,e,f,g) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d,e,f,g)
instance Field2 (a,b,c,d,e,f,g,h) (a,b',c,d,e,f,g,h) b b' where
_2 k ~(a,b,c,d,e,f,g,h) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d,e,f,g,h)
instance Field2 (a,b,c,d,e,f,g,h,i) (a,b',c,d,e,f,g,h,i) b b' where
_2 k ~(a,b,c,d,e,f,g,h,i) = indexed k (1 :: Int) b <&> \b' -> (a,b',c,d,e,f,g,h,i)
class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_3 :: IndexedLens Int s t a b
instance Field3 (a,b,c) (a,b,c') c c' where
_3 k ~(a,b,c) = indexed k (2 :: Int) c <&> \c' -> (a,b,c')
instance Field3 (a,b,c,d) (a,b,c',d) c c' where
_3 k ~(a,b,c,d) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d)
instance Field3 (a,b,c,d,e) (a,b,c',d,e) c c' where
_3 k ~(a,b,c,d,e) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d,e)
instance Field3 (a,b,c,d,e,f) (a,b,c',d,e,f) c c' where
_3 k ~(a,b,c,d,e,f) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d,e,f)
instance Field3 (a,b,c,d,e,f,g) (a,b,c',d,e,f,g) c c' where
_3 k ~(a,b,c,d,e,f,g) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d,e,f,g)
instance Field3 (a,b,c,d,e,f,g,h) (a,b,c',d,e,f,g,h) c c' where
_3 k ~(a,b,c,d,e,f,g,h) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d,e,f,g,h)
instance Field3 (a,b,c,d,e,f,g,h,i) (a,b,c',d,e,f,g,h,i) c c' where
_3 k ~(a,b,c,d,e,f,g,h,i) = indexed k (2 :: Int) c <&> \c' -> (a,b,c',d,e,f,g,h,i)
class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_4 :: IndexedLens Int s t a b
instance Field4 (a,b,c,d) (a,b,c,d') d d' where
_4 k ~(a,b,c,d) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d')
instance Field4 (a,b,c,d,e) (a,b,c,d',e) d d' where
_4 k ~(a,b,c,d,e) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d',e)
instance Field4 (a,b,c,d,e,f) (a,b,c,d',e,f) d d' where
_4 k ~(a,b,c,d,e,f) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d',e,f)
instance Field4 (a,b,c,d,e,f,g) (a,b,c,d',e,f,g) d d' where
_4 k ~(a,b,c,d,e,f,g) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d',e,f,g)
instance Field4 (a,b,c,d,e,f,g,h) (a,b,c,d',e,f,g,h) d d' where
_4 k ~(a,b,c,d,e,f,g,h) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d',e,f,g,h)
instance Field4 (a,b,c,d,e,f,g,h,i) (a,b,c,d',e,f,g,h,i) d d' where
_4 k ~(a,b,c,d,e,f,g,h,i) = indexed k (3 :: Int) d <&> \d' -> (a,b,c,d',e,f,g,h,i)
class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_5 :: IndexedLens Int s t a b
instance Field5 (a,b,c,d,e) (a,b,c,d,e') e e' where
_5 k ~(a,b,c,d,e) = indexed k (4 :: Int) e <&> \e' -> (a,b,c,d,e')
instance Field5 (a,b,c,d,e,f) (a,b,c,d,e',f) e e' where
_5 k ~(a,b,c,d,e,f) = indexed k (4 :: Int) e <&> \e' -> (a,b,c,d,e',f)
instance Field5 (a,b,c,d,e,f,g) (a,b,c,d,e',f,g) e e' where
_5 k ~(a,b,c,d,e,f,g) = indexed k (4 :: Int) e <&> \e' -> (a,b,c,d,e',f,g)
instance Field5 (a,b,c,d,e,f,g,h) (a,b,c,d,e',f,g,h) e e' where
_5 k ~(a,b,c,d,e,f,g,h) = indexed k (4 :: Int) e <&> \e' -> (a,b,c,d,e',f,g,h)
instance Field5 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e',f,g,h,i) e e' where
_5 k ~(a,b,c,d,e,f,g,h,i) = indexed k (4 :: Int) e <&> \e' -> (a,b,c,d,e',f,g,h,i)
class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_6 :: IndexedLens Int s t a b
instance Field6 (a,b,c,d,e,f) (a,b,c,d,e,f') f f' where
_6 k ~(a,b,c,d,e,f) = indexed k (5 :: Int) f <&> \f' -> (a,b,c,d,e,f')
instance Field6 (a,b,c,d,e,f,g) (a,b,c,d,e,f',g) f f' where
_6 k ~(a,b,c,d,e,f,g) = indexed k (5 :: Int) f <&> \f' -> (a,b,c,d,e,f',g)
instance Field6 (a,b,c,d,e,f,g,h) (a,b,c,d,e,f',g,h) f f' where
_6 k ~(a,b,c,d,e,f,g,h) = indexed k (5 :: Int) f <&> \f' -> (a,b,c,d,e,f',g,h)
instance Field6 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e,f',g,h,i) f f' where
_6 k ~(a,b,c,d,e,f,g,h,i) = indexed k (5 :: Int) f <&> \f' -> (a,b,c,d,e,f',g,h,i)
class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_7 :: IndexedLens Int s t a b
instance Field7 (a,b,c,d,e,f,g) (a,b,c,d,e,f,g') g g' where
_7 k ~(a,b,c,d,e,f,g) = indexed k (6 :: Int) g <&> \g' -> (a,b,c,d,e,f,g')
instance Field7 (a,b,c,d,e,f,g,h) (a,b,c,d,e,f,g',h) g g' where
_7 k ~(a,b,c,d,e,f,g,h) = indexed k (6 :: Int) g <&> \g' -> (a,b,c,d,e,f,g',h)
instance Field7 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e,f,g',h,i) g g' where
_7 k ~(a,b,c,d,e,f,g,h,i) = indexed k (6 :: Int) g <&> \g' -> (a,b,c,d,e,f,g',h,i)
class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_8 :: IndexedLens Int s t a b
instance Field8 (a,b,c,d,e,f,g,h) (a,b,c,d,e,f,g,h') h h' where
_8 k ~(a,b,c,d,e,f,g,h) = indexed k (7 :: Int) h <&> \h' -> (a,b,c,d,e,f,g,h')
instance Field8 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e,f,g,h',i) h h' where
_8 k ~(a,b,c,d,e,f,g,h,i) = indexed k (7 :: Int) h <&> \h' -> (a,b,c,d,e,f,g,h',i)
class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where
_9 :: IndexedLens Int s t a b
instance Field9 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e,f,g,h,i') i i' where
_9 k ~(a,b,c,d,e,f,g,h,i) = indexed k (8 :: Int) i <&> \i' -> (a,b,c,d,e,f,g,h,i')