Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type DFBackend (t :: Type) (ds :: [Nat]) = Backend I t ds (BackendFamily t ds)
- newtype Backend (i :: Type) (t :: Type) (ds :: [Nat]) (backend :: Type) = Backend {
- _getBackend :: backend
- type family BackendFamily (t :: Type) (ds :: [Nat]) = (v :: Type) | v -> t ds where ...
- type KnownBackend (t :: Type) (ds :: [Nat]) = KnownBackend t ds (BackendFamily t ds)
- inferKnownBackend :: forall (t :: Type) (ds :: [Nat]). (PrimBytes t, Dimensions ds) => Dict (KnownBackend t ds)
- inferPrimElem :: forall (t :: Type) (d :: Nat) (ds :: [Nat]). KnownBackend t (d ': ds) => DFBackend t (d ': ds) -> Dict (PrimBytes t)
- inferEq :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Eq t, KnownBackend t ds b) => Dict (Eq (Backend I t ds b))
- inferOrd :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (Backend I t ds b))
- inferProductOrder :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (ProductOrder (Backend I t ds b))
- inferPONonTransitive :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend I t ds b)))
- inferPOPartial :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend I t ds b)))
- inferBounded :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Bounded t, KnownBackend t ds b) => Dict (Bounded (Backend I t ds b))
- inferNum :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Num t, KnownBackend t ds b) => Dict (Num (Backend I t ds b))
- inferFractional :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Fractional t, KnownBackend t ds b) => Dict (Fractional (Backend I t ds b))
- inferFloating :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Floating t, KnownBackend t ds b) => Dict (Floating (Backend I t ds b))
- inferPrimBytes :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (PrimBytes t, Dimensions ds, KnownBackend t ds b) => Dict (PrimBytes (Backend I t ds b))
- inferPrimArray :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (PrimBytes t, KnownBackend t ds b) => Dict (PrimArray t (Backend I t ds b))
Documentation
type DFBackend (t :: Type) (ds :: [Nat]) = Backend I t ds (BackendFamily t ds) Source #
Implementation behind the DataFrame
newtype Backend (i :: Type) (t :: Type) (ds :: [Nat]) (backend :: Type) Source #
A newtype wrapper for all DataFrame implementations. I need two layers of wrappers to provide default overlappable instances to all type classes using KnownBackend mechanics. Type arguments are redundant here; nevertheless, they improve readability of error messages.
Backend | |
|
type family BackendFamily (t :: Type) (ds :: [Nat]) = (v :: Type) | v -> t ds where ... Source #
This type family aggregates all types used for arrays with different
dimensioinality.
The family is injective; thus, it is possible to get type family instance
given the data constructor (and vice versa).
If GHC knows the dimensionality of a backend at compile time, it chooses
a more efficient specialized instance of BackendFamily
, e.g. Scalar newtype wrapper.
Otherwise, it falls back to the generic ArrayBase implementation.
Data family would not work here, because it would give overlapping instances.
BackendFamily t '[] = ScalarBase t | |
BackendFamily Float '[2] = FloatX2 | |
BackendFamily Float '[3] = FloatX3 | |
BackendFamily Float '[4] = FloatX4 | |
BackendFamily Double '[2] = DoubleX2 | |
BackendFamily Double '[3] = DoubleX3 | |
BackendFamily Double '[4] = DoubleX4 | |
BackendFamily t ds = ArrayBase t ds |
type KnownBackend (t :: Type) (ds :: [Nat]) = KnownBackend t ds (BackendFamily t ds) Source #
Backend resolver:
Use this constraint to find any class instances defined for all DataFrame implementations,
e.g. Num
, PrimBytes
, etc.
inferKnownBackend :: forall (t :: Type) (ds :: [Nat]). (PrimBytes t, Dimensions ds) => Dict (KnownBackend t ds) Source #
inferPrimElem :: forall (t :: Type) (d :: Nat) (ds :: [Nat]). KnownBackend t (d ': ds) => DFBackend t (d ': ds) -> Dict (PrimBytes t) Source #
Auto-deriving instances
inferEq :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Eq t, KnownBackend t ds b) => Dict (Eq (Backend I t ds b)) Source #
inferOrd :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (Backend I t ds b)) Source #
inferProductOrder :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (ProductOrder (Backend I t ds b)) Source #
inferPONonTransitive :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend I t ds b))) Source #
inferPOPartial :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend I t ds b))) Source #
inferBounded :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Bounded t, KnownBackend t ds b) => Dict (Bounded (Backend I t ds b)) Source #
inferNum :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Num t, KnownBackend t ds b) => Dict (Num (Backend I t ds b)) Source #
inferFractional :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Fractional t, KnownBackend t ds b) => Dict (Fractional (Backend I t ds b)) Source #
inferFloating :: forall (t :: Type) (ds :: [Nat]) (b :: Type). (Floating t, KnownBackend t ds b) => Dict (Floating (Backend I t ds b)) Source #