easytensor-0.1.0.0: Initial project template from stack

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

Numeric.EasyTensor

Contents

Description

This module generalizes matrices and vectors. Yet it is limited to rank 2, allowing for a simple and nicely type-checked interface.

Synopsis

Documentation

data Tensor t n m Source #

Instances

Eq (TT t n m) => Eq (Tensor t n m) Source # 

Methods

(==) :: Tensor t n m -> Tensor t n m -> Bool #

(/=) :: Tensor t n m -> Tensor t n m -> Bool #

Floating (TT t n m) => Floating (Tensor t n m) Source # 

Methods

pi :: Tensor t n m #

exp :: Tensor t n m -> Tensor t n m #

log :: Tensor t n m -> Tensor t n m #

sqrt :: Tensor t n m -> Tensor t n m #

(**) :: Tensor t n m -> Tensor t n m -> Tensor t n m #

logBase :: Tensor t n m -> Tensor t n m -> Tensor t n m #

sin :: Tensor t n m -> Tensor t n m #

cos :: Tensor t n m -> Tensor t n m #

tan :: Tensor t n m -> Tensor t n m #

asin :: Tensor t n m -> Tensor t n m #

acos :: Tensor t n m -> Tensor t n m #

atan :: Tensor t n m -> Tensor t n m #

sinh :: Tensor t n m -> Tensor t n m #

cosh :: Tensor t n m -> Tensor t n m #

tanh :: Tensor t n m -> Tensor t n m #

asinh :: Tensor t n m -> Tensor t n m #

acosh :: Tensor t n m -> Tensor t n m #

atanh :: Tensor t n m -> Tensor t n m #

log1p :: Tensor t n m -> Tensor t n m #

expm1 :: Tensor t n m -> Tensor t n m #

log1pexp :: Tensor t n m -> Tensor t n m #

log1mexp :: Tensor t n m -> Tensor t n m #

Fractional (TT t n m) => Fractional (Tensor t n m) Source # 

Methods

(/) :: Tensor t n m -> Tensor t n m -> Tensor t n m #

recip :: Tensor t n m -> Tensor t n m #

fromRational :: Rational -> Tensor t n m #

Num (TT t n m) => Num (Tensor t n m) Source # 

Methods

(+) :: Tensor t n m -> Tensor t n m -> Tensor t n m #

(-) :: Tensor t n m -> Tensor t n m -> Tensor t n m #

(*) :: Tensor t n m -> Tensor t n m -> Tensor t n m #

negate :: Tensor t n m -> Tensor t n m #

abs :: Tensor t n m -> Tensor t n m #

signum :: Tensor t n m -> Tensor t n m #

fromInteger :: Integer -> Tensor t n m #

Ord (TT t n m) => Ord (Tensor t n m) Source # 

Methods

compare :: Tensor t n m -> Tensor t n m -> Ordering #

(<) :: Tensor t n m -> Tensor t n m -> Bool #

(<=) :: Tensor t n m -> Tensor t n m -> Bool #

(>) :: Tensor t n m -> Tensor t n m -> Bool #

(>=) :: Tensor t n m -> Tensor t n m -> Bool #

max :: Tensor t n m -> Tensor t n m -> Tensor t n m #

min :: Tensor t n m -> Tensor t n m -> Tensor t n m #

Show (TT t n m) => Show (Tensor t n m) Source # 

Methods

showsPrec :: Int -> Tensor t n m -> ShowS #

show :: Tensor t n m -> String #

showList :: [Tensor t n m] -> ShowS #

WordBytes (TT t n m) => WordBytes (Tensor t n m) Source # 

Methods

ixW :: Int# -> Tensor t n m -> Word# Source #

IntBytes (TT t n m) => IntBytes (Tensor t n m) Source # 

Methods

ixI :: Int# -> Tensor t n m -> Int# Source #

DoubleBytes (TT t n m) => DoubleBytes (Tensor t n m) Source # 

Methods

ixD :: Int# -> Tensor t n m -> Double# Source #

