{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
module DataFrame.Internal.Types where
import Data.Int ( Int8, Int16, Int32, Int64 )
import Data.Kind (Type, Constraint)
import Data.Maybe (fromMaybe)
import Data.Typeable (Typeable, type (:~:) (..))
import Data.Word ( Word8, Word16, Word32, Word64 )
import Type.Reflection (TypeRep, typeOf, typeRep)
import Data.Type.Equality (TestEquality(..))
import qualified Data.Vector as VB
import qualified Data.Vector.Unboxed as VU
type Columnable' a = (Typeable a, Show a, Ord a, Eq a, Read a)
data Rep
= RBoxed
| RUnboxed
| ROptional
type family If (cond :: Bool) (yes :: k) (no :: k) :: k where
If 'True yes _ = yes
If 'False _ no = no
type family Unboxable (a :: Type) :: Bool where
Unboxable Int = 'True
Unboxable Int8 = 'True
Unboxable Int16 = 'True
Unboxable Int32 = 'True
Unboxable Int64 = 'True
Unboxable Word = 'True
Unboxable Word8 = 'True
Unboxable Word16 = 'True
Unboxable Word32 = 'True
Unboxable Word64 = 'True
Unboxable Char = 'True
Unboxable Bool = 'True
Unboxable Double = 'True
Unboxable Float = 'True
Unboxable _ = 'False
type family Numeric (a :: Type) :: Bool where
Numeric Int = 'True
Numeric Int8 = 'True
Numeric Int16 = 'True
Numeric Int32 = 'True
Numeric Int64 = 'True
Numeric Word = 'True
Numeric Word8 = 'True
Numeric Word16 = 'True
Numeric Word32 = 'True
Numeric Word64 = 'True
Numeric Double = 'True
Numeric Float = 'True
Numeric _ = 'False
type family KindOf a :: Rep where
KindOf (Maybe a) = 'ROptional
KindOf a = If (Unboxable a) 'RUnboxed 'RBoxed
data SBool (b :: Bool) where
STrue :: SBool 'True
SFalse :: SBool 'False
class SBoolI (b :: Bool) where
sbool :: SBool b
instance SBoolI 'True where sbool :: SBool 'True
sbool = SBool 'True
STrue
instance SBoolI 'False where sbool :: SBool 'False
sbool = SBool 'False
SFalse
sUnbox :: forall a. SBoolI (Unboxable a) => SBool (Unboxable a)
sUnbox :: forall a. SBoolI (Unboxable a) => SBool (Unboxable a)
sUnbox = forall (b :: Bool). SBoolI b => SBool b
sbool @(Unboxable a)
sNumeric :: forall a. SBoolI (Numeric a) => SBool (Numeric a)
sNumeric :: forall a. SBoolI (Numeric a) => SBool (Numeric a)
sNumeric = forall (b :: Bool). SBoolI b => SBool b
sbool @(Numeric a)
type family When (flag :: Bool) (c :: Constraint) :: Constraint where
When 'True c = c
When 'False c = ()
type UnboxIf a = When (Unboxable a) (VU.Unbox a)