module Data.Has (Has(..)) where
import Data.Functor
import Data.Functor.Identity
#if MIN_VERSION_base(4,9,0)
import Data.Functor.Const
#else
import Data.Functor.Const.Compat
#endif
type Lens t a = forall f. Functor f => (a -> f a) -> t -> f t
class Has a t where
    
    getter :: t -> a
    getter = getConst . hasLens Const
    modifier :: (a -> a) -> t -> t
    modifier f t = runIdentity (hasLens (Identity . f) t)
    hasLens :: Lens t a
    hasLens afa t = (\a -> modifier (const a) t) <$> afa (getter t)
instance Has a a where
    getter = id
    
    modifier = id
    
instance Has a (a, b) where
    getter (a, _) = a
    
    modifier f (a, b) = (f a, b)
    
instance Has b (a, b) where
    getter (_, b) = b
    
    modifier f (a, b) = (a, f b)
    
instance Has a (a, b, c) where
    getter (a, _, _) = a
    
    modifier f (a, b, c) = (f a, b, c)
    
instance Has b (a, b, c) where
    getter (_, b, _) = b
    
    modifier f (a, b, c) = (a, f b, c)
    
instance Has c (a, b, c) where
    getter (_, _, c) = c
    
    modifier f (a, b, c) = (a, b, f c)
    
instance Has a (a, b, c, d) where
    getter (a, _, _, _) = a
    
    modifier f (a, b, c, d) = (f a, b, c, d)
    
instance Has b (a, b, c, d) where
    getter (_, b, _, _) = b
    
    modifier f (a, b, c, d) = (a, f b, c, d)
    
instance Has c (a, b, c, d) where
    getter (_, _, c, _) = c
    
    modifier f (a, b, c, d) = (a, b, f c, d)
    
instance Has d (a, b, c, d) where
    getter (_, _, _, d) = d
    
    modifier f (a, b, c, d) = (a, b, c, f d)
    
instance Has a (a, b, c, d, e) where
    getter (a, _, _, _, _) = a
    
    modifier f (a, b, c, d, e) = (f a, b, c, d, e)
    
instance Has b (a, b, c, d, e) where
    getter (_, b, _, _, _) = b
    
    modifier f (a, b, c, d, e) = (a, f b, c, d, e)
    
instance Has c (a, b, c, d, e) where
    getter (_, _, c, _, _) = c
    
    modifier f (a, b, c, d, e) = (a, b, f c, d, e)
    
instance Has d (a, b, c, d, e) where
    getter (_, _, _, d, _) = d
    
    modifier f (a, b, c, d, e) = (a, b, c, f d, e)
    
instance Has e (a, b, c, d, e) where
    getter (_, _, _, _, e) = e
    
    modifier f (a, b, c, d, e) = (a, b, c, d, f e)
    
instance Has a (a, b, c, d, e, f) where
    getter (a, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f) = (ff a, b, c, d, e, f)
    
instance Has b (a, b, c, d, e, f) where
    getter (_, b, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f) = (a, ff b, c, d, e, f)
    
instance Has c (a, b, c, d, e, f) where
    getter (_, _, c, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f) = (a, b, ff c, d, e, f)
    
instance Has d (a, b, c, d, e, f) where
    getter (_, _, _, d, _, _) = d
    
    modifier ff (a, b, c, d, e, f) = (a, b, c, ff d, e, f)
    
instance Has e (a, b, c, d, e, f) where
    getter (_, _, _, _, e, _) = e
    
    modifier ff (a, b, c, d, e, f) = (a, b, c, d, ff e, f)
    
instance Has f (a, b, c, d, e, f) where
    getter (_, _, _, _, _, f) = f
    
    modifier ff (a, b, c, d, e, f) = (a, b, c, d, e, ff f)
    
instance Has a (a, b, c, d, e, f, g) where
    getter (a, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g) = (ff a, b, c, d, e, f, g)
    
