{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}

#if MIN_VERSION_base(4,14,0)
{-# LANGUAGE StandaloneKindSignatures #-}
#endif

-- | Tuple helpers
module Haskus.Utils.Tuple
   ( uncurry3
   , uncurry4
   , uncurry5
   , uncurry6
   , uncurry7
   , take4
   , fromTuple4
   , module Data.Tuple
   , Solo, pattern Solo
   , Tuple
   , Tuple#
   , TypeReps
   , ExtractTuple (..)
   , TupleCon (..)
   , tupleHead
   , TupleTail (..)
   , TupleCons (..)
   , ReorderTuple (..)
   )
where

import GHC.Tuple
import GHC.Exts
import Data.Tuple
import Haskus.Utils.Types

#if !MIN_VERSION_base(4,15,0)
type Solo = Unit
{-# COMPLETE Solo #-}
pattern Solo :: a -> Solo a
pattern $bSolo :: a -> Solo a
$mSolo :: forall r a. Solo a -> (a -> r) -> (Void# -> r) -> r
Solo a = Unit a
#endif

-- | Uncurry3
uncurry3 :: (a -> b -> c -> r) -> (a,b,c) -> r
{-# INLINABLE uncurry3 #-}
uncurry3 :: (a -> b -> c -> r) -> (a, b, c) -> r
uncurry3 a -> b -> c -> r
fn (a
a,b
b,c
c) = a -> b -> c -> r
fn a
a b
b c
c

-- | Uncurry4
uncurry4 :: (a -> b -> c -> d -> r) -> (a,b,c,d) -> r
{-# INLINABLE uncurry4 #-}
uncurry4 :: (a -> b -> c -> d -> r) -> (a, b, c, d) -> r
uncurry4 a -> b -> c -> d -> r
fn (a
a,b
b,c
c,d
d) = a -> b -> c -> d -> r
fn a
a b
b c
c d
d

-- | Uncurry5
uncurry5 :: (a -> b -> c -> d -> e -> r) -> (a,b,c,d,e) -> r
{-# INLINABLE uncurry5 #-}
uncurry5 :: (a -> b -> c -> d -> e -> r) -> (a, b, c, d, e) -> r
uncurry5 a -> b -> c -> d -> e -> r
fn (a
a,b
b,c
c,d
d,e
e) = a -> b -> c -> d -> e -> r
fn a
a b
b c
c d
d e
e

-- | Uncurry6
uncurry6 :: (a -> b -> c -> d -> e -> f -> r) -> (a,b,c,d,e,f) -> r
{-# INLINABLE uncurry6 #-}
uncurry6 :: (a -> b -> c -> d -> e -> f -> r) -> (a, b, c, d, e, f) -> r
uncurry6 a -> b -> c -> d -> e -> f -> r
fn (a
a,b
b,c
c,d
d,e
e,f
f) = a -> b -> c -> d -> e -> f -> r
fn a
a b
b c
c d
d e
e f
f

-- | Uncurry7
uncurry7 :: (a -> b -> c -> d -> e -> f -> g -> r) -> (a,b,c,d,e,f,g) -> r
{-# INLINABLE uncurry7 #-}
uncurry7 :: (a -> b -> c -> d -> e -> f -> g -> r)
-> (a, b, c, d, e, f, g) -> r
uncurry7 a -> b -> c -> d -> e -> f -> g -> r
fn (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = a -> b -> c -> d -> e -> f -> g -> r
fn a
a b
b c
c d
d e
e f
f g
g


-- | Take specialised for quadruple
take4 :: [a] -> (a,a,a,a)
{-# INLINABLE take4 #-}
take4 :: [a] -> (a, a, a, a)
take4 [a
a,a
b,a
c,a
d] = (a
a,a
b,a
c,a
d)
take4 [a]
_         = [Char] -> (a, a, a, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"take4: invalid list (exactly 4 elements required)"


-- | toList for quadruple
fromTuple4 :: (a,a,a,a) -> [a]
{-# INLINABLE fromTuple4 #-}
fromTuple4 :: (a, a, a, a) -> [a]
fromTuple4 (a
a,a
b,a
c,a
d) = [a
a,a
b,a
c,a
d]

-- | Extract a tuple value statically
class ExtractTuple (n :: Nat) xs where
   -- | Extract a tuple value by type-level index
   tupleN :: Tuple xs -> Index n xs

instance ExtractTuple 0 '[a] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[a] -> Index 0 '[a]
tupleN (Solo t) = a
Index 0 '[a]
t

instance ExtractTuple 0 '[e0,e1] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1] -> Index 0 '[e0, e1]
tupleN (t,_) = e0
Index 0 '[e0, e1]
t

instance ExtractTuple 1 '[e0,e1] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1] -> Index 1 '[e0, e1]
tupleN (_,t) = e1
Index 1 '[e0, e1]
t

instance ExtractTuple 0 '[e0,e1,e2] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2] -> Index 0 '[e0, e1, e2]
tupleN (t,_,_) = e0
Index 0 '[e0, e1, e2]
t

instance ExtractTuple 1 '[e0,e1,e2] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2] -> Index 1 '[e0, e1, e2]
tupleN (_,t,_) = e1
Index 1 '[e0, e1, e2]
t

instance ExtractTuple 2 '[e0,e1,e2] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2] -> Index 2 '[e0, e1, e2]
tupleN (_,_,t) = e2
Index 2 '[e0, e1, e2]
t

instance ExtractTuple 0 '[e0,e1,e2,e3] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3] -> Index 0 '[e0, e1, e2, e3]
tupleN (t,_,_,_) = e0
Index 0 '[e0, e1, e2, e3]
t

instance ExtractTuple 1 '[e0,e1,e2,e3] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3] -> Index 1 '[e0, e1, e2, e3]
tupleN (_,t,_,_) = e1
Index 1 '[e0, e1, e2, e3]
t

instance ExtractTuple 2 '[e0,e1,e2,e3] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3] -> Index 2 '[e0, e1, e2, e3]
tupleN (_,_,t,_) = e2
Index 2 '[e0, e1, e2, e3]
t

instance ExtractTuple 3 '[e0,e1,e2,e3] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3] -> Index 3 '[e0, e1, e2, e3]
tupleN (_,_,_,t) = e3
Index 3 '[e0, e1, e2, e3]
t


instance ExtractTuple 0 '[e0,e1,e2,e3,e4] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4] -> Index 0 '[e0, e1, e2, e3, e4]
tupleN (t,_,_,_,_) = e0
Index 0 '[e0, e1, e2, e3, e4]
t

instance ExtractTuple 1 '[e0,e1,e2,e3,e4] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4] -> Index 1 '[e0, e1, e2, e3, e4]
tupleN (_,t,_,_,_) = e1
Index 1 '[e0, e1, e2, e3, e4]
t

instance ExtractTuple 2 '[e0,e1,e2,e3,e4] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4] -> Index 2 '[e0, e1, e2, e3, e4]
tupleN (_,_,t,_,_) = e2
Index 2 '[e0, e1, e2, e3, e4]
t

instance ExtractTuple 3 '[e0,e1,e2,e3,e4] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4] -> Index 3 '[e0, e1, e2, e3, e4]
tupleN (_,_,_,t,_) = e3
Index 3 '[e0, e1, e2, e3, e4]
t

instance ExtractTuple 4 '[e0,e1,e2,e3,e4] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4] -> Index 4 '[e0, e1, e2, e3, e4]
tupleN (_,_,_,_,t) = e4
Index 4 '[e0, e1, e2, e3, e4]
t


instance ExtractTuple 0 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 0 '[e0, e1, e2, e3, e4, e5]
tupleN (t,_,_,_,_,_) = e0
Index 0 '[e0, e1, e2, e3, e4, e5]
t

instance ExtractTuple 1 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 1 '[e0, e1, e2, e3, e4, e5]
tupleN (_,t,_,_,_,_) = e1
Index 1 '[e0, e1, e2, e3, e4, e5]
t

instance ExtractTuple 2 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 2 '[e0, e1, e2, e3, e4, e5]
tupleN (_,_,t,_,_,_) = e2
Index 2 '[e0, e1, e2, e3, e4, e5]
t

instance ExtractTuple 3 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 3 '[e0, e1, e2, e3, e4, e5]
tupleN (_,_,_,t,_,_) = e3
Index 3 '[e0, e1, e2, e3, e4, e5]
t

instance ExtractTuple 4 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 4 '[e0, e1, e2, e3, e4, e5]
tupleN (_,_,_,_,t,_) = e4
Index 4 '[e0, e1, e2, e3, e4, e5]
t

instance ExtractTuple 5 '[e0,e1,e2,e3,e4,e5] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5]
-> Index 5 '[e0, e1, e2, e3, e4, e5]
tupleN (_,_,_,_,_,t) = e5
Index 5 '[e0, e1, e2, e3, e4, e5]
t


instance ExtractTuple 0 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 0 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (t,_,_,_,_,_,_) = e0
Index 0 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 1 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 1 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,t,_,_,_,_,_) = e1
Index 1 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 2 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 2 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,_,t,_,_,_,_) = e2
Index 2 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 3 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 3 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,_,_,t,_,_,_) = e3
Index 3 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 4 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 4 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,_,_,_,t,_,_) = e4
Index 4 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 5 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 5 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,_,_,_,_,t,_) = e5
Index 5 '[e0, e1, e2, e3, e4, e5, e6]
t

instance ExtractTuple 6 '[e0,e1,e2,e3,e4,e5,e6] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6]
-> Index 6 '[e0, e1, e2, e3, e4, e5, e6]
tupleN (_,_,_,_,_,_,t) = e6
Index 6 '[e0, e1, e2, e3, e4, e5, e6]
t


instance ExtractTuple 0 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 0 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (t,_,_,_,_,_,_,_) = e0
Index 0 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 1 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 1 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,t,_,_,_,_,_,_) = e1
Index 1 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 2 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 2 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,t,_,_,_,_,_) = e2
Index 2 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 3 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 3 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,_,t,_,_,_,_) = e3
Index 3 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 4 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 4 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,_,_,t,_,_,_) = e4
Index 4 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 5 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 5 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,_,_,_,t,_,_) = e5
Index 5 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 6 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 6 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,_,_,_,_,t,_) = e6
Index 6 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

instance ExtractTuple 7 '[e0,e1,e2,e3,e4,e5,e6,e7] where
   {-# INLINABLE tupleN #-}
   tupleN :: Tuple '[e0, e1, e2, e3, e4, e5, e6, e7]
-> Index 7 '[e0, e1, e2, e3, e4, e5, e6, e7]
tupleN (_,_,_,_,_,_,_,t) = e7
Index 7 '[e0, e1, e2, e3, e4, e5, e6, e7]
t

-- | Get first element of the tuple
tupleHead :: forall xs. ExtractTuple 0 xs => Tuple xs -> Index 0 xs
tupleHead :: Tuple xs -> Index 0 xs
tupleHead = forall (xs :: [*]). ExtractTuple 0 xs => Tuple xs -> Index 0 xs
forall (n :: Nat) (xs :: [*]).
ExtractTuple n xs =>
Tuple xs -> Index n xs
tupleN @0

class TupleTail ts ts' | ts -> ts' where
   tupleTail :: ts -> ts'

instance TupleTail (a,b) (Solo b) where
   {-# INLINABLE tupleTail #-}
   tupleTail :: (a, b) -> Solo b
tupleTail (a
_,b
b) = b -> Solo b
forall a. a -> Solo a
Solo b
b

instance TupleTail (a,b,c) (b,c) where
   {-# INLINABLE tupleTail #-}
   tupleTail :: (a, b, c) -> (b, c)
tupleTail (a
_,b
b,c
c) = (b
b,c
c)

instance TupleTail (a,b,c,d) (b,c,d) where
   {-# INLINABLE tupleTail #-}
   tupleTail :: (a, b, c, d) -> (b, c, d)
tupleTail (a
_,b
b,c
c,d
d) = (b
b,c
c,d
d)

instance TupleTail (a,b,c,d,e) (b,c,d,e) where
   {-# INLINABLE tupleTail #-}
   tupleTail :: (a, b, c, d, e) -> (b, c, d, e)
tupleTail (a
_,b
b,c
c,d
d,e
e) = (b
b,c
c,d
d,e
e)

instance TupleTail (a,b,c,d,e,f) (b,c,d,e,f) where
   {-# INLINABLE tupleTail #-}
   tupleTail :: (a, b, c, d, e, f) -> (b, c, d, e, f)
tupleTail (a
_,b
b,c
c,d
d,e
e,f
f) = (b
b,c
c,d
d,e
e,f
f)



class TupleCons t ts ts' | t ts -> ts' where
   tupleCons :: t -> ts -> ts'

instance TupleCons a (Solo b) (a,b) where
   {-# INLINABLE tupleCons #-}
   tupleCons :: a -> Solo b -> (a, b)
tupleCons a
a (Solo b
b) = (a
a,b
b)

instance TupleCons a (b,c) (a,b,c) where
   {-# INLINABLE tupleCons #-}
   tupleCons :: a -> (b, c) -> (a, b, c)
tupleCons a
a (b
b,c
c) = (a
a,b
b,c
c)

instance TupleCons a (b,c,d) (a,b,c,d) where
   {-# INLINABLE tupleCons #-}
   tupleCons :: a -> (b, c, d) -> (a, b, c, d)
tupleCons a
a (b
b,c
c,d
d) = (a
a,b
b,c
c,d
d)

instance TupleCons a (b,c,d,e) (a,b,c,d,e) where
   {-# INLINABLE tupleCons #-}
   tupleCons :: a -> (b, c, d, e) -> (a, b, c, d, e)
tupleCons a
a (b
b,c
c,d
d,e
e) = (a
a,b
b,c
c,d
d,e
e)

instance TupleCons a (b,c,d,e,f) (a,b,c,d,e,f) where
   {-# INLINABLE tupleCons #-}
   tupleCons :: a -> (b, c, d, e, f) -> (a, b, c, d, e, f)
tupleCons a
a (b
b,c
c,d
d,e
e,f
f) = (a
a,b
b,c
c,d
d,e
e,f
f)


-- | Reorder tuple elements
class ReorderTuple t1 t2 where
   -- | Reorder tuple elements
   tupleReorder :: t1 -> t2


instance ReorderTuple (Solo a) (Solo a) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: Solo a -> Solo a
tupleReorder = Solo a -> Solo a
forall a. a -> a
id

instance ReorderTuple (a,b) (a,b) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b) -> (a, b)
tupleReorder = (a, b) -> (a, b)
forall a. a -> a
id

instance ReorderTuple (a,b,c) (a,b,c) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (a, b, c)
tupleReorder = (a, b, c) -> (a, b, c)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d) (a,b,c,d) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d) -> (a, b, c, d)
tupleReorder = (a, b, c, d) -> (a, b, c, d)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e) (a,b,c,d,e) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (a, b, c, d, e)
tupleReorder = (a, b, c, d, e) -> (a, b, c, d, e)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e,f) (a,b,c,d,e,f) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (a, b, c, d, e, f)
tupleReorder = (a, b, c, d, e, f) -> (a, b, c, d, e, f)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e,f,g) (a,b,c,d,e,f,g) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g)
tupleReorder = (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e,f,g,h) (a,b,c,d,e,f,g,h) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h)
tupleReorder = (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e,f,g,h,i) (a,b,c,d,e,f,g,h,i) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i)
tupleReorder = (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i)
forall a. a -> a
id

instance ReorderTuple (a,b,c,d,e,f,g,h,i,j) (a,b,c,d,e,f,g,h,i,j) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j)
tupleReorder = (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j)
forall a. a -> a
id


instance ReorderTuple (a,b) (b,a) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b) -> (b, a)
tupleReorder (a
a,b
b) = (b
b,a
a)

instance ReorderTuple (a,b,c) (a,c,b) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (a, c, b)
tupleReorder (a
a,b
b,c
c) = (a
a,c
c,b
b)

instance ReorderTuple (a,b,c) (b,a,c) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (b, a, c)
tupleReorder (a
a,b
b,c
c) = (b
b,a
a,c
c)

instance ReorderTuple (a,b,c) (b,c,a) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (b, c, a)
tupleReorder (a
a,b
b,c
c) = (b
b,c
c,a
a)

instance ReorderTuple (a,b,c) (c,a,b) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (c, a, b)
tupleReorder (a
a,b
b,c
c) = (c
c,a
a,b
b)

instance ReorderTuple (a,b,c) (c,b,a) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c) -> (c, b, a)
tupleReorder (a
a,b
b,c
c) = (c
c,b
b,a
a)

