multilinear-0.4.0.0: Comprehensive and efficient (multi)linear algebra implementation.

Copyright(c) Artur M. Brodzki 2018
LicenseBSD3
Maintainerartur@brodzki.org
Stabilityexperimental
PortabilityWindows/POSIX
Safe HaskellNone
LanguageHaskell2010

Multilinear.Generic.Sequential

Contents

Description

 
Synopsis

Generic tensor datatype and its instances

data Tensor a where Source #

Tensor defined recursively as scalar or list of other tensors

c is type of a container, i is type of index size and a is type of tensor elements

Constructors

Scalar

Scalar

Fields

SimpleFinite

Simple, one-dimensional finite tensor

Fields

FiniteTensor

Finite array of other tensors

Fields

Instances
Unbox a => Multilinear Tensor a Source # 
Instance details

Defined in Multilinear.Generic.Sequential

(Eq a, Unbox a) => Eq (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic.Sequential

Methods

(==) :: Tensor a -> Tensor a -> Bool #

(/=) :: Tensor a -> Tensor a -> Bool #

(Unbox a, Floating a, NFData a) => Floating (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic.Sequential

Methods

pi :: Tensor a #

exp :: Tensor a -> Tensor a #

log :: Tensor a -> Tensor a #

sqrt :: Tensor a -> Tensor a #

(**) :: Tensor a -> Tensor a -> Tensor a #

logBase :: Tensor a -> Tensor a -> Tensor a #

sin :: Tensor a -> Tensor a #

cos :: Tensor a -> Tensor a #

tan :: Tensor a -> Tensor a #

asin :: Tensor a -> Tensor a #

acos :: Tensor a -> Tensor a #

atan :: Tensor a -> Tensor a #

sinh :: Tensor a -> Tensor a #

cosh :: Tensor a -> Tensor a #

tanh :: Tensor a -> Tensor a #

asinh :: Tensor a -> Tensor a #

acosh :: Tensor a -> Tensor a #

atanh :: Tensor a -> Tensor a #

log1p :: Tensor a -> Tensor a #

expm1 :: Tensor a -> Tensor a #

log1pexp :: Tensor a -> Tensor a #

log1mexp :: Tensor a -> Tensor a #

(Unbox a, Fractional a, NFData a) => Fractional (Tensor a) Source #

Tensors can be divided by each other

Instance details

Defined in Multilinear.Generic.Sequential

Methods

(/) :: Tensor a -> Tensor a -> Tensor a #

recip :: Tensor a -> Tensor a #

fromRational :: Rational -> Tensor a #

(Unbox a, Num a, NFData a) => Num (Tensor a) Source #

Tensors can be added, subtracted and multiplicated

Instance details

Defined in Multilinear.Generic.Sequential

Methods

(+) :: Tensor a -> Tensor a -> Tensor a #

(-) :: Tensor a -> Tensor a -> Tensor a #

(*) :: Tensor a -> Tensor a -> Tensor a #

negate :: Tensor a -> Tensor a #

abs :: Tensor a -> Tensor a #

signum :: Tensor a -> Tensor a #

fromInteger :: Integer -> Tensor a #

(Unbox a, Show a) => Show (Tensor a) Source #

Print tensor

Instance details

Defined in Multilinear.Generic.Sequential

Methods

showsPrec :: Int -> Tensor a -> ShowS #

show :: Tensor a -> String #

showList :: [Tensor a] -> ShowS #

Generic (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic.Sequential

Associated Types

type Rep (Tensor a) :: Type -> Type #

Methods

from :: Tensor a -> Rep (Tensor a) x #

to :: Rep (Tensor a) x -> Tensor a #

NFData a => NFData (Tensor a) Source #

NFData instance

Instance details

Defined in Multilinear.Generic.Sequential

Methods

rnf :: Tensor a -> () #

type Rep (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic.Sequential

type Rep (Tensor a) = D1 (MetaData "Tensor" "Multilinear.Generic.Sequential" "multilinear-0.4.0.0-4pOeX4Mdw3wCdDrdwUPw2p" False) (C1 (MetaCons "Scalar" PrefixI True) (S1 (MetaSel (Just "scalarVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: (C1 (MetaCons "SimpleFinite" PrefixI True) (S1 (MetaSel (Just "tensorFiniteIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Index) :*: S1 (MetaSel (Just "tensorScalars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector a))) :+: C1 (MetaCons "FiniteTensor" PrefixI True) (S1 (MetaSel (Just "tensorFiniteIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Index) :*: S1 (MetaSel (Just "tensorsFinite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Tensor a))))))

Auxiliary functions

(!) Source #

Arguments

:: Unbox a 
=> Tensor a

tensor t

-> Int

index i

-> Tensor a

tensor t[i]

Recursive indexing on list tensor. If index is greater than index size, performs modulo indexing t ! i = t[i]

isScalar :: Unbox a => Tensor a -> Bool Source #

Return true if tensor is a scalar

isSimple :: Unbox a => Tensor a -> Bool Source #

Return true if tensor is a simple tensor

isFiniteTensor :: Unbox a => Tensor a -> Bool Source #

Return True if tensor is a complex tensor

tensorIndex :: Unbox a => Tensor a -> TIndex Source #

Return generic tensor index

_standardize :: Unbox a => Tensor a -> Tensor a Source #

Move contravariant indices to lower recursion level

_mergeScalars :: Unbox a => Tensor a -> Tensor a Source #

Merge FiniteTensor of Scalars to SimpleFinite tensor for performance improvement

_map :: (Unbox a, Unbox b) => (a -> b) -> Tensor a -> Tensor b Source #

Generic map function, which does not require a,b types to be Num

_contractedIndices Source #

Arguments

:: Tensor Double

first tensor to contract

-> Tensor Double

second tensor to contract

-> Set String 

Contracted indices have to be consumed in result tensor.

_elemByElem Source #

Arguments

:: (Num a, Unbox a, NFData a) 
=> Tensor a

First argument of operator

-> Tensor a

Second argument of operator

-> (a -> a -> a)

Operator on tensor elements if indices are different

-> (Tensor a -> Tensor a -> Tensor a)

Tensor operator called if indices are the same

-> Tensor a

Result tensor

Apply a tensor operator elem by elem and merge scalars to simple tensor at the and

zipT Source #

Arguments

:: (Num a, NFData a, Unbox a) 
=> (a -> a -> a)

The zipping combinator

-> Tensor a

First tensor to zip

-> Tensor a

Second tensor to zip

-> Tensor a

Result tensor Two simple tensors case

Zipping two tensors with a combinator, assuming they have the same indices.

Additional functions

(.+) :: (Unbox a, Num a) => Tensor a -> a -> Tensor a Source #

(.-) :: (Unbox a, Num a) => Tensor a -> a -> Tensor a Source #

(.*) :: (Unbox a, Num a) => Tensor a -> a -> Tensor a Source #

(+.) :: (Unbox a, Num a) => a -> Tensor a -> Tensor a Source #

(-.) :: (Unbox a, Num a) => a -> Tensor a -> Tensor a Source #

(*.) :: (Unbox a, Num a) => a -> Tensor a -> Tensor a Source #

map :: (Unbox a, Unbox b) => (a -> b) -> Tensor a -> Tensor b Source #

Simple mapping

map f t returns tensor t2 in which t2[i1,i2,...] = f t[i1,i2,...]

filter Source #

Arguments

:: Unbox a 
=> (String -> Int -> Bool)

filter function

-> Tensor a

tensor to filter

-> Tensor a 

Filtering tensor. Filtering multi-dimensional arrray may be dangerous, as we always assume, that on each recursion level, all tensors have the same size (length). To disable invalid filters, filtering is done over indices, not tensor elements. Filter function takes and index name and index value and if it returns True, this index value remains in result tensor. This allows to remove whole columns or rows of eg. a matrix: filter (i n -> i = "a" || i > 10) filters all rows of "a" index (because if i = "a", filter returns True) and for "a" index filter elements with index value <= 10 But this disallow to remove particular matrix element. If for some index all elements are removed, the index itself is removed from tensor.

filterIndex Source #

Arguments

:: Unbox a 
=> String

Index name to filter

-> (Int -> Bool)

filter function

-> Tensor a

tensor to filter

-> Tensor a 

Filtering one index of tensor.

zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Tensor a -> Tensor b -> Tensor c Source #