exp-pairs-0.2.0.0: Linear programming over exponent pairs

Copyright(c) Andrew Lelechenko 2014-2015
LicenseGPL-3
Maintainerandrew.lelechenko@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Math.ExpPairs.Matrix3

Description

Provides types and functions for matrices and vectors of order 3. Can be used instead of Data.Matrix to reduce overhead and simplify code.

Synopsis

Documentation

data Matrix3 t Source #

Matrix of order 3. Instances of Num and Fractional are given in terms of the multiplicative group of matrices, not the additive one. E. g.,

toList 1 == [1,0,0,0,1,0,0,0,1]
toList 1 /= [1,1,1,1,1,1,1,1,1]

Constructors

Matrix3 

Fields

Instances
Functor Matrix3 Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

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

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

Foldable Matrix3 Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

fold :: Monoid m => Matrix3 m -> m #

foldMap :: Monoid m => (a -> m) -> Matrix3 a -> m #

foldr :: (a -> b -> b) -> b -> Matrix3 a -> b #

foldr' :: (a -> b -> b) -> b -> Matrix3 a -> b #

foldl :: (b -> a -> b) -> b -> Matrix3 a -> b #

foldl' :: (b -> a -> b) -> b -> Matrix3 a -> b #

foldr1 :: (a -> a -> a) -> Matrix3 a -> a #

foldl1 :: (a -> a -> a) -> Matrix3 a -> a #

toList :: Matrix3 a -> [a] #

null :: Matrix3 a -> Bool #

length :: Matrix3 a -> Int #

elem :: Eq a => a -> Matrix3 a -> Bool #

maximum :: Ord a => Matrix3 a -> a #

minimum :: Ord a => Matrix3 a -> a #

sum :: Num a => Matrix3 a -> a #

product :: Num a => Matrix3 a -> a #

Eq t => Eq (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

(==) :: Matrix3 t -> Matrix3 t -> Bool #

(/=) :: Matrix3 t -> Matrix3 t -> Bool #

(Fractional t, Ord t) => Fractional (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

(/) :: Matrix3 t -> Matrix3 t -> Matrix3 t #

recip :: Matrix3 t -> Matrix3 t #

fromRational :: Rational -> Matrix3 t #

(Num t, Ord t) => Num (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

(+) :: Matrix3 t -> Matrix3 t -> Matrix3 t #

(-) :: Matrix3 t -> Matrix3 t -> Matrix3 t #

(*) :: Matrix3 t -> Matrix3 t -> Matrix3 t #

negate :: Matrix3 t -> Matrix3 t #

abs :: Matrix3 t -> Matrix3 t #

signum :: Matrix3 t -> Matrix3 t #

fromInteger :: Integer -> Matrix3 t #

Show t => Show (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

showsPrec :: Int -> Matrix3 t -> ShowS #

show :: Matrix3 t -> String #

showList :: [Matrix3 t] -> ShowS #

Generic (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Associated Types

type Rep (Matrix3 t) :: * -> * #

Methods

from :: Matrix3 t -> Rep (Matrix3 t) x #

to :: Rep (Matrix3 t) x -> Matrix3 t #

NFData t => NFData (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

rnf :: Matrix3 t -> () #

Pretty t => Pretty (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

Methods

pretty :: Matrix3 t -> Doc ann #

prettyList :: [Matrix3 t] -> Doc ann #

type Rep (Matrix3 t) Source # 
Instance details

Defined in Math.ExpPairs.Matrix3

fromList :: [t] -> Matrix3 t Source #

Convert a list of 9 elements into Matrix3. Reverse conversion can be done by toList from Data.Foldable.

toList :: Foldable t => t a -> [a] #

List of elements of a structure, from left to right.

det :: Num t => Matrix3 t -> t Source #

Compute the determinant of a matrix.

multCol :: Num t => Matrix3 t -> (t, t, t) -> (t, t, t) Source #

Multiplicate a matrix by a vector (considered as a column).

normalize :: Integral t => Matrix3 t -> Matrix3 t Source #

Divide all elements of the matrix by their greatest common divisor. This is useful for matrices of projective transformations to reduce the magnitude of computations.

makarovMult :: Num t => Matrix3 t -> Matrix3 t -> Matrix3 t Source #

Multiplicate matrices under assumption that multiplication of elements is commutative. Requires 22 multiplications and 66 additions. It becomes faster than usual multiplication (which requires 27 multiplications and 18 additions), when matrix's elements are large (several hundred digits) integers.

An algorithm follows O. M. Makarov. An algorithm for multiplication of 3 × 3 matrices. Zh. Vychisl. Mat. i Mat. Fiz., 26(2):293–294, 320, 1986.

We were able to reduce the number of additions from 105 to 66 by sofisticated choice of intermediate variables.

ladermanMult :: Num t => Matrix3 t -> Matrix3 t -> Matrix3 t Source #

Multiplicate matrices by 23 multiplications and 68 additions. It becomes faster than usual multiplication (which requires 27 multiplications and 18 additions), when matrix's elements are large (several hundred digits) integers.

An algorithm follows J. Laderman. A noncommutative algorithm for multiplying 3 × 3 matrices using 23 multiplications. Bull. Amer. Math. Soc., 82:126–128, 1976.

We were able to reduce the number of additions from 98 to 68 by sofisticated choice of intermediate variables.