multilinear-0.2.2.1: 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

Description

  • This module contains generic implementation of tensor defined as nested arrays
Synopsis

Documentation

data Tensor a 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

FiniteTensor

Finite array of other tensors

Fields

InfiniteTensor

Infinite list of other tensors

Fields

Err

Operations on tensors may throw an error

Fields

Instances
Functor Tensor Source # 
Instance details

Defined in Multilinear.Generic

Methods

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

(<$) :: a -> Tensor b -> Tensor a #

Num a => Accessible Tensor a Source #

List allows for random access to tensor elements

Instance details

Defined in Multilinear.Generic

Methods

el :: Tensor a -> (String, [Int]) -> Tensor a Source #

($$|) :: Tensor a -> (String, [Int]) -> Tensor a Source #

iMap :: ([Int] -> a -> b) -> Tensor a -> Tensor b Source #

Num a => Multilinear Tensor a Source # 
Instance details

Defined in Multilinear.Generic

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

Defined in Multilinear.Generic

Methods

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

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

Floating a => Floating (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

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 #

Fractional a => Fractional (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

Methods

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

recip :: Tensor a -> Tensor a #

fromRational :: Rational -> Tensor a #

Num a => Num (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

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 #

Ord a => Ord (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

Methods

compare :: Tensor a -> Tensor a -> Ordering #

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

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

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

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

max :: Tensor a -> Tensor a -> Tensor a #

min :: Tensor a -> Tensor a -> Tensor a #

(Show a, Num a) => Show (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

Methods

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

show :: Tensor a -> String #

showList :: [Tensor a] -> ShowS #

Generic (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

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 # 
Instance details

Defined in Multilinear.Generic

Methods

rnf :: Tensor a -> () #

(Num a, Bits a) => Bits (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

Methods

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

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

xor :: Tensor a -> Tensor a -> Tensor a #

complement :: Tensor a -> Tensor a #

shift :: Tensor a -> Int -> Tensor a #

rotate :: Tensor a -> Int -> Tensor a #

zeroBits :: Tensor a #

bit :: Int -> Tensor a #

setBit :: Tensor a -> Int -> Tensor a #

clearBit :: Tensor a -> Int -> Tensor a #

complementBit :: Tensor a -> Int -> Tensor a #

testBit :: Tensor a -> Int -> Bool #

bitSizeMaybe :: Tensor a -> Maybe Int #

bitSize :: Tensor a -> Int #

isSigned :: Tensor a -> Bool #

shiftL :: Tensor a -> Int -> Tensor a #

unsafeShiftL :: Tensor a -> Int -> Tensor a #

shiftR :: Tensor a -> Int -> Tensor a #

unsafeShiftR :: Tensor a -> Int -> Tensor a #

rotateL :: Tensor a -> Int -> Tensor a #

rotateR :: Tensor a -> Int -> Tensor a #

popCount :: Tensor a -> Int #

type Rep (Tensor a) Source # 
Instance details

Defined in Multilinear.Generic

(!) Source #

Arguments

:: Tensor a

tensor t

-> Int

index i

-> Tensor a

tensor t[i]

Recursive indexing on list tensor t ! i = t[i]

mergeScalars :: Tensor a -> Tensor a Source #

Merge FiniteTensor of Scalars to SimpleFinite tensor for performance improvement

isScalar :: Tensor a -> Bool Source #

Return true if tensor is a scalar

isSimple :: Tensor a -> Bool Source #

Return true if tensor is a simple tensor

isFiniteTensor :: Tensor a -> Bool Source #

Return True if tensor is a complex tensor

isInfiniteTensor :: Tensor a -> Bool Source #

Return True if tensor is a infinite tensor

dot Source #

Arguments

:: Num a 
=> Tensor a

First dot product argument

-> Tensor a

Second dot product argument

-> Tensor a

Resulting dot product

_elemByElem Source #

Arguments

:: Num 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

contractionErr Source #

Arguments

:: TIndex

Index of first dot product parameter

-> TIndex

Index of second dot product parameter

-> Tensor a

Erorr message

tensorIndex :: Tensor a -> TIndex Source #

Return generic tensor index