instance Has b (a, b, c, d, e, f, g) where
    getter (_, b, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g) = (a, ff b, c, d, e, f, g)
    
instance Has c (a, b, c, d, e, f, g) where
    getter (_, _, c, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g) = (a, b, ff c, d, e, f, g)
    
instance Has d (a, b, c, d, e, f, g) where
    getter (_, _, _, d, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g) = (a, b, c, ff d, e, f, g)
    
instance Has e (a, b, c, d, e, f, g) where
    getter (_, _, _, _, e, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g) = (a, b, c, d, ff e, f, g)
    
instance Has f (a, b, c, d, e, f, g) where
    getter (_, _, _, _, _, f, _) = f
    
    modifier ff (a, b, c, d, e, f, g) = (a, b, c, d, e, ff f, g)
    
instance Has g (a, b, c, d, e, f, g) where
    getter (_, _, _, _, _, _, g) = g
    
    modifier ff (a, b, c, d, e, f, g) = (a, b, c, d, e, f, ff g)
    
instance Has a (a, b, c, d, e, f, g, h) where
    getter (a, _, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g, h) = (ff a, b, c, d, e, f, g, h)
    
instance Has b (a, b, c, d, e, f, g, h) where
    getter (_, b, _, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, ff b, c, d, e, f, g, h)
    
instance Has c (a, b, c, d, e, f, g, h) where
    getter (_, _, c, _, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, ff c, d, e, f, g, h)
    
instance Has d (a, b, c, d, e, f, g, h) where
    getter (_, _, _, d, _, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, c, ff d, e, f, g, h)
    
instance Has e (a, b, c, d, e, f, g, h) where
    getter (_, _, _, _, e, _, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, c, d, ff e, f, g, h)
    
instance Has f (a, b, c, d, e, f, g, h) where
    getter (_, _, _, _, _, f, _, _) = f
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, c, d, e, ff f, g, h)
    
instance Has g (a, b, c, d, e, f, g, h) where
    getter (_, _, _, _, _, _, g, _) = g
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, c, d, e, f, ff g, h)
    
instance Has h (a, b, c, d, e, f, g, h) where
    getter (_, _, _, _, _, _, _, h) = h
    
    modifier ff (a, b, c, d, e, f, g, h) = (a, b, c, d, e, f, g, ff h)
    
instance Has a (a, b, c, d, e, f, g, h, i) where
    getter (a, _, _, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (ff a, b, c, d, e, f, g, h, i)
    
instance Has b (a, b, c, d, e, f, g, h, i) where
    getter (_, b, _, _, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, ff b, c, d, e, f, g, h, i)
    
instance Has c (a, b, c, d, e, f, g, h, i) where
    getter (_, _, c, _, _, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, ff c, d, e, f, g, h, i)
    
instance Has d (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, d, _, _, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, ff d, e, f, g, h, i)
    
instance Has e (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, _, e, _, _, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, d, ff e, f, g, h, i)
    
instance Has f (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, _, _, f, _, _, _) = f
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, d, e, ff f, g, h, i)
    
instance Has g (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, _, _, _, g, _, _) = g
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, d, e, f, ff g, h, i)
    
instance Has h (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, _, _, _, _, h, _) = h
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, d, e, f, g, ff h, i)
    
instance Has i (a, b, c, d, e, f, g, h, i) where
    getter (_, _, _, _, _, _, _, _, i) = i
    
    modifier ff (a, b, c, d, e, f, g, h, i) = (a, b, c, d, e, f, g, h, ff i)
    
instance Has a (a, b, c, d, e, f, g, h, i, j) where
    getter (a, _, _, _, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (ff a, b, c, d, e, f, g, h, i, j)
    
instance Has b (a, b, c, d, e, f, g, h, i, j) where
    getter (_, b, _, _, _, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, ff b, c, d, e, f, g, h, i, j)
    
instance Has c (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, c, _, _, _, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, ff c, d, e, f, g, h, i, j)
    
instance Has d (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, d, _, _, _, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, ff d, e, f, g, h, i, j)
    
instance Has e (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, e, _, _, _, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, ff e, f, g, h, i, j)
    
instance Has f (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, _, f, _, _, _, _) = f
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, e, ff f, g, h, i, j)
    
