| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
DataFrame.Internal.Types
Synopsis
- type Columnable' a = (Typeable a, Show a, Ord a, Eq a, Read a)
 - data Rep
 - type family If (cond :: Bool) (yes :: k) (no :: k) :: k where ...
 - type family Unboxable a :: Bool where ...
 - type family Numeric a :: Bool where ...
 - type family KindOf a :: Rep where ...
 - data SBool (b :: Bool) where
 - class SBoolI (b :: Bool) where
 - sUnbox :: SBoolI (Unboxable a) => SBool (Unboxable a)
 - sNumeric :: SBoolI (Numeric a) => SBool (Numeric a)
 - type family When (flag :: Bool) c where ...
 - type UnboxIf a = When (Unboxable a) (Unbox a)
 - type family IntegralTypes a :: Bool where ...
 - sIntegral :: SBoolI (IntegralTypes a) => SBool (IntegralTypes a)
 - type IntegralIf a = When (IntegralTypes a) (Integral a)
 - type family FloatingTypes a :: Bool where ...
 - sFloating :: SBoolI (FloatingTypes a) => SBool (FloatingTypes a)
 - type FloatingIf a = When (FloatingTypes a) (Real a, Fractional a)
 
Documentation
A type with column representations used to select the
"right" representation when specializing the toColumn function.
type family Unboxable a :: Bool where ... Source #
All unboxable types (according to the vector package).
Equations
| 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 _1 = 'False | 
type family Numeric a :: Bool where ... Source #
Equations
| Numeric Integer = 'True | |
| 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 _1 = 'False | 
sUnbox :: SBoolI (Unboxable a) => SBool (Unboxable a) Source #
Type-level function to determine whether or not a type is unboxa
type family IntegralTypes a :: Bool where ... Source #
Equations
| IntegralTypes Integer = 'True | |
| IntegralTypes Int = 'True | |
| IntegralTypes Int8 = 'True | |
| IntegralTypes Int16 = 'True | |
| IntegralTypes Int32 = 'True | |
| IntegralTypes Int64 = 'True | |
| IntegralTypes Word = 'True | |
| IntegralTypes Word8 = 'True | |
| IntegralTypes Word16 = 'True | |
| IntegralTypes Word32 = 'True | |
| IntegralTypes Word64 = 'True | |
| IntegralTypes _1 = 'False | 
sIntegral :: SBoolI (IntegralTypes a) => SBool (IntegralTypes a) Source #
type IntegralIf a = When (IntegralTypes a) (Integral a) Source #
type family FloatingTypes a :: Bool where ... Source #
Equations
| FloatingTypes Float = 'True | |
| FloatingTypes Double = 'True | |
| FloatingTypes _1 = 'False | 
sFloating :: SBoolI (FloatingTypes a) => SBool (FloatingTypes a) Source #
type FloatingIf a = When (FloatingTypes a) (Real a, Fractional a) Source #