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

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

Numeric.DataFrame

Contents

Description

 

Synopsis

Documentation

data family DataFrame (t :: Type) (xs :: [k]) Source #

Keep data in a primitive data frame and maintain information about Dimensions in the type-system

Instances

(Dimensions ds, ElementWise (Idx ds) t (Array t ds)) => ElementWise (Idx ds) t (DataFrame Nat t ds) Source # 

Methods

indexOffset# :: DataFrame Nat t ds -> Int# -> t

(!) :: DataFrame Nat t ds -> Idx ds -> t

ewmap :: (Idx ds -> t -> t) -> DataFrame Nat t ds -> DataFrame Nat t ds

ewgen :: (Idx ds -> t) -> DataFrame Nat t ds

ewgenA :: Applicative f => (Idx ds -> f t) -> f (DataFrame Nat t ds)

ewfoldl :: (Idx ds -> a -> t -> a) -> a -> DataFrame Nat t ds -> a

ewfoldr :: (Idx ds -> t -> a -> a) -> a -> DataFrame Nat t ds -> a

elementWise :: Applicative f => (t -> f t) -> DataFrame Nat t ds -> f (DataFrame Nat t ds)

indexWise :: Applicative f => (Idx ds -> t -> f t) -> DataFrame Nat t ds -> f (DataFrame Nat t ds)

broadcast :: t -> DataFrame Nat t ds

update :: Idx ds -> t -> DataFrame Nat t ds -> DataFrame Nat t ds

Bounded (Array t ds) => Bounded (DataFrame Nat t ds) Source # 

Methods

minBound :: DataFrame Nat t ds #

maxBound :: DataFrame Nat t ds #

Enum (Array t ds) => Enum (DataFrame Nat t ds) Source # 

Methods

succ :: DataFrame Nat t ds -> DataFrame Nat t ds #

pred :: DataFrame Nat t ds -> DataFrame Nat t ds #

toEnum :: Int -> DataFrame Nat t ds #

fromEnum :: DataFrame Nat t ds -> Int #

enumFrom :: DataFrame Nat t ds -> [DataFrame Nat t ds] #

enumFromThen :: DataFrame Nat t ds -> DataFrame Nat t ds -> [DataFrame Nat t ds] #

enumFromTo :: DataFrame Nat t ds -> DataFrame Nat t ds -> [DataFrame Nat t ds] #

enumFromThenTo :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds -> [DataFrame Nat t ds] #

Eq (Array t ds) => Eq (DataFrame Nat t ds) Source # 

Methods

(==) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

(/=) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

Eq (DataFrame XNat t ds) Source # 

Methods

(==) :: DataFrame XNat t ds -> DataFrame XNat t ds -> Bool #

(/=) :: DataFrame XNat t ds -> DataFrame XNat t ds -> Bool #

Floating (Array t ds) => Floating (DataFrame Nat t ds) Source # 

Methods

pi :: DataFrame Nat t ds #

exp :: DataFrame Nat t ds -> DataFrame Nat t ds #

log :: DataFrame Nat t ds -> DataFrame Nat t ds #

sqrt :: DataFrame Nat t ds -> DataFrame Nat t ds #

(**) :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

logBase :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

sin :: DataFrame Nat t ds -> DataFrame Nat t ds #

cos :: DataFrame Nat t ds -> DataFrame Nat t ds #

tan :: DataFrame Nat t ds -> DataFrame Nat t ds #

asin :: DataFrame Nat t ds -> DataFrame Nat t ds #

acos :: DataFrame Nat t ds -> DataFrame Nat t ds #

atan :: DataFrame Nat t ds -> DataFrame Nat t ds #

sinh :: DataFrame Nat t ds -> DataFrame Nat t ds #

cosh :: DataFrame Nat t ds -> DataFrame Nat t ds #

tanh :: DataFrame Nat t ds -> DataFrame Nat t ds #

asinh :: DataFrame Nat t ds -> DataFrame Nat t ds #

acosh :: DataFrame Nat t ds -> DataFrame Nat t ds #

atanh :: DataFrame Nat t ds -> DataFrame Nat t ds #

log1p :: DataFrame Nat t ds -> DataFrame Nat t ds #

expm1 :: DataFrame Nat t ds -> DataFrame Nat t ds #

log1pexp :: DataFrame Nat t ds -> DataFrame Nat t ds #

log1mexp :: DataFrame Nat t ds -> DataFrame Nat t ds #

Fractional (Array t ds) => Fractional (DataFrame Nat t ds) Source # 

Methods

(/) :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

recip :: DataFrame Nat t ds -> DataFrame Nat t ds #

fromRational :: Rational -> DataFrame Nat t ds #

Integral (Array t ds) => Integral (DataFrame Nat t ds) Source # 

Methods

quot :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

rem :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

div :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

mod :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

quotRem :: DataFrame Nat t ds -> DataFrame Nat t ds -> (DataFrame Nat t ds, DataFrame Nat t ds) #

divMod :: DataFrame Nat t ds -> DataFrame Nat t ds -> (DataFrame Nat t ds, DataFrame Nat t ds) #

toInteger :: DataFrame Nat t ds -> Integer #

Num (Array t ds) => Num (DataFrame Nat t ds) Source # 

Methods

(+) :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

(-) :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

(*) :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

negate :: DataFrame Nat t ds -> DataFrame Nat t ds #

abs :: DataFrame Nat t ds -> DataFrame Nat t ds #

signum :: DataFrame Nat t ds -> DataFrame Nat t ds #

fromInteger :: Integer -> DataFrame Nat t ds #

Ord (Array t ds) => Ord (DataFrame Nat t ds) Source # 

Methods

compare :: DataFrame Nat t ds -> DataFrame Nat t ds -> Ordering #

(<) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

(<=) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

(>) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

(>=) :: DataFrame Nat t ds -> DataFrame Nat t ds -> Bool #

