{-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE DefaultSignatures , DeriveDataTypeable , FlexibleContexts , PolyKinds , ScopedTypeVariables , 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 import Graphics.QML.DataModel.Internal.Generic.Mock -- |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 :: sing t -> Int default countFields :: (Mock t, Generic t, GCountFields (Rep t)) => sing t -> Int countFields _ = gCountFields $ from (mock :: t) -- |Generic implementation of the 'CountFields' class. class GCountFields f where gCountFields :: f a -> Int -- |A container type has a single column. instance GCountFields (K1 i c) where gCountFields (K1 _) = 1 -- |Meta information is skipped, and the recursion proceeds further down. instance GCountFields f => GCountFields (M1 i t f) where gCountFields (M1 a) = gCountFields a -- |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 (a :*: b) = gCountFields a + gCountFields b