FloatBytes (TT t n m) => FloatBytes (Tensor t n m) Source # 

Methods

ixF :: Int# -> Tensor t n m -> Float# Source #

PrimBytes (TT t n m) => PrimBytes (Tensor t n m) Source # 

Common operations

fill :: MatrixCalculus t n m (Tensor t n m) => Tensor t 1 1 -> Tensor t n m Source #

Fill whole tensor with a single value

prod :: MatrixProduct (Tensor t n m) (Tensor t m k) (Tensor t n k) => Tensor t n m -> Tensor t m k -> Tensor t n k Source #

Matrix product for tensors rank 2, as well matrix-vector or vector-matrix products

(%*) :: MatrixProduct (Tensor t n m) (Tensor t m k) (Tensor t n k) => Tensor t n m -> Tensor t m k -> Tensor t n k infixl 7 Source #

Matrix product for tensors rank 2, as well matrix-vector or vector-matrix products

inverse :: MatrixInverse (Tensor t n n) => Tensor t n n -> Tensor t n n Source #

Matrix inverse

transpose :: (MatrixCalculus t n m (Tensor t n m), MatrixCalculus t m n (Tensor t m n), PrimBytes (Tensor t m n)) => Tensor t n m -> Tensor t m n Source #

(<:>) :: (PrimBytes (Tensor t k n), PrimBytes (Tensor t k m), PrimBytes (Tensor t k (n + m))) => Tensor t k n -> Tensor t k m -> Tensor t k (n + m) infixl 5 Source #

Append one vector to another, adding up their dimensionality