instance ReorderTuple (b,c,d) (x,y,z) => ReorderTuple (a,b,c,d) (a,x,y,z) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d) -> (a, x, y, z)
tupleReorder (a
a,b
b,c
c,d
d) = let (x
x,y
y,z
z) = (b, c, d) -> (x, y, z)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (b
b,c
c,d
d) in (a
a,x
x,y
y,z
z)

instance ReorderTuple (a,c,d) (x,y,z) => ReorderTuple (a,b,c,d) (x,b,y,z) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d) -> (x, b, y, z)
tupleReorder (a
a,b
b,c
c,d
d) = let (x
x,y
y,z
z) = (a, c, d) -> (x, y, z)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,c
c,d
d) in (x
x,b
b,y
y,z
z)

instance ReorderTuple (a,b,d) (x,y,z) => ReorderTuple (a,b,c,d) (x,y,c,z) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d) -> (x, y, c, z)
tupleReorder (a
a,b
b,c
c,d
d) = let (x
x,y
y,z
z) = (a, b, d) -> (x, y, z)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,d
d) in (x
x,y
y,c
c,z
z)

instance ReorderTuple (a,b,c) (x,y,z) => ReorderTuple (a,b,c,d) (x,y,z,d) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d) -> (x, y, z, d)
tupleReorder (a
a,b
b,c
c,d
d) = let (x
x,y
y,z
z) = (a, b, c) -> (x, y, z)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c) in (x
x,y
y,z
z,d
d)

