{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
module Quipper.Utils.Tuple where
class TupleOrUnary t s | s -> t where
weak_tuple :: s -> t
weak_untuple :: t -> s
instance TupleOrUnary () () where
weak_tuple () = ()
weak_untuple () = ()
instance TupleOrUnary a (a,()) where
weak_tuple (a,()) = a
weak_untuple a = (a,())
instance TupleOrUnary (a,b) (a,(b,())) where
weak_tuple (a,(b,())) = (a,b)
weak_untuple (a,b) = (a,(b,()))
instance TupleOrUnary (a,b,c) (a,(b,(c,()))) where
weak_tuple (a,(b,(c,()))) = (a,b,c)
weak_untuple (a,b,c) = (a,(b,(c,())))
instance TupleOrUnary (a,b,c,d) (a,(b,(c,(d,())))) where
weak_tuple (a,(b,(c,(d,())))) = (a,b,c,d)
weak_untuple (a,b,c,d) = (a,(b,(c,(d,()))))
instance TupleOrUnary (a,b,c,d,e) (a,(b,(c,(d,(e,()))))) where
weak_tuple (a,(b,(c,(d,(e,()))))) = (a,b,c,d,e)
weak_untuple (a,b,c,d,e) = (a,(b,(c,(d,(e,())))))
instance TupleOrUnary (a,b,c,d,e,f) (a,(b,(c,(d,(e,(f,())))))) where
weak_tuple (a,(b,(c,(d,(e,(f,())))))) = (a,b,c,d,e,f)
weak_untuple (a,b,c,d,e,f) = (a,(b,(c,(d,(e,(f,()))))))
instance TupleOrUnary (a,b,c,d,e,f,g) (a,(b,(c,(d,(e,(f,(g,()))))))) where
weak_tuple (a,(b,(c,(d,(e,(f,(g,()))))))) = (a,b,c,d,e,f,g)
weak_untuple (a,b,c,d,e,f,g) = (a,(b,(c,(d,(e,(f,(g,())))))))
instance TupleOrUnary (a,b,c,d,e,f,g,h) (a,(b,(c,(d,(e,(f,(g,(h,())))))))) where
weak_tuple (a,(b,(c,(d,(e,(f,(g,(h,())))))))) = (a,b,c,d,e,f,g,h)
weak_untuple (a,b,c,d,e,f,g,h) = (a,(b,(c,(d,(e,(f,(g,(h,()))))))))
instance TupleOrUnary (a,b,c,d,e,f,g,h,i) (a,(b,(c,(d,(e,(f,(g,(h,(i,()))))))))) where
weak_tuple (a,(b,(c,(d,(e,(f,(g,(h,(i,()))))))))) = (a,b,c,d,e,f,g,h,i)
weak_untuple (a,b,c,d,e,f,g,h,i) = (a,(b,(c,(d,(e,(f,(g,(h,(i,())))))))))
instance TupleOrUnary (a,b,c,d,e,f,g,h,i,j) (a,(b,(c,(d,(e,(f,(g,(h,(i,(j,())))))))))) where
weak_tuple (a,(b,(c,(d,(e,(f,(g,(h,(i,(j,())))))))))) = (a,b,c,d,e,f,g,h,i,j)
weak_untuple (a,b,c,d,e,f,g,h,i,j) = (a,(b,(c,(d,(e,(f,(g,(h,(i,(j,()))))))))))
class (TupleOrUnary t s) => Tuple t s | s -> t, t -> s where
tuple :: s -> t
tuple = weak_tuple
untuple :: t -> s
untuple = weak_untuple
instance Tuple () ()
instance Tuple (a,b) (a,(b,()))
instance Tuple (a,b,c) (a,(b,(c,())))
instance Tuple (a,b,c,d) (a,(b,(c,(d,()))))
instance Tuple (a,b,c,d,e) (a,(b,(c,(d,(e,())))))
instance Tuple (a,b,c,d,e,f) (a,(b,(c,(d,(e,(f,()))))))
instance Tuple (a,b,c,d,e,f,g) (a,(b,(c,(d,(e,(f,(g,())))))))
instance Tuple (a,b,c,d,e,f,g,h) (a,(b,(c,(d,(e,(f,(g,(h,()))))))))
instance Tuple (a,b,c,d,e,f,g,h,i) (a,(b,(c,(d,(e,(f,(g,(h,(i,())))))))))
instance Tuple (a,b,c,d,e,f,g,h,i,j) (a,(b,(c,(d,(e,(f,(g,(h,(i,(j,()))))))))))