easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.Backend

Synopsis

Documentation

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.

Constructors

Backend 

Fields

Instances

Instances details
type DeriveContext (Backend i t ds b) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Backend

type DeriveContext (Backend i t ds b) = b ~ BackendFamily t ds

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.

Equations

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 

class KnownBackend t ds (BackendFamily t ds) => KnownBackend (t :: Type) (ds :: [Nat]) Source #

Backend resolver: Use this constraint to find any class instances defined for all DataFrame implementations, e.g. Num, PrimBytes, etc.

Instances

Instances details
KnownBackend t ds (BackendFamily t ds) => KnownBackend t ds Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Backend

inferKnownBackend :: forall (t :: Type) (ds :: [Nat]). (PrimBytes t, Dimensions ds) => Dict (KnownBackend t ds) Source #

inferPrimElem :: forall (t :: Type) (d :: Nat) (ds :: [Nat]) (i :: Type). KnownBackend t (d ': ds) => Backend i t (d ': ds) (BackendFamily t (d ': ds)) -> Dict (PrimBytes t) Source #

Auto-deriving instances

inferEq :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Eq t, KnownBackend t ds b) => Dict (Eq (Backend i t ds b)) Source #

inferOrd :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (Backend i t ds b)) Source #

inferProductOrder :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Ord t, KnownBackend t ds b) => Dict (ProductOrder (Backend i t ds b)) Source #

inferPONonTransitive :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend i t ds b))) Source #

inferPOPartial :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Ord t, KnownBackend t ds b) => Dict (Ord (ProductOrd (Backend i t ds b))) Source #

inferBounded :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Bounded t, KnownBackend t ds b) => Dict (Bounded (Backend i t ds b)) Source #

inferNum :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Num t, KnownBackend t ds b) => Dict (Num (Backend i t ds b)) Source #

inferFractional :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Fractional t, KnownBackend t ds b) => Dict (Fractional (Backend i t ds b)) Source #

inferFloating :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (Floating t, KnownBackend t ds b) => Dict (Floating (Backend i t ds b)) Source #

inferPrimBytes :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (PrimBytes t, Dimensions ds, KnownBackend t ds b) => Dict (PrimBytes (Backend i t ds b)) Source #

inferPrimArray :: forall (t :: Type) (ds :: [Nat]) (b :: Type) (i :: Type). (PrimBytes t, KnownBackend t ds b) => Dict (PrimArray t (Backend i t ds b)) Source #