max :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

min :: DataFrame Nat t ds -> DataFrame Nat t ds -> DataFrame Nat t ds #

(Read (Array t ds), Dimensions ds) => Read (DataFrame Nat t ds) Source # 
Real (Array t ds) => Real (DataFrame Nat t ds) Source # 

Methods

toRational :: DataFrame Nat t ds -> Rational #

RealFloat (Array t ds) => RealFloat (DataFrame Nat t ds) Source # 
RealFrac (Array t ds) => RealFrac (DataFrame Nat t ds) Source # 

Methods

properFraction :: Integral b => DataFrame Nat t ds -> (b, DataFrame Nat t ds) #

truncate :: Integral b => DataFrame Nat t ds -> b #

round :: Integral b => DataFrame Nat t ds -> b #

ceiling :: Integral b => DataFrame Nat t ds -> b #

floor :: Integral b => DataFrame Nat t ds -> b #

(Show (Array t ds), Dimensions ds) => Show (DataFrame Nat t ds) Source # 

Methods

showsPrec :: Int -> DataFrame Nat t ds -> ShowS #

show :: DataFrame Nat t ds -> String #

showList :: [DataFrame Nat t ds] -> ShowS #

Show (DataFrame XNat t ds) Source # 

Methods

showsPrec :: Int -> DataFrame XNat t ds -> ShowS #

show :: DataFrame XNat t ds -> String #

showList :: [DataFrame XNat t ds] -> ShowS #

PrimBytes (DataFrame k t ds) => Storable (DataFrame k t ds) Source # 

Methods

sizeOf :: DataFrame k t ds -> Int #

alignment :: DataFrame k t ds -> Int #

peekElemOff :: Ptr (DataFrame k t ds) -> Int -> IO (DataFrame k t ds) #

pokeElemOff :: Ptr (DataFrame k t ds) -> Int -> DataFrame k t ds -> IO () #

peekByteOff :: Ptr b -> Int -> IO (DataFrame k t ds) #

pokeByteOff :: Ptr b -> Int -> DataFrame k t ds -> IO () #

peek :: Ptr (DataFrame k t ds) -> IO (DataFrame k t ds) #

poke :: Ptr (DataFrame k t ds) -> DataFrame k t ds -> IO () #

