{-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables, DeriveDataTypeable #-}

module Data.AdaptiveTuple.AdaptiveTuple (
  -- *Type classes
  AdaptiveTuple (..)
  -- *Types
  ,AdaptiveTupleException (..)
  -- *Error functions
  ,oObExcp
  ,insExcp
  )

where

import Data.TypeLevel.Num
import Data.Data
import Control.Exception
import Control.Applicative

-- |Adaptive tuples: unboxed tuples of varying size.
-- @s@ is a type-level indicator of the number of elements in the container.
class (Nat s, Applicative (c s)) => AdaptiveTuple c s where
  getIndex   :: c s el -> Int -> el
  setIndex   :: Int -> el -> c s el -> c s el
  mapIndex   :: (el -> el) -> Int -> c s el -> c s el
  toATuple   :: [el] -> c s el
  fromATuple :: c s el -> [el]
  tupLength  :: c s el -> Int
  tupLength _ = toInt (undefined :: s)

-- -------------------------------------
-- exceptions

data AdaptiveTupleException =
    ATupleIndexOutOfBounds String
  | ATupleInsufficientInput
  deriving (Show, Typeable)

instance Exception AdaptiveTupleException

oObExcp :: String -> a
oObExcp = throw . ATupleIndexOutOfBounds

insExcp :: a
insExcp = throw ATupleInsufficientInput