instance ReorderTuple (b,c,d,e) (x,y,z,w) => ReorderTuple (a,b,c,d,e) (a,x,y,z,w) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (a, x, y, z, w)
tupleReorder (a
a,b
b,c
c,d
d,e
e) = let (x
x,y
y,z
z,w
w) = (b, c, d, e) -> (x, y, z, w)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (b
b,c
c,d
d,e
e) in (a
a,x
x,y
y,z
z,w
w)

instance ReorderTuple (a,c,d,e) (x,y,z,w) => ReorderTuple (a,b,c,d,e) (x,b,y,z,w) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (x, b, y, z, w)
tupleReorder (a
a,b
b,c
c,d
d,e
e) = let (x
x,y
y,z
z,w
w) = (a, c, d, e) -> (x, y, z, w)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,c
c,d
d,e
e) in (x
x,b
b,y
y,z
z,w
w)

instance ReorderTuple (a,b,d,e) (x,y,z,w) => ReorderTuple (a,b,c,d,e) (x,y,c,z,w) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (x, y, c, z, w)
tupleReorder (a
a,b
b,c
c,d
d,e
e) = let (x
x,y
y,z
z,w
w) = (a, b, d, e) -> (x, y, z, w)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,d
d,e
e) in (x
x,y
y,c
c,z
z,w
w)

