{-# LANGUAGE UnicodeSyntax, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts #-}
-- | Generalizes 'Prelude.snd', 'Prelude.fst', and so on.
module Data.Nthable
where

import Data.TypeLevel.Num.Sets
import Data.TypeLevel.Num.Reps
import Data.TypeLevel.Num.Aliases

-- | A class that knows how to access the "nth" member of a
--   type.
class (Pos n)  Nthable t n a | t n  a where
	nth  n  t  a
	-- ^ Example: 
	--
	-- > nth d1 (1,2) == 1
	-- > nth d2 (1,2) == 2
	-- > nth d3 (1,2) == error!

instance Nthable (a,b) D1 a where nth _ (a,_) = a
instance Nthable (a,b) D2 b where nth _ (_,b) = b

instance Nthable (a,b,c) D1 a where nth _ (a,_,_) = a
instance Nthable (a,b,c) D2 b where nth _ (_,b,_) = b
instance Nthable (a,b,c) D3 c where nth _ (_,_,c) = c

instance Nthable (a,b,c,d) D1 a where nth _ (a,_,_,_) = a
instance Nthable (a,b,c,d) D2 b where nth _ (_,b,_,_) = b
instance Nthable (a,b,c,d) D3 c where nth _ (_,_,c,_) = c
instance Nthable (a,b,c,d) D4 d where nth _ (_,_,_,d) = d

instance Nthable (a,b,c,d,e) D1 a where nth _ (a,_,_,_,_) = a
instance Nthable (a,b,c,d,e) D2 b where nth _ (_,b,_,_,_) = b
instance Nthable (a,b,c,d,e) D3 c where nth _ (_,_,c,_,_) = c
instance Nthable (a,b,c,d,e) D4 d where nth _ (_,_,_,d,_) = d
instance Nthable (a,b,c,d,e) D5 e where nth _ (_,_,_,_,e) = e

instance Nthable (a,b,c,d,e,f) D1 a where nth _ (a,_,_,_,_,_) = a
instance Nthable (a,b,c,d,e,f) D2 b where nth _ (_,b,_,_,_,_) = b
instance Nthable (a,b,c,d,e,f) D3 c where nth _ (_,_,c,_,_,_) = c
instance Nthable (a,b,c,d,e,f) D4 d where nth _ (_,_,_,d,_,_) = d
instance Nthable (a,b,c,d,e,f) D5 e where nth _ (_,_,_,_,e,_) = e
instance Nthable (a,b,c,d,e,f) D6 f where nth _ (_,_,_,_,_,f) = f

instance Nthable (a,b,c,d,e,f,g) D1 a where nth _ (a,_,_,_,_,_,_) = a
instance Nthable (a,b,c,d,e,f,g) D2 b where nth _ (_,b,_,_,_,_,_) = b
instance Nthable (a,b,c,d,e,f,g) D3 c where nth _ (_,_,c,_,_,_,_) = c
instance Nthable (a,b,c,d,e,f,g) D4 d where nth _ (_,_,_,d,_,_,_) = d
instance Nthable (a,b,c,d,e,f,g) D5 e where nth _ (_,_,_,_,e,_,_) = e
instance Nthable (a,b,c,d,e,f,g) D6 f where nth _ (_,_,_,_,_,f,_) = f
instance Nthable (a,b,c,d,e,f,g) D7 g where nth _ (_,_,_,_,_,_,g) = g

-- | 'Prelude.fst' extended to work on any 'Nthable' type.
fst  (Nthable n D1 a)  n  a
fst mr = nth d1 mr

-- | 'Prelude.snd' extended to work on any 'Nthable' type.
snd  (Nthable n D2 a)  n  a
snd mr = nth d2 mr

thrd  (Nthable n D3 a)  n  a
thrd mr = nth d3 mr

frth  (Nthable n D4 a)  n  a
frth mr = nth d4 mr

ffth  (Nthable n D5 a)  n  a
ffth mr = nth d5 mr

sxth  (Nthable n D6 a)  n  a
sxth mr = nth d6 mr

svnth  (Nthable n D7 a)  n  a
svnth mr = nth d7 mr