module Graphics.QML.DataModel.Internal.Generic.Get where
import Graphics.QML.DataModel.Internal.FFI
import Graphics.QML.DataModel.Internal.Generic.Count
import Control.Exception
import Control.Monad
import Data.Proxy
import Data.Text (Text, unpack)
import Foreign.C.Types
import GHC.Generics
import Numeric.Natural
class QtTable t where
getColumn :: Int -> t -> IO QtVariant
default getColumn :: (Generic t, GQtTable (Rep t)) => Int -> t -> IO QtVariant
getColumn ix = gGetColumn ix . from
class GQtTable f where
gGetColumn :: Int -> f a -> IO QtVariant
instance QtField t => GQtTable (K1 i t) where
gGetColumn _ (K1 v) = qtField v
instance GQtTable f => GQtTable (M1 i t f) where
gGetColumn ix (M1 a) = gGetColumn ix a
instance (GCountFields a, GCountFields b, GQtTable a, GQtTable b) => GQtTable (a :*: b) where
gGetColumn ix (a :*: b) = do
when (ix < 0) . throwIO $ ColumnIndexNegative ix
when (ix >= (na + nb)) . throwIO $ ColumnIndexOutOfBounds ix (na + nb)
if ix < na
then gGetColumn ix a
else gGetColumn (ix na) b
where na = gCountFields pa
nb = gCountFields pb
pa :: Proxy a = Proxy
pb :: Proxy b = Proxy
class QtField t where
qtField :: t -> IO QtVariant
instance QtField Int where
qtField = c_newQtInt . CInt . fromIntegral
instance QtField Double where
qtField = c_newQtDouble . CDouble
instance QtField String where
qtField = newQtString
instance QtField Text where
qtField = newQtString . unpack
instance QtField Bool where
qtField v = c_newQtBool $ fromIntegral b
where b :: Int
b = if v then 1 else 0
instance QtField Integer where
qtField = newQtString . show
instance QtField Natural where
qtField = newQtString . show
instance QtField t => QtField (Maybe t) where
qtField Nothing = c_newQtNull
qtField (Just t) = qtField t