instance ReorderTuple (a,b,c,e) (x,y,z,w) => ReorderTuple (a,b,c,d,e) (x,y,z,d,w) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (x, y, z, d, w)
tupleReorder (a
a,b
b,c
c,d
d,e
e) = let (x
x,y
y,z
z,w
w) = (a, b, c, e) -> (x, y, z, w)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,e
e) in (x
x,y
y,z
z,d
d,w
w)

instance ReorderTuple (a,b,c,d) (x,y,z,w) => ReorderTuple (a,b,c,d,e) (x,y,z,w,e) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e) -> (x, y, z, w, e)
tupleReorder (a
a,b
b,c
c,d
d,e
e) = let (x
x,y
y,z
z,w
w) = (a, b, c, d) -> (x, y, z, w)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d) in (x
x,y
y,z
z,w
w,e
e)

instance ReorderTuple (b,c,d,e,f) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (a,x,y,z,w,v) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (a, x, y, z, w, v)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (b, c, d, e, f) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (b
b,c
c,d
d,e
e,f
f) in (a
a,x
x,y
y,z
z,w
w,v
v)

instance ReorderTuple (a,c,d,e,f) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (x,b,y,z,w,v) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (x, b, y, z, w, v)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (a, c, d, e, f) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,c
c,d
d,e
e,f
f) in (x
x,b
b,y
y,z
z,w
w,v
v)