(//) :: (MatrixProduct (Tensor t n m) (Tensor t m m) (Tensor t n m), MatrixInverse (TT t m m)) => Tensor t n m -> Tensor t m m -> Tensor t n m Source #

Divide on the right: R = A * B^(-1)

(\\) :: (MatrixProduct (Tensor t n n) (Tensor t n m) (Tensor t n m), MatrixInverse (TT t n n)) => Tensor t n n -> Tensor t n m -> Tensor t n m Source #

Divide on the left: R = A^(-1) * b

index :: MatrixCalculus t n m (Tensor t n m) => Int -> Int -> Tensor t n m -> Tensor t 1 1 Source #

Get an element of a tensor

indexCol :: (MatrixCalculus t n m (Tensor t n m), VectorCalculus t n (Tensor t n 1), PrimBytes (Tensor t n 1)) => Int -> Tensor t n m -> Tensor t n 1 Source #

Get a column vector of a matrix

indexRow :: (MatrixCalculus t n m (Tensor t n m), VectorCalculus t m (Tensor t 1 m), PrimBytes (Tensor t 1 m)) => Int -> Tensor t n m -> Tensor t 1 m Source #

Get a row vector of a matrix

dimN :: MatrixCalculus t n m (Tensor t n m) => Tensor t n m -> Int Source #

dimM :: MatrixCalculus t n m (Tensor t n m) => Tensor t n m -> Int Source #

(.*.) :: VectorCalculus t n v => v -> v -> v Source #

Scalar product -- sum of Vecs' components products, propagated into whole Vec

dot :: VectorCalculus t n v => v -> v -> Tensor t 1 1 Source #

Dot product of two vectors

· :: VectorCalculus t n v => v -> v -> Tensor t 1 1 infixl 7 Source #

Dot product of two vectors

normL1 :: VectorCalculus t n v => v -> Tensor t 1 1 Source #

Sum of absolute values

normL2 :: VectorCalculus t n v => v -> Tensor t 1 1 Source #

hypot function (square root of squares)

normLPInf :: VectorCalculus t n v => v -> Tensor t 1 1 Source #

Maximum of absolute values

normLNInf :: VectorCalculus t n v => v -> Tensor t 1 1 Source #

Minimum of absolute values

normLP :: VectorCalculus t n v => Int -> v -> Tensor t 1 1 Source #

Norm in Lp space

eye :: SquareMatrixCalculus t n (Tensor t n n) => Tensor t n n Source #

Identity matrix. Mat with 1 on diagonal and 0 elsewhere

diag :: SquareMatrixCalculus t n (Tensor t n n) => Tensor t 1 1 -> Tensor t n n Source #

Put the same value on the Mat diagonal, 0 otherwise

det :: SquareMatrixCalculus t n (Tensor t n n) => Tensor t n n -> Tensor t 1 1 Source #

Determinant of Mat

trace :: SquareMatrixCalculus t n (Tensor t n n) => Tensor t n n -> Tensor t 1 1 Source #

Sum of diagonal elements

toDiag :: (SquareMatrixCalculus t n (Tensor t n n), VectorCalculus t n (Tensor t n 1), PrimBytes (Tensor t n 1)) => Tensor t n 1 -> Tensor t n n Source #

Set Vec values into the diagonal elements of Mat

toDiag' :: (SquareMatrixCalculus t n (Tensor t n n), VectorCalculus t n (Tensor t 1 n), PrimBytes (Tensor t 1 n)) => Tensor t 1 n -> Tensor t n n Source #

Set Vec values into the diagonal elements of Mat

fromDiag :: (SquareMatrixCalculus t n (Tensor t n n), VectorCalculus t n (Tensor t n 1), PrimBytes (Tensor t n 1)) => Tensor t n n -> Tensor t n 1 Source #

Get the diagonal elements from Mat into Vec

fromDiag' :: (SquareMatrixCalculus t n (Tensor t n n), VectorCalculus t n (Tensor t 1 n), PrimBytes (Tensor t 1 n)) => Tensor t n n -> Tensor t 1 n Source #

Get the diagonal elements from Mat into Vec

Type abbreviations

type Mat t n m = Tensor t n m Source #

type Vec t n = Tensor t n 1 Source #

type Vec' t m = Tensor t 1 m Source #

Simplified type constructors

scalar :: t -> Tensor t 1 1 Source #

vec2 :: Vector2D t => t -> t -> Tensor t 2 1 Source #

vec3 :: Vector3D t => t -> t -> t -> Tensor t 3 1 Source #

vec4 :: Vector4D t => t -> t -> t -> t -> Tensor t 4 1 Source #

vec2' :: Vector2D t => t -> t -> Tensor t 1 2 Source #

vec3' :: Vector3D t => t -> t -> t -> Tensor t 1 3 Source #

vec4' :: Vector4D t => t -> t -> t -> t -> Tensor t 1 4 Source #

mat22 :: Matrix2x2 t => Tensor t 2 1 -> Tensor t 2 1 -> Tensor t 2 2 Source #

Compose a 2x2D matrix

mat33 :: (PrimBytes (Tensor t 3 3), PrimBytes (Tensor t 3 2), PrimBytes (Tensor t 3 1)) => Tensor t 3 1 -> Tensor t 3 1 -> Tensor t 3 1 -> Tensor t 3 3 Source #

Compose a 3x3D matrix

mat44 :: (PrimBytes (Tensor t 4 4), PrimBytes (Tensor t 4 3), PrimBytes (Tensor t 4 2), PrimBytes (Tensor t 4 1)) => Tensor t 4 1 -> Tensor t 4 1 -> Tensor t 4 1 -> Tensor t 4 1 -> Tensor t 4 4 Source #

Compose a 4x4D matrix

Some low-dimensional operations

det2 :: Vector2D t => Tensor t 2 1 -> Tensor t 2 1 -> Tensor t 1 1 Source #

det2' :: Vector2D t => Tensor t 1 2 -> Tensor t 1 2 -> Tensor t 1 1 Source #

cross :: Vector3D t => Tensor t 3 1 -> Tensor t 3 1 -> Tensor t 3 1 Source #

Cross product for two vectors in 3D

(×) :: Vector3D t => Tensor t 3 1 -> Tensor t 3 1 -> Tensor t 3 1 infixl 7 Source #

Cross product for two vectors in 3D