linear-accelerate-0.4: Lifting linear vector spaces into Accelerate

Copyright2014 Edward Kmett Charles Durham
2015 Trevor L. McDonell
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Linear.Matrix

Description

Simple matrix operations for low-dimensional primitives

Synopsis

Documentation

type M22 a = V2 (V2 a) #

A 2x2 matrix with row-major representation

type M23 a = V2 (V3 a) #

A 2x3 matrix with row-major representation

type M24 a = V2 (V4 a) #

A 2x4 matrix with row-major representation

type M32 a = V3 (V2 a) #

A 3x2 matrix with row-major representation

type M33 a = V3 (V3 a) #

A 3x3 matrix with row-major representation

type M34 a = V3 (V4 a) #

A 3x4 matrix with row-major representation

type M42 a = V4 (V2 a) #

A 4x2 matrix with row-major representation

type M43 a = V4 (V3 a) #

A 4x3 matrix with row-major representation

type M44 a = V4 (V4 a) #

A 4x4 matrix with row-major representation

(!*!) :: (Functor m, Foldable t, Additive t, Additive n, Num a, Box2 m t a, Box2 t n a, Box2 m n a) => Exp (m (t a)) -> Exp (t (n a)) -> Exp (m (n a)) infixl 7 Source #

Matrix product. This can compute any combination of sparse and dense multiplication.

>>> lift (V2 (V3 1 2 3) (V3 4 5 6) :: M23 Int) !*! lift (V3 (V2 1 2) (V2 3 4) (V2 4 5) :: M32 Int)
((19,25),(43,58))

(!+!) :: (Additive m, Additive n, Num a, Box2 m n a) => Exp (m (n a)) -> Exp (m (n a)) -> Exp (m (n a)) infixl 6 Source #

Entry-wise matrix addition.

>>> lift (V2 (V3 1 2 3) (V3 4 5 6) :: M23 Int) !+! lift (V2 (V3 7 8 9) (V3 1 2 3) :: M23 Int)
((8,10,12),(5,7,9))

(!-!) :: (Additive m, Additive n, Num a, Box2 m n a) => Exp (m (n a)) -> Exp (m (n a)) -> Exp (m (n a)) infixl 6 Source #

Entry-wise matrix subtraction.

>>> lift (V2 (V3 1 2 3) (V3 4 5 6) :: M23 Int) !-! lift (V2 (V3 7 8 9) (V3 1 2 3) :: M23 Int)
((-6,-6,-6),(3,3,3))

(!*) :: (Functor m, Foldable r, Additive r, Num a, Box2 m r a, Box m a) => Exp (m (r a)) -> Exp (r a) -> Exp (m a) infixl 7 Source #

Matrix * column vector

>>> lift (V2 (V3 1 2 3) (V3 4 5 6) :: M23 Int) !* lift (V3 7 8 9 :: V3 Int)
(50,122)

(*!) :: (Foldable t, Additive f, Additive t, Num a, Box t a, Box f a, Box2 t f a) => Exp (t a) -> Exp (t (f a)) -> Exp (f a) infixl 7 Source #

Row vector * matrix

>>> lift (V2 1 2 :: V2 Int) *! lift (V2 (V3 3 4 5) (V3 6 7 8) :: M23 Int)
(15,18,21)

(!!*) :: (Functor m, Functor r, Num a, Box2 m r a) => Exp (m (r a)) -> Exp a -> Exp (m (r a)) infixl 7 Source #

Matrix-scalar product

>>> lift (V2 (V2 1 2) (V2 3 4) :: M22 Int) !!* 5
((5,10),(15,20))

(*!!) :: (Functor m, Functor r, Num a, Box2 m r a) => Exp a -> Exp (m (r a)) -> Exp (m (r a)) infixl 7 Source #

Scalar-matrix product

>>> 5 *!! lift (V2 (V2 1 2) (V2 3 4) :: M22 Int)
((5,10),(15,20))

(!!/) :: (Functor m, Functor r, Floating a, Box2 m r a) => Exp (m (r a)) -> Exp a -> Exp (m (r a)) infixl 7 Source #

Matrix-scalar division

transpose :: (Distributive g, Functor f, Box2 f g a, Box2 g f a) => Exp (f (g a)) -> Exp (g (f a)) Source #

transpose is just an alias for distribute

transpose (V3 (V2 1 2) (V2 3 4) (V2 5 6))

V2 (V3 1 3 5) (V3 2 4 6)

identity :: forall t a. (Traversable t, Applicative t, Num a, Box2 t t a) => Exp (t (t a)) Source #

The identity matrix for any dimension vector.

>>> identity :: Exp (M44 Int)
let x0 = 1 in
let x1 = 0
in ((x0,x1,x1,x1),(x1,x0,x1,x1),(x1,x1,x0,x1),(x1,x1,x1,x0))
>>> identity :: Exp (V3 (V3 Int))
let x0 = 1 in
let x1 = 0
in ((x0,x1,x1),(x1,x0,x1),(x1,x1,x0))

class Trace m => Trace m where Source #

Methods

trace :: (Num a, Box2 m m a) => Exp (m (m a)) -> Exp a Source #

Compute the trace of a matrix

diagonal :: Box2 m m a => Exp (m (m a)) -> Exp (m a) Source #

Compute the diagonal of a matrix

Instances

Trace Complex Source # 
Trace Quaternion Source # 
Trace Plucker Source # 
Trace V4 Source # 

Methods

trace :: (Num a, Box2 V4 V4 a) => Exp (V4 (V4 a)) -> Exp a Source #

diagonal :: Box2 V4 V4 a => Exp (V4 (V4 a)) -> Exp (V4 a) Source #

Trace V3 Source # 

Methods

trace :: (Num a, Box2 V3 V3 a) => Exp (V3 (V3 a)) -> Exp a Source #

diagonal :: Box2 V3 V3 a => Exp (V3 (V3 a)) -> Exp (V3 a) Source #

Trace V2 Source # 

Methods

trace :: (Num a, Box2 V2 V2 a) => Exp (V2 (V2 a)) -> Exp a Source #

diagonal :: Box2 V2 V2 a => Exp (V2 (V2 a)) -> Exp (V2 a) Source #

Trace V1 Source # 

Methods

trace :: (Num a, Box2 V1 V1 a) => Exp (V1 (V1 a)) -> Exp a Source #

diagonal :: Box2 V1 V1 a => Exp (V1 (V1 a)) -> Exp (V1 a) Source #

Trace V0 Source # 

Methods

trace :: (Num a, Box2 V0 V0 a) => Exp (V0 (V0 a)) -> Exp a Source #

diagonal :: Box2 V0 V0 a => Exp (V0 (V0 a)) -> Exp (V0 a) Source #