instance ReorderTuple (a,b,d,e,f) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (x,y,c,z,w,v) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (x, y, c, z, w, v)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (a, b, d, e, f) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,d
d,e
e,f
f) in (x
x,y
y,c
c,z
z,w
w,v
v)

instance ReorderTuple (a,b,c,e,f) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (x,y,z,d,w,v) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, d, w, v)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (a, b, c, e, f) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,e
e,f
f) in (x
x,y
y,z
z,d
d,w
w,v
v)

instance ReorderTuple (a,b,c,d,f) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (x,y,z,w,e,v) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, w, e, v)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (a, b, c, d, f) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d,f
f) in (x
x,y
y,z
z,w
w,e
e,v
v)

instance ReorderTuple (a,b,c,d,e) (x,y,z,w,v) => ReorderTuple (a,b,c,d,e,f) (x,y,z,w,v,f) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, w, v, f)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) = let (x
x,y
y,z
z,w
w,v
v) = (a, b, c, d, e) -> (x, y, z, w, v)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d,e
e) in (x
x,y
y,z
z,w
w,v
v,f
f)


instance ReorderTuple (b,c,d,e,f,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (a,x,y,z,w,v,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (a, x, y, z, w, v, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (b, c, d, e, f, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (b
b,c
c,d
d,e
e,f
f,g
g) in (a
a,x
x,y
y,z
z,w
w,v
v,u
u)

instance ReorderTuple (a,c,d,e,f,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,b,y,z,w,v,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, b, y, z, w, v, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, c, d, e, f, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,c
c,d
d,e
e,f
f,g
g) in (x
x,b
b,y
y,z
z,w
w,v
v,u
u)

instance ReorderTuple (a,b,d,e,f,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,y,c,z,w,v,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, c, z, w, v, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, b, d, e, f, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,d
d,e
e,f
f,g
g) in (x
x,y
y,c
c,z
z,w
w,v
v,u
u)

instance ReorderTuple (a,b,c,e,f,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,y,z,d,w,v,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, d, w, v, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, b, c, e, f, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,e
e,f
f,g
g) in (x
x,y
y,z
z,d
d,w
w,v
v,u
u)

instance ReorderTuple (a,b,c,d,f,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,y,z,w,e,v,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, e, v, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, b, c, d, f, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d,f
f,g
g) in (x
x,y
y,z
z,w
w,e
e,v
v,u
u)

instance ReorderTuple (a,b,c,d,e,g) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,y,z,w,v,f,u) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, v, f, u)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, b, c, d, e, g) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d,e
e,g
g) in (x
x,y
y,z
z,w
w,v
v,f
f,u
u)