instance Has g (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, _, _, g, _, _, _) = g
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, e, f, ff g, h, i, j)
    
instance Has h (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, _, _, _, h, _, _) = h
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, e, f, g, ff h, i, j)
    
instance Has i (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, _, _, _, _, i, _) = i
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, e, f, g, h, ff i, j)
    
instance Has j (a, b, c, d, e, f, g, h, i, j) where
    getter (_, _, _, _, _, _, _, _, _, j) = j
    
    modifier ff (a, b, c, d, e, f, g, h, i, j) = (a, b, c, d, e, f, g, h, i, ff j)
    
instance Has a (a, b, c, d, e, f, g, h, i, j, k) where
    getter (a, _, _, _, _, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (ff a, b, c, d, e, f, g, h, i, j, k)
    
instance Has b (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, b, _, _, _, _, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, ff b, c, d, e, f, g, h, i, j, k)
    
instance Has c (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, c, _, _, _, _, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, ff c, d, e, f, g, h, i, j, k)
    
instance Has d (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, d, _, _, _, _, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, ff d, e, f, g, h, i, j, k)
    
instance Has e (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, e, _, _, _, _, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, ff e, f, g, h, i, j, k)
    
instance Has f (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, f, _, _, _, _, _) = f
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, ff f, g, h, i, j, k)
    
instance Has g (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, _, g, _, _, _, _) = g
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, f, ff g, h, i, j, k)
    
instance Has h (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, _, _, h, _, _, _) = h
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, f, g, ff h, i, j, k)
    
instance Has i (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, _, _, _, i, _, _) = i
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, f, g, h, ff i, j, k)
    
instance Has j (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, _, _, _, _, j, _) = j
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, f, g, h, i, ff j, k)
    
instance Has k (a, b, c, d, e, f, g, h, i, j, k) where
    getter (_, _, _, _, _, _, _, _, _, _, k) = k
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k) = (a, b, c, d, e, f, g, h, i, j, ff k)
    
instance Has a (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (a, _, _, _, _, _, _, _, _, _, _, _) = a
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (ff a, b, c, d, e, f, g, h, i, j, k, l)
    
instance Has b (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, b, _, _, _, _, _, _, _, _, _, _) = b
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, ff b, c, d, e, f, g, h, i, j, k, l)
    
instance Has c (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, c, _, _, _, _, _, _, _, _, _) = c
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, ff c, d, e, f, g, h, i, j, k, l)
    
instance Has d (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, d, _, _, _, _, _, _, _, _) = d
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, ff d, e, f, g, h, i, j, k, l)
    
instance Has e (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, e, _, _, _, _, _, _, _) = e
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, ff e, f, g, h, i, j, k, l)
    
instance Has f (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, f, _, _, _, _, _, _) = f
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, ff f, g, h, i, j, k, l)
    
instance Has g (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, g, _, _, _, _, _) = g
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, ff g, h, i, j, k, l)
    
instance Has h (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, _, h, _, _, _, _) = h
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, g, ff h, i, j, k, l)
    
instance Has i (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, _, _, i, _, _, _) = i
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, g, h, ff i, j, k, l)
    
instance Has j (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, _, _, _, j, _, _) = j
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, g, h, i, ff j, k, l)
    
instance Has k (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, _, _, _, _, k, _) = k
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, g, h, i, j, ff k, l)
    
instance Has l (a, b, c, d, e, f, g, h, i, j, k, l) where
    getter (_, _, _, _, _, _, _, _, _, _, _, l) = l
    
    modifier ff (a, b, c, d, e, f, g, h, i, j, k, l) = (a, b, c, d, e, f, g, h, i, j, k, ff l)