{-# OPTIONS_HADDOCK show-extensions #-}

{-# LANGUAGE 
    DefaultSignatures
  , DeriveDataTypeable
  , FlexibleContexts
  , PolyKinds
  , ScopedTypeVariables
  , TypeFamilies
  , TypeOperators 
  #-}

{-|
Module      : Graphics.QML.DataModel.Internal.Generic.Count
Copyright   : (c) Marcin Mrotek, 2015
License     : BSD3
Maintainer  : marcin.jan.mrotek@gmail.com
Stability   : experimental

Count the number of columns in a data type.
-}

module Graphics.QML.DataModel.Internal.Generic.Count where

import Control.Exception
import Data.Typeable
import GHC.Generics

-- |Exception thrown when QML tries to acces a column that is not available. Shouldn't really happen.
data ColumnIndexException =
    ColumnIndexNegative Int        -- ^QML called for a negative column index.
  | ColumnIndexOutOfBounds Int Int -- ^QML called for a column index that is too high.
 deriving (Show, Typeable)

instance Exception ColumnIndexException

-- |A class of types that have a specific number of fields. Generic implementation is provided for all purely product types.
class CountFields t where
  countFields :: proxy t -> Int
 
  default countFields :: ( Generic t, GCountFields (Rep t) ) => proxy t -> Int
  countFields _ = gCountFields p
    where p :: Proxy (Rep t) = Proxy

-- |Generic implementation of the 'CountFields' class.
class GCountFields f where
  gCountFields :: proxy f -> Int

-- |A container type has a proxyle column.
instance GCountFields (K1 i c) where
  gCountFields _ = 1

-- |Meta information is skipped, and the recursion proceeds further down.
instance GCountFields f => GCountFields (M1 i t f) where
  gCountFields _ = gCountFields p
    where p :: Proxy f = Proxy

-- |A product type's number of columns is a sum of the terms' column numbers.
instance (GCountFields a, GCountFields b) => GCountFields (a :*: b) where
  gCountFields _ = gCountFields a + gCountFields b
    where a :: Proxy a = Proxy
          b :: Proxy b = Proxy