instance ReorderTuple (a,b,c,d,e,f) (x,y,z,w,v,u) => ReorderTuple (a,b,c,d,e,f,g) (x,y,z,w,v,u,g) where
   {-# INLINABLE tupleReorder #-}
   tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, v, u, g)
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = let (x
x,y
y,z
z,w
w,v
v,u
u) = (a, b, c, d, e, f) -> (x, y, z, w, v, u)
forall t1 t2. ReorderTuple t1 t2 => t1 -> t2
tupleReorder (a
a,b
b,c
c,d
d,e
e,f
f) in (x
x,y
y,z
z,w
w,v
v,u
u,g
g)

type family TupleFun r xs where
   TupleFun r '[]      = r
   TupleFun r (x:xs)   = x -> (TupleFun r xs)

-- | Create a Tuple
class TupleCon xs where
   -- | Create a Tuple
   tupleCon :: TupleFun (Tuple xs) xs

instance TupleCon '[] where
   tupleCon :: TupleFun (Tuple '[]) '[]
tupleCon = ()

instance TupleCon '[a] where
   tupleCon :: TupleFun (Tuple '[a]) '[a]
tupleCon = TupleFun (Tuple '[a]) '[a]
forall a. a -> Solo a
Solo

instance TupleCon '[a,b] where
   tupleCon :: TupleFun (Tuple '[a, b]) '[a, b]
tupleCon = (,)

instance TupleCon '[a,b,c] where
   tupleCon :: TupleFun (Tuple '[a, b, c]) '[a, b, c]
tupleCon = (,,)

instance TupleCon '[a,b,c,d] where
   tupleCon :: TupleFun (Tuple '[a, b, c, d]) '[a, b, c, d]
tupleCon = (,,,)

instance TupleCon '[a,b,c,d,e] where
   tupleCon :: TupleFun (Tuple '[a, b, c, d, e]) '[a, b, c, d, e]
tupleCon = (,,,,)

instance TupleCon '[a,b,c,d,e,f] where
   tupleCon :: TupleFun (Tuple '[a, b, c, d, e, f]) '[a, b, c, d, e, f]
tupleCon = (,,,,,)

-- | Boxed tuple
--
-- TODO: put this family into GHC
type family Tuple xs = t | t -> xs where
   Tuple '[]                                                    = ()
   Tuple '[a]                                                   = Solo a
   Tuple '[a,b]                                                 = (a,b)
   Tuple '[a,b,c]                                               = (a,b,c)
   Tuple '[a,b,c,d]                                             = (a,b,c,d)
   Tuple '[a,b,c,d,e]                                           = (a,b,c,d,e)
   Tuple '[a,b,c,d,e,f]                                         = (a,b,c,d,e,f)
   Tuple '[a,b,c,d,e,f,g]                                       = (a,b,c,d,e,f,g)
   Tuple '[a,b,c,d,e,f,g,h]                                     = (a,b,c,d,e,f,g,h)
   Tuple '[a,b,c,d,e,f,g,h,i]                                   = (a,b,c,d,e,f,g,h,i)
   Tuple '[a,b,c,d,e,f,g,h,i,j]                                 = (a,b,c,d,e,f,g,h,i,j)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k]                               = (a,b,c,d,e,f,g,h,i,j,k)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l]                             = (a,b,c,d,e,f,g,h,i,j,k,l)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m]                           = (a,b,c,d,e,f,g,h,i,j,k,l,m)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n]                         = (a,b,c,d,e,f,g,h,i,j,k,l,m,n)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o]                       = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p]                     = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q]                   = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r]                 = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s]               = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t]             = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u]           = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v]         = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w]       = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x]     = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y]   = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y)
   Tuple '[a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z] = (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z)


type family TypeReps xs where
   TypeReps '[]                 = '[]
   TypeReps ((a::TYPE k) ': as) = k ': TypeReps as

-- | Unboxed tuple
--
-- TODO: put this family into GHC
#if MIN_VERSION_base(4,14,0)
type Tuple# :: forall xs -> TYPE ('TupleRep (TypeReps xs))
type family Tuple# xs = t | t -> xs where
#else
type family Tuple# xs = (t :: TYPE ('TupleRep (TypeReps xs))) | t -> xs where
#endif
   Tuple# '[]                  = (##)
   Tuple# '[a]                 = (# a #)
   Tuple# '[a,b]               = (# a,b #)
   Tuple# '[a,b,c]             = (# a,b,c #)
   Tuple# '[a,b,c,d]           = (# a,b,c,d #)
   Tuple# '[a,b,c,d,e]         = (# a,b,c,d,e #)
   Tuple# '[a,b,c,d,e,f]       = (# a,b,c,d,e,f #)
   Tuple# '[a,b,c,d,e,f,g]     = (# a,b,c,d,e,f,g #)
   Tuple# '[a,b,c,d,e,f,g,h]   = (# a,b,c,d,e,f,g,h #)
   Tuple# '[a,b,c,d,e,f,g,h,i] = (# a,b,c,d,e,f,g,h,i #)