easytensor-1.0.1.0: Pure, type-indexed haskell vector, matrix, and tensor library.

Copyright(c) Artem Chirkin
LicenseBSD3
Maintainerchirkin@arch.ethz.ch
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.Array.Family

Description

 
Synopsis

Documentation

type family Array (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 an array at compile time, it chooses a more efficient specialized instance of Array, 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

Array t '[] = ScalarBase t 
Array Float '[2] = FloatX2 
Array Float '[3] = FloatX3 
Array Float '[4] = FloatX4 
Array Double '[2] = DoubleX2 
Array Double '[3] = DoubleX3 
Array Double '[4] = DoubleX4 
Array t ds = ArrayBase t ds 

newtype ScalarBase t Source #

Specialize ScalarBase type without any arrays

Constructors

ScalarBase 

Fields

Instances
PrimBytes t => PrimArray t (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Methods

broadcast :: t -> ScalarBase t Source #

ix# :: Int# -> ScalarBase t -> t Source #

gen# :: Int# -> (s -> (#s, t#)) -> s -> (#s, ScalarBase t#) Source #

upd# :: Int# -> Int# -> t -> ScalarBase t -> ScalarBase t Source #

elemOffset :: ScalarBase t -> Int# Source #

elemSize0 :: ScalarBase t -> Int# Source #

fromElems :: Int# -> Int# -> ByteArray# -> ScalarBase t Source #

Bounded (ScalarBase Double) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Bounded (ScalarBase Float) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Bounded t => Bounded (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Enum t => Enum (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Eq t => Eq (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Methods

(==) :: ScalarBase t -> ScalarBase t -> Bool #

(/=) :: ScalarBase t -> ScalarBase t -> Bool #

Floating t => Floating (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Fractional t => Fractional (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Integral t => Integral (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Num t => Num (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Ord t => Ord (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Read t => Read (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Real t => Real (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

RealFloat t => RealFloat (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

RealFrac t => RealFrac (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

Methods

properFraction :: Integral b => ScalarBase t -> (b, ScalarBase t) #

truncate :: Integral b => ScalarBase t -> b #

round :: Integral b => ScalarBase t -> b #

ceiling :: Integral b => ScalarBase t -> b #

floor :: Integral b => ScalarBase t -> b #

Show t => Show (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

PrimBytes t => PrimBytes (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

data ArrayBase (t :: Type) (ds :: [Nat]) Source #

Generic Array implementation. This array can reside in plain ByteArray# and can share the ByteArray# with other arrays. However, byte offset in the ByteArray# must be multiple of the element size.

Constructors

ArrayBase (#t | (#Int#, Int#, ByteArray#, Evidence (PrimBytes t)#)#) 
Instances
PrimBytes t => PrimArray t (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

broadcast :: t -> ArrayBase t ds Source #

ix# :: Int# -> ArrayBase t ds -> t Source #

gen# :: Int# -> (s -> (#s, t#)) -> s -> (#s, ArrayBase t ds#) Source #

upd# :: Int# -> Int# -> t -> ArrayBase t ds -> ArrayBase t ds Source #

elemOffset :: ArrayBase t ds -> Int# Source #

elemSize0 :: ArrayBase t ds -> Int# Source #

fromElems :: Int# -> Int# -> ByteArray# -> ArrayBase t ds Source #

Bounded (ArrayBase Double ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Bounded (ArrayBase Float ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Bounded t => Bounded (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

minBound :: ArrayBase t ds #

maxBound :: ArrayBase t ds #

Eq t => Eq (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

(==) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

(/=) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

Floating t => Floating (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

pi :: ArrayBase t ds #

exp :: ArrayBase t ds -> ArrayBase t ds #

log :: ArrayBase t ds -> ArrayBase t ds #

sqrt :: ArrayBase t ds -> ArrayBase t ds #

(**) :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

logBase :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

sin :: ArrayBase t ds -> ArrayBase t ds #

cos :: ArrayBase t ds -> ArrayBase t ds #

tan :: ArrayBase t ds -> ArrayBase t ds #

asin :: ArrayBase t ds -> ArrayBase t ds #

acos :: ArrayBase t ds -> ArrayBase t ds #

atan :: ArrayBase t ds -> ArrayBase t ds #

sinh :: ArrayBase t ds -> ArrayBase t ds #

cosh :: ArrayBase t ds -> ArrayBase t ds #

tanh :: ArrayBase t ds -> ArrayBase t ds #

asinh :: ArrayBase t ds -> ArrayBase t ds #

acosh :: ArrayBase t ds -> ArrayBase t ds #

atanh :: ArrayBase t ds -> ArrayBase t ds #

log1p :: ArrayBase t ds -> ArrayBase t ds #

expm1 :: ArrayBase t ds -> ArrayBase t ds #

log1pexp :: ArrayBase t ds -> ArrayBase t ds #

log1mexp :: ArrayBase t ds -> ArrayBase t ds #

Fractional t => Fractional (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

(/) :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

recip :: ArrayBase t ds -> ArrayBase t ds #

fromRational :: Rational -> ArrayBase t ds #

Num t => Num (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

(+) :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

(-) :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

(*) :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

negate :: ArrayBase t ds -> ArrayBase t ds #

abs :: ArrayBase t ds -> ArrayBase t ds #

signum :: ArrayBase t ds -> ArrayBase t ds #

fromInteger :: Integer -> ArrayBase t ds #

Ord t => Ord (ArrayBase t ds) Source #

Implement partial ordering for >, <, >=, <= and lexicographical ordering for compare

Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

compare :: ArrayBase t ds -> ArrayBase t ds -> Ordering #

(<) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

(<=) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

(>) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

(>=) :: ArrayBase t ds -> ArrayBase t ds -> Bool #

max :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

min :: ArrayBase t ds -> ArrayBase t ds -> ArrayBase t ds #

(Dimensions ds, Show t) => Show (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

Methods

showsPrec :: Int -> ArrayBase t ds -> ShowS #

show :: ArrayBase t ds -> String #

showList :: [ArrayBase t ds] -> ShowS #

(PrimBytes t, Dimensions ds) => PrimBytes (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

class ArraySingleton (t :: Type) (ds :: [Nat]) where Source #

A framework for using Array type family instances.

Methods

aSing :: ArraySing t ds Source #

Get Array type family instance

Instances
(Array t ds ~ ArrayBase t ds, PrimBytes t) => ArraySingleton t ds Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing t ds Source #

ArraySingleton t ([] :: [Nat]) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing t [] Source #

ArraySingleton Double (2 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Double (2 ': []) Source #

ArraySingleton Double (3 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Double (3 ': []) Source #

ArraySingleton Double (4 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Double (4 ': []) Source #

ArraySingleton Float (2 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Float (2 ': []) Source #

ArraySingleton Float (3 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Float (3 ': []) Source #

ArraySingleton Float (4 ': ([] :: [Nat])) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

aSing :: ArraySing Float (4 ': []) Source #

data ArraySing t (ds :: [Nat]) where Source #

Constructors

AScalar :: Array t ds ~ ScalarBase t => ArraySing t '[] 
AF2 :: Array t ds ~ FloatX2 => ArraySing Float '[2] 
AF3 :: Array t ds ~ FloatX3 => ArraySing Float '[3] 
AF4 :: Array t ds ~ FloatX4 => ArraySing Float '[4] 
AD2 :: Array t ds ~ DoubleX2 => ArraySing Double '[2] 
AD3 :: Array t ds ~ DoubleX3 => ArraySing Double '[3] 
AD4 :: Array t ds ~ DoubleX4 => ArraySing Double '[4] 
ABase :: (Array t ds ~ ArrayBase t ds, PrimBytes t) => ArraySing t ds 
Instances
Eq (ArraySing t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

(==) :: ArraySing t ds -> ArraySing t ds -> Bool #

(/=) :: ArraySing t ds -> ArraySing t ds -> Bool #

Ord (ArraySing t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

compare :: ArraySing t ds -> ArraySing t ds -> Ordering #

(<) :: ArraySing t ds -> ArraySing t ds -> Bool #

(<=) :: ArraySing t ds -> ArraySing t ds -> Bool #

(>) :: ArraySing t ds -> ArraySing t ds -> Bool #

(>=) :: ArraySing t ds -> ArraySing t ds -> Bool #

max :: ArraySing t ds -> ArraySing t ds -> ArraySing t ds #

min :: ArraySing t ds -> ArraySing t ds -> ArraySing t ds #

Show (ArraySing t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family

Methods

showsPrec :: Int -> ArraySing t ds -> ShowS #

show :: ArraySing t ds -> String #

showList :: [ArraySing t ds] -> ShowS #

aSingEv :: ArraySing t ds -> Evidence (ArraySingleton t ds) Source #

Use ArraySing GADT to construct an ArraySingleton dictionary. In other words, bring an evidence of ArraySingleton instance into a scope at runtime.

inferASing :: forall t ds. (PrimBytes t, Dimensions ds) => Evidence (ArraySingleton t ds) Source #

Use ArraySing GADT to construct an ArraySingleton dictionary. The same as aSingEv, but relies on PrimBytes and Dimensions.

inferPrimElem :: forall t d ds. ArraySingleton t (d ': ds) => Evidence (PrimBytes t) Source #

This is a special function, because Scalar does not require PrimBytes. That is why the dimension list in the argument is not empty.

inferPrim :: forall t ds. (PrimBytes t, ArraySingleton t ds, Dimensions ds) => Evidence (PrimBytes (Array t ds), PrimArray t (Array t ds)) Source #

inferEq :: forall t ds. (Eq t, ArraySingleton t ds) => Evidence (Eq (Array t ds)) Source #

inferShow :: forall t ds. (Show t, Dimensions ds, ArraySingleton t ds) => Evidence (Show (Array t ds)) Source #

inferOrd :: forall t ds. (Ord t, ArraySingleton t ds) => Evidence (Ord (Array t ds)) Source #

inferNum :: forall t ds. (Num t, ArraySingleton t ds) => Evidence (Num (Array t ds)) Source #

inferFloating :: forall t ds. (Floating t, ArraySingleton t ds) => Evidence (Floating (Array t ds)) Source #