(PrimBytes (Array Double ds), (~) (TYPE DoubleRep) (ElemPrim DoubleRep (Array Double ds)) Double#, (~) RuntimeRep (ElemRep (Array Double ds)) DoubleRep) => PrimBytes (DataFrame Nat Double ds) Source # 
(PrimBytes (Array Float ds), (~) (TYPE FloatRep) (ElemPrim FloatRep (Array Float ds)) Float#, (~) RuntimeRep (ElemRep (Array Float ds)) FloatRep) => PrimBytes (DataFrame Nat Float ds) Source # 
(PrimBytes (Array Int ds), (~) (TYPE IntRep) (ElemPrim IntRep (Array Int ds)) Int#, (~) RuntimeRep (ElemRep (Array Int ds)) IntRep) => PrimBytes (DataFrame Nat Int ds) Source # 
(PrimBytes (Array Int8 ds), (~) (TYPE IntRep) (ElemPrim IntRep (Array Int8 ds)) Int#, (~) RuntimeRep (ElemRep (Array Int8 ds)) IntRep) => PrimBytes (DataFrame Nat Int8 ds) Source # 
(PrimBytes (Array Int16 ds), (~) (TYPE IntRep) (ElemPrim IntRep (Array Int16 ds)) Int#, (~) RuntimeRep (ElemRep (Array Int16 ds)) IntRep) => PrimBytes (DataFrame Nat Int16 ds) Source # 
(PrimBytes (Array Int32 ds), (~) (TYPE IntRep) (ElemPrim IntRep (Array Int32 ds)) Int#, (~) RuntimeRep (ElemRep (Array Int32 ds)) IntRep) => PrimBytes (DataFrame Nat Int32 ds) Source # 
(PrimBytes (Array Int64 ds), (~) (TYPE IntRep) (ElemPrim IntRep (Array Int64 ds)) Int#, (~) RuntimeRep (ElemRep (Array Int64 ds)) IntRep) => PrimBytes (DataFrame Nat Int64 ds) Source # 
(PrimBytes (Array Word ds), (~) (TYPE WordRep) (ElemPrim WordRep (Array Word ds)) Word#, (~) RuntimeRep (ElemRep (Array Word ds)) WordRep) => PrimBytes (DataFrame Nat Word ds) Source # 
(PrimBytes (Array Word8 ds), (~) (TYPE WordRep) (ElemPrim WordRep (Array Word8 ds)) Word#, (~) RuntimeRep (ElemRep (Array Word8 ds)) WordRep) => PrimBytes (DataFrame Nat Word8 ds) Source # 
(PrimBytes (Array Word16 ds), (~) (TYPE WordRep) (ElemPrim WordRep (Array Word16 ds)) Word#, (~) RuntimeRep (ElemRep (Array Word16 ds)) WordRep) => PrimBytes (DataFrame Nat Word16 ds) Source # 
(PrimBytes (Array Word32 ds), (~) (TYPE WordRep) (ElemPrim WordRep (Array Word32 ds)) Word#, (~) RuntimeRep (ElemRep (Array Word32 ds)) WordRep) => PrimBytes (DataFrame Nat Word32 ds) Source # 
(PrimBytes (Array Word64 ds), (~) (TYPE WordRep) (ElemPrim WordRep (Array Word64 ds)) Word#, (~) RuntimeRep (ElemRep (Array Word64 ds)) WordRep) => PrimBytes (DataFrame Nat Word64 ds) Source # 
data DataFrame Nat Source #

Completely fixed at compile time

data DataFrame Nat = KnownDataFrame {}
data DataFrame XNat Source #

Partially known at compile time

type ElemPrim IntRep (DataFrame k Int64 ds) Source # 
type ElemPrim IntRep (DataFrame k Int32 ds) Source # 
type ElemPrim IntRep (DataFrame k Int16 ds) Source # 
type ElemPrim IntRep (DataFrame k Int8 ds) Source # 
type ElemPrim IntRep (DataFrame k Int ds) Source # 
type ElemPrim WordRep (DataFrame k Word64 ds) Source # 
type ElemPrim WordRep (DataFrame k Word32 ds) Source # 
type ElemPrim WordRep (DataFrame k Word16 ds) Source # 
type ElemPrim WordRep (DataFrame k Word8 ds) Source # 
type ElemPrim WordRep (DataFrame k Word ds) Source # 
type ElemPrim FloatRep (DataFrame k Float ds) Source # 
type ElemPrim DoubleRep (DataFrame k Double ds) Source # 
type Item (DataFrame XNat t ((:) XNat x xns')) # 
type Item (DataFrame XNat t ((:) XNat x xns')) = DataFrame Nat t (AsDims (Init XNat ((:) XNat x xns')))
type ElemRep (DataFrame Nat t xs) Source # 
type ElemRep (DataFrame Nat t xs)

type NumericFrame t ds = (CommonOpFrame t ds, NumericVariantFrame t ds) Source #

Allow all numeric operations depending on element type

Utility type families and constraints

type FPFRame t ds = (Fractional (DataFrame t ds), Floating (DataFrame t ds)) Source #

Allow floating-point operations on data frames

type IntegralFrame t ds = Bounded (DataFrame t ds) Source #

Allow some integer-like operations on data frames

type CommonOpFrame t ds = (Show (DataFrame t ds), Eq (DataFrame t ds), Ord (DataFrame t ds), Num (DataFrame t ds), ElementWise (Idx ds) t (DataFrame t ds), PrimBytes (DataFrame t ds), ArrayInstanceInference t ds, KnownDims ds, FiniteList ds, Dimensions ds) Source #

Allow all common operations on data frames

Simplified type aliases

Functionality

class (ConcatList as bs asbs, Dimensions as, Dimensions bs, Dimensions asbs) => SubSpace t as bs asbs | asbs as -> bs, asbs bs -> as, as bs -> asbs where Source #

Operations on DataFrames

as is an element dimensionality

bs is an indexing dimensionality

t is an underlying data type (i.e. Float, Int, Double)

Methods

indexOffset# :: Int# -> Int# -> DataFrame t asbs -> DataFrame t as Source #

Unsafely get a sub-dataframe by its primitive element subset. The offset is not checked to be aligned to the space structure or for bounds. Arguments are zero-based element offset and element size (aka totalDim of sub dataframe)

Normal indexing can be expressed in terms of indexOffset#:

i !. x = case (# dimVal (dim @as), fromEnum i #) of (# I# n, I# j #) -> indexOffset# (n *# j) n x

(!.) :: Idx bs -> DataFrame t asbs -> DataFrame t as infixr 4 Source #

Get an element by its index in the dataframe

update :: Idx bs -> DataFrame t as -> DataFrame t asbs -> DataFrame t asbs Source #

Set a new value to an element

ewmap :: forall s as' asbs'. SubSpace s as' bs asbs' => (DataFrame s as' -> DataFrame t as) -> DataFrame s asbs' -> DataFrame t asbs Source #

Map a function over each element of DataFrame

iwmap :: forall s as' asbs'. SubSpace s as' bs asbs' => (Idx bs -> DataFrame s as' -> DataFrame t as) -> DataFrame s asbs' -> DataFrame t asbs Source #

Map a function over each element with its index of DataFrame

ewgen :: DataFrame t as -> DataFrame t asbs Source #

Generate a DataFrame by repeating an element

iwgen :: (Idx bs -> DataFrame t as) -> DataFrame t asbs Source #

Generate a DataFrame by iterating a function (index -> element)

ewfoldl :: (b -> DataFrame t as -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative fold of a DataFrame. The fold is strict, so accumulater is evaluated to WHNF; but you'd better make sure that the function is strict enough to not produce memory leaks deeply inside the result data type.

iwfoldl :: (Idx bs -> b -> DataFrame t as -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative fold of a DataFrame with an index The fold is strict, so accumulater is evaluated to WHNF; but you'd better make sure that the function is strict enough to not produce memory leaks deeply inside the result data type.

ewfoldr :: (DataFrame t as -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative fold of a DataFrame The fold is strict, so accumulater is evaluated to WHNF; but you'd better make sure that the function is strict enough to not produce memory leaks deeply inside the result data type.

iwfoldr :: (Idx bs -> DataFrame t as -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative fold of a DataFrame with an index The fold is strict, so accumulater is evaluated to WHNF; but you'd better make sure that the function is strict enough to not produce memory leaks deeply inside the result data type.

elementWise :: forall s as' asbs' f. (Applicative f, SubSpace s as' bs asbs') => (DataFrame s as' -> f (DataFrame t as)) -> DataFrame s asbs' -> f (DataFrame t asbs) Source #

Apply an applicative functor on each element (Lens-like traversal)

indexWise :: forall s as' asbs' f. (Applicative f, SubSpace s as' bs asbs') => (Idx bs -> DataFrame s as' -> f (DataFrame t as)) -> DataFrame s asbs' -> f (DataFrame t asbs) Source #

Apply an applicative functor on each element with its index (Lens-like indexed traversal)

Instances

(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs, Dimensions asbs, PrimBytes (DataFrame Nat t as), PrimBytes (DataFrame Nat t asbs), (~) [Nat] as ((:) Nat a'' as''), (~) [Nat] asbs ((:) Nat a'' asbs'')) => SubSpace t as bs asbs Source # 

Methods

indexOffset# :: Int# -> Int# -> DataFrame Nat t asbs -> DataFrame Nat t as Source #

(!.) :: Idx bs -> DataFrame Nat t asbs -> DataFrame Nat t as Source #

update :: Idx bs -> DataFrame Nat t as -> DataFrame Nat t asbs -> DataFrame Nat t asbs Source #

ewmap :: SubSpace s as' bs asbs' => (DataFrame Nat s as' -> DataFrame Nat t as) -> DataFrame Nat s asbs' -> DataFrame Nat t asbs Source #

iwmap :: SubSpace s as' bs asbs' => (Idx bs -> DataFrame Nat s as' -> DataFrame Nat t as) -> DataFrame Nat s asbs' -> DataFrame Nat t asbs Source #

ewgen :: DataFrame Nat t as -> DataFrame Nat t asbs Source #

iwgen :: (Idx bs -> DataFrame Nat t as) -> DataFrame Nat t asbs Source #

ewfoldl :: (b -> DataFrame Nat t as -> b) -> b -> DataFrame Nat t asbs -> b Source #

iwfoldl :: (Idx bs -> b -> DataFrame Nat t as -> b) -> b -> DataFrame Nat t asbs -> b Source #

ewfoldr :: (DataFrame Nat t as -> b -> b) -> b -> DataFrame Nat t asbs -> b Source #

iwfoldr :: (Idx bs -> DataFrame Nat t as -> b -> b) -> b -> DataFrame Nat t asbs -> b Source #

elementWise :: (Applicative f, SubSpace s as' bs asbs') => (DataFrame Nat s as' -> f (DataFrame Nat t as)) -> DataFrame Nat s asbs' -> f (DataFrame Nat t asbs) Source #

indexWise :: (Applicative f, SubSpace s as' bs asbs') => (Idx bs -> DataFrame Nat s as' -> f (DataFrame Nat t as)) -> DataFrame Nat s asbs' -> f (DataFrame Nat t asbs) Source #

(Dimensions bs, ElementWise (Idx bs) t (DataFrame Nat t bs), PrimBytes (DataFrame Nat t bs)) => SubSpace t ([] Nat) bs bs Source #

Specialized instance of SubSpace for operating on scalars.

Methods

indexOffset# :: Int# -> Int# -> DataFrame Nat t bs -> DataFrame Nat t [Nat] Source #

(!.) :: Idx bs -> DataFrame Nat t bs -> DataFrame Nat t [Nat] Source #

update :: Idx bs -> DataFrame Nat t [Nat] -> DataFrame Nat t bs -> DataFrame Nat t bs Source #

ewmap :: SubSpace s as' bs asbs' => (DataFrame Nat s as' -> DataFrame Nat t [Nat]) -> DataFrame Nat s asbs' -> DataFrame Nat t bs Source #

iwmap :: SubSpace s as' bs asbs' => (Idx bs -> DataFrame Nat s as' -> DataFrame Nat t [Nat]) -> DataFrame Nat s asbs' -> DataFrame Nat t bs Source #

ewgen :: DataFrame Nat t [Nat] -> DataFrame Nat t bs Source #

iwgen :: (Idx bs -> DataFrame Nat t [Nat]) -> DataFrame Nat t bs Source #

ewfoldl :: (b -> DataFrame Nat t [Nat] -> b) -> b -> DataFrame Nat t bs -> b Source #

iwfoldl :: (Idx bs -> b -> DataFrame Nat t [Nat] -> b) -> b -> DataFrame Nat t bs -> b Source #

ewfoldr :: (DataFrame Nat t [Nat] -> b -> b) -> b -> DataFrame Nat t bs -> b Source #

iwfoldr :: (Idx bs -> DataFrame Nat t [Nat] -> b -> b) -> b -> DataFrame Nat t bs -> b Source #

elementWise :: (Applicative f, SubSpace s as' bs asbs') => (DataFrame Nat s as' -> f (DataFrame Nat t [Nat])) -> DataFrame Nat s asbs' -> f (DataFrame Nat t bs) Source #

indexWise :: (Applicative f, SubSpace s as' bs asbs') => (Idx bs -> DataFrame Nat s as' -> f (DataFrame Nat t [Nat])) -> DataFrame Nat s asbs' -> f (DataFrame Nat t bs) Source #

(!) :: SubSpace t (as :: [Nat]) (bs :: [Nat]) (asbs :: [Nat]) => DataFrame t asbs -> Idx bs -> DataFrame t as infixl 4 Source #

Index an element (reverse of !.)

element :: forall t as bs asbs f. (SubSpace t as bs asbs, Applicative f) => Idx bs -> (DataFrame t as -> f (DataFrame t as)) -> DataFrame t asbs -> f (DataFrame t asbs) Source #

Apply a functor over a single element (simple lens)

ewfoldMap :: forall t as bs asbs m. (Monoid m, SubSpace t as bs asbs) => (DataFrame t as -> m) -> DataFrame t asbs -> m Source #

iwfoldMap :: forall t as bs asbs m. (Monoid m, SubSpace t as bs asbs) => (Idx bs -> DataFrame t as -> m) -> DataFrame t asbs -> m Source #

ewzip :: forall t as bs asbs s as' asbs' r as'' asbs''. (SubSpace t as bs asbs, SubSpace s as' bs asbs', SubSpace r as'' bs asbs'') => (DataFrame t as -> DataFrame s as' -> DataFrame r as'') -> DataFrame t asbs -> DataFrame s asbs' -> DataFrame r asbs'' Source #

Zip two spaces on a specified subspace element-wise (without index)

iwzip :: forall t as bs asbs s as' asbs' r as'' asbs''. (SubSpace t as bs asbs, SubSpace s as' bs asbs', SubSpace r as'' bs asbs'') => (Idx bs -> DataFrame t as -> DataFrame s as' -> DataFrame r as'') -> DataFrame t asbs -> DataFrame s asbs' -> DataFrame r asbs'' Source #

Zip two spaces on a specified subspace index-wise (with index)

class ConcatList as bs asbs => Contraction t as bs asbs | asbs as -> bs, asbs bs -> as, as bs -> asbs where Source #

Minimal complete definition

contract

Methods

contract :: (KnownDim m, PrimBytes (DataFrame t (as +: m)), PrimBytes (DataFrame t (m :+ bs)), PrimBytes (DataFrame t asbs)) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t asbs Source #

Generalization of a matrix product: take scalar product over one dimension and, thus, concatenate other dimesnions

Instances

(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Double as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Float as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Int as bs asbs Source # 

Methods

contract :: (KnownDim m, PrimBytes (DataFrame Nat Int ((Nat +: as) m)), PrimBytes (DataFrame Nat Int ((Nat :+ m) bs)), PrimBytes (DataFrame Nat Int asbs)) => DataFrame Nat Int ((Nat +: as) m) -> DataFrame Nat Int ((Nat :+ m) bs) -> DataFrame Nat Int asbs Source #

(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Int8 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Int16 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Int32 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Int64 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Word as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Word8 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Word16 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Word32 as bs asbs Source # 
(ConcatList Nat as bs asbs, Dimensions as, Dimensions bs) => Contraction Word64 as bs asbs Source # 

(%*) :: (ConcatList as bs (as ++ bs), Contraction t as bs asbs, KnownDim m, PrimBytes (DataFrame t (as +: m)), PrimBytes (DataFrame t (m :+ bs)), PrimBytes (DataFrame t (as ++ bs))) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t (as ++ bs) infixl 7 Source #

Tensor contraction. In particular: 1. matrix-matrix product 2. matrix-vector or vector-matrix product 3. dot product of two vectors.

type PrimBytesEvidence t ds = Evidence (PrimBytes (DataFrame t ds)) Source #

Evidence for PrimBytes class

inferPrimBytes :: forall t ds. (ArrayInstanceInference t ds, Dimensions ds) => PrimBytesEvidence t ds Source #

type ElementWiseEvidence t ds = Evidence (ElementWise (Idx ds) t (DataFrame t ds)) Source #

Evidence for ElementWise class

inferElementWise :: forall t ds. (ArrayInstanceInference t ds, Dimensions ds) => ElementWiseEvidence t ds Source #

type NumericFrameEvidence t ds = Evidence (NumericFrame t ds) Source #

Allow all common operations on available data frames

inferNumericFrame :: forall t ds. (ArrayInstanceInference t ds, Dimensions ds) => NumericFrameEvidence t ds Source #

(<:>) :: forall n m npm ds t. (PrimBytes (DataFrame t (ds +: n)), PrimBytes (DataFrame t (ds +: m)), PrimBytes (DataFrame t (ds +: npm)), npm ~ (n + m), n ~ (npm - m), m ~ (npm - n)) => DataFrame t (ds +: n) -> DataFrame t (ds +: m) -> DataFrame t (ds +: npm) infixl 5 Source #

Append one DataFrame to another, adding up their last dimensionality

(<::>) :: forall ds t. (PrimBytes (DataFrame t ds), PrimBytes (DataFrame t ds), PrimBytes (DataFrame t (ds +: 2 :: [Nat]))) => DataFrame t ds -> DataFrame t ds -> DataFrame t (ds +: 2 :: [Nat]) infixl 5 Source #

Append one DataFrame to another, adding up their last dimensionality

(<+:>) :: forall ds n m t. (PrimBytes (DataFrame t (ds +: n)), PrimBytes (DataFrame t ds), PrimBytes (DataFrame t (ds +: m)), m ~ (n + 1)) => DataFrame t (ds +: n) -> DataFrame t ds -> DataFrame t (ds +: m) infixl 5 Source #

Append one DataFrame to another, adding up their last dimensionality

fromList :: forall ns t xns xnsm. (ns ~ AsDims xns, xnsm ~ (xns +: XN 2), PrimBytes (DataFrame t ns), Dimensions ns, ArrayInstanceInference t ns) => [DataFrame t ns] -> DataFrame t (xns +: XN 2) Source #

Input must be parametrized by [Nat] to make sure every element in the input list has the same dimensionality. Output is in [XNat], because the last dimension is unknown at compile time

class DataFrameToList t z ds where Source #

Implement function toList. We need to create a dedicated type class for this to make it polymorphic over kind k (Nat - XNat).

Minimal complete definition

toList

Methods

toList :: DataFrame t (ds +: z) -> [DataFrame t ds] Source #

Unwrap the last dimension of a DataFrame into a list of smaller frames

Instances

(Dimensions ns, Dimensions ((+:) Nat ns z), PrimBytes (DataFrame Nat t ns), PrimBytes (DataFrame Nat t ((+:) Nat ns z))) => DataFrameToList Nat t z ns Source # 

Methods

toList :: DataFrame t z ((t +: ds) ns) -> [DataFrame t z ds] Source #

DataFrameToList XNat t xz xns Source # 

Methods

toList :: DataFrame t xz ((t +: ds) xns) -> [DataFrame t xz ds] Source #

fromScalar :: ElementWise (Idx ds) t (DataFrame t ds) => Scalar t -> DataFrame t ds Source #

Broadcast scalar value onto a whole data frame

class ElementWise i x t | t -> x i Source #

Access elements. i is an index type x is an element t is a container type

Minimal complete definition

indexOffset#, (!), ewmap, ewgen, ewgenA, ewfoldl, ewfoldr, elementWise, indexWise, broadcast, update

Instances

ElementWise Int Double Double Source # 

Methods

indexOffset# :: Double -> Int# -> Double

(!) :: Double -> Int -> Double

ewmap :: (Int -> Double -> Double) -> Double -> Double

ewgen :: (Int -> Double) -> Double

ewgenA :: Applicative f => (Int -> f Double) -> f Double

ewfoldl :: (Int -> a -> Double -> a) -> a -> Double -> a

ewfoldr :: (Int -> Double -> a -> a) -> a -> Double -> a

elementWise :: Applicative f => (Double -> f Double) -> Double -> f Double

indexWise :: Applicative f => (Int -> Double -> f Double) -> Double -> f Double

broadcast :: Double -> Double

update :: Int -> Double -> Double -> Double

ElementWise Int Float Float Source # 

Methods

indexOffset# :: Float -> Int# -> Float

(!) :: Float -> Int -> Float

ewmap :: (Int -> Float -> Float) -> Float -> Float

ewgen :: (Int -> Float) -> Float

ewgenA :: Applicative f => (Int -> f Float) -> f Float

ewfoldl :: (Int -> a -> Float -> a) -> a -> Float -> a

ewfoldr :: (Int -> Float -> a -> a) -> a -> Float -> a

elementWise :: Applicative f => (Float -> f Float) -> Float -> f Float

indexWise :: Applicative f => (Int -> Float -> f Float) -> Float -> f Float

broadcast :: Float -> Float

update :: Int -> Float -> Float -> Float

ElementWise Int Int Int Source # 

Methods

indexOffset# :: Int -> Int# -> Int

(!) :: Int -> Int -> Int

ewmap :: (Int -> Int -> Int) -> Int -> Int

ewgen :: (Int -> Int) -> Int

ewgenA :: Applicative f => (Int -> f Int) -> f Int

ewfoldl :: (Int -> a -> Int -> a) -> a -> Int -> a

ewfoldr :: (Int -> Int -> a -> a) -> a -> Int -> a

elementWise :: Applicative f => (Int -> f Int) -> Int -> f Int

indexWise :: Applicative f => (Int -> Int -> f Int) -> Int -> f Int

broadcast :: Int -> Int

update :: Int -> Int -> Int -> Int

ElementWise Int Int8 Int8 Source # 

Methods

indexOffset# :: Int8 -> Int# -> Int8

(!) :: Int8 -> Int -> Int8

ewmap :: (Int -> Int8 -> Int8) -> Int8 -> Int8

ewgen :: (Int -> Int8) -> Int8

ewgenA :: Applicative f => (Int -> f Int8) -> f Int8

ewfoldl :: (Int -> a -> Int8 -> a) -> a -> Int8 -> a

ewfoldr :: (Int -> Int8 -> a -> a) -> a -> Int8 -> a

elementWise :: Applicative f => (Int8 -> f Int8) -> Int8 -> f Int8

indexWise :: Applicative f => (Int -> Int8 -> f Int8) -> Int8 -> f Int8

broadcast :: Int8 -> Int8

update :: Int -> Int8 -> Int8 -> Int8

ElementWise Int Int16 Int16 Source # 

Methods

indexOffset# :: Int16 -> Int# -> Int16

(!) :: Int16 -> Int -> Int16

ewmap :: (Int -> Int16 -> Int16) -> Int16 -> Int16

ewgen :: (Int -> Int16) -> Int16

ewgenA :: Applicative f => (Int -> f Int16) -> f Int16

ewfoldl :: (Int -> a -> Int16 -> a) -> a -> Int16 -> a

ewfoldr :: (Int -> Int16 -> a -> a) -> a -> Int16 -> a

elementWise :: Applicative f => (Int16 -> f Int16) -> Int16 -> f Int16

indexWise :: Applicative f => (Int -> Int16 -> f Int16) -> Int16 -> f Int16

broadcast :: Int16 -> Int16

update :: Int -> Int16 -> Int16 -> Int16

ElementWise Int Int32 Int32 Source # 

Methods

indexOffset# :: Int32 -> Int# -> Int32

(!) :: Int32 -> Int -> Int32

ewmap :: (Int -> Int32 -> Int32) -> Int32 -> Int32

ewgen :: (Int -> Int32) -> Int32

ewgenA :: Applicative f => (Int -> f Int32) -> f Int32

ewfoldl :: (Int -> a -> Int32 -> a) -> a -> Int32 -> a

ewfoldr :: (Int -> Int32 -> a -> a) -> a -> Int32 -> a

elementWise :: Applicative f => (Int32 -> f Int32) -> Int32 -> f Int32

indexWise :: Applicative f => (Int -> Int32 -> f Int32) -> Int32 -> f Int32

broadcast :: Int32 -> Int32

update :: Int -> Int32 -> Int32 -> Int32

ElementWise Int Int64 Int64 Source # 

Methods

indexOffset# :: Int64 -> Int# -> Int64

(!) :: Int64 -> Int -> Int64

ewmap :: (Int -> Int64 -> Int64) -> Int64 -> Int64

ewgen :: (Int -> Int64) -> Int64

ewgenA :: Applicative f => (Int -> f Int64) -> f Int64

ewfoldl :: (Int -> a -> Int64 -> a) -> a -> Int64 -> a

ewfoldr :: (Int -> Int64 -> a -> a) -> a -> Int64 -> a

elementWise :: Applicative f => (Int64 -> f Int64) -> Int64 -> f Int64

indexWise :: Applicative f => (Int -> Int64 -> f Int64) -> Int64 -> f Int64

broadcast :: Int64 -> Int64

update :: Int -> Int64 -> Int64 -> Int64

ElementWise Int Word Word Source # 

Methods

indexOffset# :: Word -> Int# -> Word

(!) :: Word -> Int -> Word

ewmap :: (Int -> Word -> Word) -> Word -> Word

ewgen :: (Int -> Word) -> Word

ewgenA :: Applicative f => (Int -> f Word) -> f Word

ewfoldl :: (Int -> a -> Word -> a) -> a -> Word -> a

ewfoldr :: (Int -> Word -> a -> a) -> a -> Word -> a

elementWise :: Applicative f => (Word -> f Word) -> Word -> f Word

indexWise :: Applicative f => (Int -> Word -> f Word) -> Word -> f Word

broadcast :: Word -> Word

update :: Int -> Word -> Word -> Word

ElementWise Int Word8 Word8 Source # 

Methods

indexOffset# :: Word8 -> Int# -> Word8

(!) :: Word8 -> Int -> Word8

ewmap :: (Int -> Word8 -> Word8) -> Word8 -> Word8

ewgen :: (Int -> Word8) -> Word8

ewgenA :: Applicative f => (Int -> f Word8) -> f Word8

ewfoldl :: (Int -> a -> Word8 -> a) -> a -> Word8 -> a

ewfoldr :: (Int -> Word8 -> a -> a) -> a -> Word8 -> a

elementWise :: Applicative f => (Word8 -> f Word8) -> Word8 -> f Word8

indexWise :: Applicative f => (Int -> Word8 -> f Word8) -> Word8 -> f Word8

broadcast :: Word8 -> Word8

update :: Int -> Word8 -> Word8 -> Word8

ElementWise Int Word16 Word16 Source # 

Methods

indexOffset# :: Word16 -> Int# -> Word16

(!) :: Word16 -> Int -> Word16

ewmap :: (Int -> Word16 -> Word16) -> Word16 -> Word16

ewgen :: (Int -> Word16) -> Word16

ewgenA :: Applicative f => (Int -> f Word16) -> f Word16

ewfoldl :: (Int -> a -> Word16 -> a) -> a -> Word16 -> a

ewfoldr :: (Int -> Word16 -> a -> a) -> a -> Word16 -> a

elementWise :: Applicative f => (Word16 -> f Word16) -> Word16 -> f Word16

indexWise :: Applicative f => (Int -> Word16 -> f Word16) -> Word16 -> f Word16

broadcast :: Word16 -> Word16

update :: Int -> Word16 -> Word16 -> Word16

ElementWise Int Word32 Word32 Source # 

Methods

indexOffset# :: Word32 -> Int# -> Word32

(!) :: Word32 -> Int -> Word32

ewmap :: (Int -> Word32 -> Word32) -> Word32 -> Word32

ewgen :: (Int -> Word32) -> Word32

ewgenA :: Applicative f => (Int -> f Word32) -> f Word32

ewfoldl :: (Int -> a -> Word32 -> a) -> a -> Word32 -> a

ewfoldr :: (Int -> Word32 -> a -> a) -> a -> Word32 -> a

elementWise :: Applicative f => (Word32 -> f Word32) -> Word32 -> f Word32

indexWise :: Applicative f => (Int -> Word32 -> f Word32) -> Word32 -> f Word32

broadcast :: Word32 -> Word32

update :: Int -> Word32 -> Word32 -> Word32

ElementWise Int Word64 Word64 Source # 

Methods

indexOffset# :: Word64 -> Int# -> Word64

(!) :: Word64 -> Int -> Word64

ewmap :: (Int -> Word64 -> Word64) -> Word64 -> Word64

ewgen :: (Int -> Word64) -> Word64

ewgenA :: Applicative f => (Int -> f Word64) -> f Word64

ewfoldl :: (Int -> a -> Word64 -> a) -> a -> Word64 -> a

ewfoldr :: (Int -> Word64 -> a -> a) -> a -> Word64 -> a

elementWise :: Applicative f => (Word64 -> f Word64) -> Word64 -> f Word64

indexWise :: Applicative f => (Int -> Word64 -> f Word64) -> Word64 -> f Word64

broadcast :: Word64 -> Word64

update :: Int -> Word64 -> Word64 -> Word64

(Dimensions ds, ElementWise (Idx ds) t (Array t ds)) => ElementWise (Idx ds) t (DataFrame Nat t ds) Source # 

Methods

indexOffset# :: DataFrame Nat t ds -> Int# -> t

(!) :: DataFrame Nat t ds -> Idx ds -> t

ewmap :: (Idx ds -> t -> t) -> DataFrame Nat t ds -> DataFrame Nat t ds

ewgen :: (Idx ds -> t) -> DataFrame Nat t ds

ewgenA :: Applicative f => (Idx ds -> f t) -> f (DataFrame Nat t ds)

ewfoldl :: (Idx ds -> a -> t -> a) -> a -> DataFrame Nat t ds -> a

ewfoldr :: (Idx ds -> t -> a -> a) -> a -> DataFrame Nat t ds -> a

elementWise :: Applicative f => (t -> f t) -> DataFrame Nat t ds -> f (DataFrame Nat t ds)

indexWise :: Applicative f => (Idx ds -> t -> f t) -> DataFrame Nat t ds -> f (DataFrame Nat t ds)

broadcast :: t -> DataFrame Nat t ds

update :: Idx ds -> t -> DataFrame Nat t ds -> DataFrame Nat t ds

type ArrayInstanceEvidence t ds = Evidence (ArrayInstanceInference t ds) Source #

A singleton type used to prove that the given Array family instance has a known instance

data ArrayInstance t ds Source #

Keep information about the instance behind Array family

Warning! This part of the code is platform and flag dependent.

Constructors

(Array t ds ~ Scalar t, ds ~ '[]) => AIScalar 
(Array t ds ~ ArrayF ds, ds ~ (n ': ns), t ~ Float) => AIArrayF 
(Array t ds ~ ArrayD ds, ds ~ (n ': ns), t ~ Double) => AIArrayD 
(Array t ds ~ ArrayI ds, ds ~ (n ': ns), t ~ Int) => AIArrayI 
(Array t ds ~ ArrayI8 ds, ds ~ (n ': ns), t ~ Int8) => AIArrayI8 
(Array t ds ~ ArrayI16 ds, ds ~ (n ': ns), t ~ Int16) => AIArrayI16 
(Array t ds ~ ArrayI32 ds, ds ~ (n ': ns), t ~ Int32) => AIArrayI32 
(Array t ds ~ ArrayI64 ds, ds ~ (n ': ns), t ~ Int64) => AIArrayI64 
(Array t ds ~ ArrayW ds, ds ~ (n ': ns), t ~ Word) => AIArrayW 
(Array t ds ~ ArrayW8 ds, ds ~ (n ': ns), t ~ Word8) => AIArrayW8 
(Array t ds ~ ArrayW16 ds, ds ~ (n ': ns), t ~ Word16) => AIArrayW16 
(Array t ds ~ ArrayW32 ds, ds ~ (n ': ns), t ~ Word32) => AIArrayW32 
(Array t ds ~ ArrayW64 ds, ds ~ (n ': ns), t ~ Word64) => AIArrayW64 
(Array t ds ~ FloatX2, ds ~ '[2], t ~ Float) => AIFloatX2 
(Array t ds ~ FloatX3, ds ~ '[3], t ~ Float) => AIFloatX3 
(Array t ds ~ FloatX4, ds ~ '[4], t ~ Float) => AIFloatX4 

getArrayInstance :: forall t ds. ArrayInstanceInference t ds => ArrayInstance t ds Source #

inferArrayInstance :: forall t ds. (FiniteList ds, KnownDims ds, ElemTypeInference t) => ArrayInstanceEvidence t ds Source #

Given element type instance and proper dimension list, infer a corresponding array instance

class ArraySizeInference ds where Source #

Methods

arraySizeInstance :: ArraySize ds Source #

Pattern match agains result to get actual array dimensionality

inferSnocArrayInstance :: (ElemTypeInference t, KnownDim z) => p t ds -> q z -> ArrayInstanceEvidence t (ds +: z) Source #

inferConsArrayInstance :: (ElemTypeInference t, KnownDim z) => q z -> p t ds -> ArrayInstanceEvidence t (z :+ ds) Source #

inferInitArrayInstance :: ElemTypeInference t => p t ds -> ArrayInstanceEvidence t (Init ds) Source #

Instances

ArraySizeInference ([] Nat) Source # 
ArraySizeInference ((:) Nat d1 ((:) Nat d2 ((:) Nat d3 ds))) Source # 

Methods

arraySizeInstance :: ArraySize ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds))) Source #

inferSnocArrayInstance :: (ElemTypeInference t, KnownDim z) => p t ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds))) -> q z -> ArrayInstanceEvidence t ((Nat +: (Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds))) z) Source #

inferConsArrayInstance :: (ElemTypeInference t, KnownDim z) => q z -> p t ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds))) -> ArrayInstanceEvidence t ((Nat :+ z) ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds)))) Source #

inferInitArrayInstance :: ElemTypeInference t => p t ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds))) -> ArrayInstanceEvidence t (Init Nat ((Nat ': d1) ((Nat ': d2) ((Nat ': d3) ds)))) Source #

KnownDim d1 => ArraySizeInference ((:) Nat d1 ((:) Nat d2 ([] Nat))) Source # 

Methods

arraySizeInstance :: ArraySize ((Nat ': d1) ((Nat ': d2) [Nat])) Source #

inferSnocArrayInstance :: (ElemTypeInference t, KnownDim z) => p t ((Nat ': d1) ((Nat ': d2) [Nat])) -> q z -> ArrayInstanceEvidence t ((Nat +: (Nat ': d1) ((Nat ': d2) [Nat])) z) Source #

inferConsArrayInstance :: (ElemTypeInference t, KnownDim z) => q z -> p t ((Nat ': d1) ((Nat ': d2) [Nat])) -> ArrayInstanceEvidence t ((Nat :+ z) ((Nat ': d1) ((Nat ': d2) [Nat]))) Source #

inferInitArrayInstance :: ElemTypeInference t => p t ((Nat ': d1) ((Nat ': d2) [Nat])) -> ArrayInstanceEvidence t (Init Nat ((Nat ': d1) ((Nat ': d2) [Nat]))) Source #

KnownDim d => ArraySizeInference ((:) Nat d ([] Nat)) Source # 

Methods

arraySizeInstance :: ArraySize ((Nat ': d) [Nat]) Source #

inferSnocArrayInstance :: (ElemTypeInference t, KnownDim z) => p t ((Nat ': d) [Nat]) -> q z -> ArrayInstanceEvidence t ((Nat +: (Nat ': d) [Nat]) z) Source #

inferConsArrayInstance :: (ElemTypeInference t, KnownDim z) => q z -> p t ((Nat ': d) [Nat]) -> ArrayInstanceEvidence t ((Nat :+ z) ((Nat ': d) [Nat])) Source #

inferInitArrayInstance :: ElemTypeInference t => p t ((Nat ': d) [Nat]) -> ArrayInstanceEvidence t (Init Nat ((Nat ': d) [Nat])) Source #

data ArraySize ds Source #

Keep information about the array dimensionality

Warning! This part of the code is platform and flag dependent.

Constructors

(ds ~ '[]) => ASScalar 
(ds ~ '[2]) => ASX2 
(ds ~ '[3]) => ASX3 
(ds ~ '[4]) => ASX4 
(ds ~ '[n], 5 <= n) => ASXN 
(ds ~ (n1 ': (n2 ': ns))) => ASArray 

data ElemType t Source #

Keep information about the element type instance.

Warning! This part of the code is platform and flag dependent.

Constructors

(t ~ Float) => ETFloat 
(t ~ Double) => ETDouble 
(t ~ Int) => ETInt 
(t ~ Int8) => ETInt8 
(t ~ Int16) => ETInt16 
(t ~ Int32) => ETInt32 
(t ~ Int64) => ETInt64 
(t ~ Word) => ETWord 
(t ~ Word8) => ETWord8 
(t ~ Word16) => ETWord16 
(t ~ Word32) => ETWord32 
(t ~ Word64) => ETWord64