hmatrix-0.18.0.0: Numeric Linear Algebra

Copyright(c) Alberto Ruiz 2015
LicenseBSD3
MaintainerAlberto Ruiz
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Numeric.LinearAlgebra.Data

Contents

Description

This module provides functions for creation and manipulation of vectors and matrices, IO, and other utilities.

Synopsis

Elements

type R = Double Source #

type I = CInt Source #

type Z = Int64 Source #

type (./.) x n = Mod n x infixr 5 Source #

Vector

1D arrays are storable vectors directly reexported from the vector package.

fromList :: Storable a => [a] -> Vector a #

O(n) Convert a list to a vector

toList :: Storable a => Vector a -> [a] Source #

(|>) :: Storable a => Int -> [a] -> Vector a infixl 9 Source #

Create a vector from a list of elements and explicit dimension. The input list is truncated if it is too long, so it may safely be used, for instance, with infinite lists.

>>> 5 |> [1..]
fromList [1.0,2.0,3.0,4.0,5.0]

vector :: [R] -> Vector R Source #

Create a real vector.

>>> vector [1..5]
fromList [1.0,2.0,3.0,4.0,5.0]

range :: Int -> Vector I Source #

>>> range 5
fromList [0,1,2,3,4]

idxs :: [Int] -> Vector I Source #

Create a vector of indexes, useful for matrix extraction using '(??)'

Matrix

The main data type of hmatrix is a 2D dense array defined on top of a storable vector. The internal representation is suitable for direct interface with standard numeric libraries.

(><) :: Storable a => Int -> Int -> [a] -> Matrix a Source #

Create a matrix from a list of elements

>>> (2><3) [2, 4, 7+2*iC,   -3, 11, 0]
(2><3)
 [       2.0 :+ 0.0,  4.0 :+ 0.0, 7.0 :+ 2.0
 , (-3.0) :+ (-0.0), 11.0 :+ 0.0, 0.0 :+ 0.0 ]

The input list is explicitly truncated, so that it can safely be used with lists that are too long (like infinite lists).

>>> (2><3)[1..]
(2><3)
 [ 1.0, 2.0, 3.0
 , 4.0, 5.0, 6.0 ]

This is the format produced by the instances of Show (Matrix a), which can also be used for input.

matrix Source #

Arguments

:: Int

number of columns

-> [R]

elements in row order

-> Matrix R 

Create a real matrix.

>>> matrix 5 [1..15]
(3><5)
 [  1.0,  2.0,  3.0,  4.0,  5.0
 ,  6.0,  7.0,  8.0,  9.0, 10.0
 , 11.0, 12.0, 13.0, 14.0, 15.0 ]

tr :: Transposable m mt => m -> mt Source #

conjugate transpose

tr' :: Transposable m mt => m -> mt Source #

transpose

Dimensions

size :: Container c t => c t -> IndexOf c Source #

>>> size $ vector [1..10]
10
>>> size $ (2><5)[1..10::Double]
(2,5)

Conversion from/to lists

fromLists :: Element t => [[t]] -> Matrix t Source #

Creates a Matrix from a list of lists (considered as rows).

>>> fromLists [[1,2],[3,4],[5,6]]
(3><2)
 [ 1.0, 2.0
 , 3.0, 4.0
 , 5.0, 6.0 ]

toLists :: Element t => Matrix t -> [[t]] Source #

the inverse of fromLists

row :: [Double] -> Matrix Double Source #

create a single row real matrix from a list

>>> row [2,3,1,8]
(1><4)
 [ 2.0, 3.0, 1.0, 8.0 ]

col :: [Double] -> Matrix Double Source #

create a single column real matrix from a list

>>> col [7,-2,4]
(3><1)
 [  7.0
 , -2.0
 ,  4.0 ]

Conversions vector/matrix

flatten :: Element t => Matrix t -> Vector t Source #

Creates a vector by concatenation of rows. If the matrix is ColumnMajor, this operation requires a transpose.

>>> flatten (ident 3)
fromList [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]

reshape :: Storable t => Int -> Vector t -> Matrix t Source #

Creates a matrix from a vector by grouping the elements in rows with the desired number of columns. (GNU-Octave groups by columns. To do it you can define reshapeF r = tr' . reshape r where r is the desired number of rows.)

>>> reshape 4 (fromList [1..12])
(3><4)
 [ 1.0,  2.0,  3.0,  4.0
 , 5.0,  6.0,  7.0,  8.0
 , 9.0, 10.0, 11.0, 12.0 ]

asRow :: Storable a => Vector a -> Matrix a Source #

creates a 1-row matrix from a vector

>>> asRow (fromList [1..5])
 (1><5)
  [ 1.0, 2.0, 3.0, 4.0, 5.0 ]

asColumn :: Storable a => Vector a -> Matrix a Source #

creates a 1-column matrix from a vector

>>> asColumn (fromList [1..5])
(5><1)
 [ 1.0
 , 2.0
 , 3.0
 , 4.0
 , 5.0 ]

fromRows :: Element t => [Vector t] -> Matrix t Source #

Create a matrix from a list of vectors. All vectors must have the same dimension, or dimension 1, which is are automatically expanded.

toRows :: Element t => Matrix t -> [Vector t] Source #

extracts the rows of a matrix as a list of vectors

fromColumns :: Element t => [Vector t] -> Matrix t Source #

Creates a matrix from a list of vectors, as columns

toColumns :: Element t => Matrix t -> [Vector t] Source #

Creates a list of vectors from the columns of a matrix

Indexing

atIndex :: Container c e => c e -> IndexOf c -> e Source #

generic indexing function

>>> vector [1,2,3] `atIndex` 1
2.0
>>> matrix 3 [0..8] `atIndex` (2,0)
6.0

class Indexable c t | c -> t, t -> c where Source #

Alternative indexing function.

>>> vector [1..10] ! 3
4.0

On a matrix it gets the k-th row as a vector:

>>> matrix 5 [1..15] ! 1
fromList [6.0,7.0,8.0,9.0,10.0]
>>> matrix 5 [1..15] ! 1 ! 3
9.0

Minimal complete definition

(!)

Methods

(!) :: c -> Int -> t infixl 9 Source #

Construction

scalar :: Container c e => e -> c e Source #

create a structure with a single element

>>> let v = fromList [1..3::Double]
>>> v / scalar (norm2 v)
fromList [0.2672612419124244,0.5345224838248488,0.8017837257372732]

class Konst e d c | d -> c, c -> d where Source #

Minimal complete definition

konst

Methods

konst :: e -> d -> c e Source #

>>> konst 7 3 :: Vector Float
fromList [7.0,7.0,7.0]
>>> konst i (3::Int,4::Int)
(3><4)
 [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
 , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
 , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]

Instances

Container Vector e => Konst e Int Vector Source # 

Methods

konst :: e -> Int -> Vector e Source #

(Num e, Container Vector e) => Konst e (Int, Int) Matrix Source # 

Methods

konst :: e -> (Int, Int) -> Matrix e Source #

class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f where Source #

Minimal complete definition

build

Methods

build :: d -> f -> c e Source #

>>> build 5 (**2) :: Vector Double
fromList [0.0,1.0,4.0,9.0,16.0]

Hilbert matrix of order N:

>>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
>>> putStr . dispf 2 $ hilb 3
3x3
1.00  0.50  0.33
0.50  0.33  0.25
0.33  0.25  0.20

Instances

Container Vector e => Build Int (e -> e) Vector e Source # 

Methods

build :: Int -> (e -> e) -> Vector e Source #

Container Matrix e => Build (Int, Int) (e -> e -> e) Matrix e Source # 

Methods

build :: (Int, Int) -> (e -> e -> e) -> Matrix e Source #

assoc Source #

Arguments

:: Container c e 
=> IndexOf c

size

-> e

default value

-> [(IndexOf c, e)]

association list

-> c e

result

Create a structure from an association list

>>> assoc 5 0 [(3,7),(1,4)] :: Vector Double
fromList [0.0,4.0,0.0,7.0,0.0]
>>> assoc (2,3) 0 [((0,2),7),((1,0),2*i-3)] :: Matrix (Complex Double)
(2><3)
 [    0.0 :+ 0.0, 0.0 :+ 0.0, 7.0 :+ 0.0
 , (-3.0) :+ 2.0, 0.0 :+ 0.0, 0.0 :+ 0.0 ]

accum Source #

Arguments

:: Container c e 
=> c e

initial structure

-> (e -> e -> e)

update function

-> [(IndexOf c, e)]

association list

-> c e

result

Modify a structure using an update function

>>> accum (ident 5) (+) [((1,1),5),((0,3),3)] :: Matrix Double
(5><5)
 [ 1.0, 0.0, 0.0, 3.0, 0.0
 , 0.0, 6.0, 0.0, 0.0, 0.0
 , 0.0, 0.0, 1.0, 0.0, 0.0
 , 0.0, 0.0, 0.0, 1.0, 0.0
 , 0.0, 0.0, 0.0, 0.0, 1.0 ]

computation of histogram:

>>> accum (konst 0 7) (+) (map (flip (,) 1) [4,5,4,1,5,2,5]) :: Vector Double
fromList [0.0,1.0,1.0,0.0,2.0,3.0,0.0]

linspace :: (Fractional e, Container Vector e) => Int -> (e, e) -> Vector e Source #

Creates a real vector containing a range of values:

>>> linspace 5 (-3,7::Double)
fromList [-3.0,-0.5,2.0,4.5,7.0]@
>>> linspace 5 (8,2+i) :: Vector (Complex Double)
fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]

Logarithmic spacing can be defined as follows:

logspace n (a,b) = 10 ** linspace n (a,b)

Diagonal

ident :: (Num a, Element a) => Int -> Matrix a Source #

creates the identity matrix of given dimension

diag :: (Num a, Element a) => Vector a -> Matrix a Source #

Creates a square matrix with a given diagonal.

diagl :: [Double] -> Matrix Double Source #

create a real diagonal matrix from a list

>>> diagl [1,2,3]
(3><3)
 [ 1.0, 0.0, 0.0
 , 0.0, 2.0, 0.0
 , 0.0, 0.0, 3.0 ]

diagRect :: Storable t => t -> Vector t -> Int -> Int -> Matrix t Source #

creates a rectangular diagonal matrix:

>>> diagRect 7 (fromList [10,20,30]) 4 5 :: Matrix Double
(4><5)
 [ 10.0,  7.0,  7.0, 7.0, 7.0
 ,  7.0, 20.0,  7.0, 7.0, 7.0
 ,  7.0,  7.0, 30.0, 7.0, 7.0
 ,  7.0,  7.0,  7.0, 7.0, 7.0 ]

takeDiag :: Element t => Matrix t -> Vector t Source #

extracts the diagonal from a rectangular matrix

Vector extraction

subVector Source #

Arguments

:: Storable t 
=> Int

index of the starting element

-> Int

number of elements to extract

-> Vector t

source

-> Vector t

result

takes a number of consecutive elements from a Vector

>>> subVector 2 3 (fromList [1..10])
fromList [3.0,4.0,5.0]

takesV :: Storable t => [Int] -> Vector t -> [Vector t] Source #

Extract consecutive subvectors of the given sizes.

>>> takesV [3,4] (linspace 10 (1,10::Double))
[fromList [1.0,2.0,3.0],fromList [4.0,5.0,6.0,7.0]]

vjoin :: Storable t => [Vector t] -> Vector t Source #

concatenate a list of vectors

>>> vjoin [fromList [1..5::Double], konst 1 3]
fromList [1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]

Matrix extraction

data Extractor Source #

Specification of indexes for the operator ??.

(??) :: Element t => Matrix t -> (Extractor, Extractor) -> Matrix t infixl 9 Source #

General matrix slicing.

>>> m
(4><5)
 [  0,  1,  2,  3,  4
 ,  5,  6,  7,  8,  9
 , 10, 11, 12, 13, 14
 , 15, 16, 17, 18, 19 ]
>>> m ?? (Take 3, DropLast 2)
(3><3)
 [  0,  1,  2
 ,  5,  6,  7
 , 10, 11, 12 ]
>>> m ?? (Pos (idxs[2,1]), All)
(2><5)
 [ 10, 11, 12, 13, 14
 ,  5,  6,  7,  8,  9 ]
>>> m ?? (PosCyc (idxs[-7,80]), Range 4 (-2) 0)
(2><3)
 [ 9, 7, 5
 , 4, 2, 0 ]

(?) :: Element t => Matrix t -> [Int] -> Matrix t infixl 9 Source #

extract rows

>>> (20><4) [1..] ? [2,1,1]
(3><4)
 [ 9.0, 10.0, 11.0, 12.0
 , 5.0,  6.0,  7.0,  8.0
 , 5.0,  6.0,  7.0,  8.0 ]

¿ :: Element t => Matrix t -> [Int] -> Matrix t infixl 9 Source #

extract columns

(unicode 0x00bf, inverted question mark, Alt-Gr ?)

>>> (3><4) [1..] ¿ [3,0]
(3><2)
 [  4.0, 1.0
 ,  8.0, 5.0
 , 12.0, 9.0 ]

fliprl :: Element t => Matrix t -> Matrix t Source #

Reverse columns

flipud :: Element t => Matrix t -> Matrix t Source #

Reverse rows

subMatrix Source #

Arguments

:: Element a 
=> (Int, Int)

(r0,c0) starting position

-> (Int, Int)

(rt,ct) dimensions of submatrix

-> Matrix a

input matrix

-> Matrix a

result

reference to a rectangular slice of a matrix (no data copy)

remap :: Element t => Matrix I -> Matrix I -> Matrix t -> Matrix t Source #

Extract elements from positions given in matrices of rows and columns.

>>> r
(3><3)
 [ 1, 1, 1
 , 1, 2, 2
 , 1, 2, 3 ]
>>> c
(3><3)
 [ 0, 1, 5
 , 2, 2, 1
 , 4, 4, 1 ]
>>> m
(4><6)
 [  0,  1,  2,  3,  4,  5
 ,  6,  7,  8,  9, 10, 11
 , 12, 13, 14, 15, 16, 17
 , 18, 19, 20, 21, 22, 23 ]
>>> remap r c m
(3><3)
 [  6,  7, 11
 ,  8, 14, 13
 , 10, 16, 19 ]

The indexes are autoconformable.

>>> c'
(3><1)
 [ 1
 , 2
 , 4 ]
>>> remap r c' m
(3><3)
 [  7,  7,  7
 ,  8, 14, 14
 , 10, 16, 22 ]

Block matrix

fromBlocks :: Element t => [[Matrix t]] -> Matrix t Source #

Create a matrix from blocks given as a list of lists of matrices.

Single row-column components are automatically expanded to match the corresponding common row and column:

disp = putStr . dispf 2
>>> disp $ fromBlocks [[ident 5, 7, row[10,20]], [3, diagl[1,2,3], 0]]
8x10
1  0  0  0  0  7  7  7  10  20
0  1  0  0  0  7  7  7  10  20
0  0  1  0  0  7  7  7  10  20
0  0  0  1  0  7  7  7  10  20
0  0  0  0  1  7  7  7  10  20
3  3  3  3  3  1  0  0   0   0
3  3  3  3  3  0  2  0   0   0
3  3  3  3  3  0  0  3   0   0

(|||) :: Element t => Matrix t -> Matrix t -> Matrix t infixl 3 Source #

horizontal concatenation

>>> ident 3 ||| konst 7 (3,4)
(3><7)
 [ 1.0, 0.0, 0.0, 7.0, 7.0, 7.0, 7.0
 , 0.0, 1.0, 0.0, 7.0, 7.0, 7.0, 7.0
 , 0.0, 0.0, 1.0, 7.0, 7.0, 7.0, 7.0 ]

(===) :: Element t => Matrix t -> Matrix t -> Matrix t infixl 2 Source #

vertical concatenation

diagBlock :: (Element t, Num t) => [Matrix t] -> Matrix t Source #

create a block diagonal matrix

>>> disp 2 $ diagBlock [konst 1 (2,2), konst 2 (3,5), col [5,7]]
7x8
1  1  0  0  0  0  0  0
1  1  0  0  0  0  0  0
0  0  2  2  2  2  2  0
0  0  2  2  2  2  2  0
0  0  2  2  2  2  2  0
0  0  0  0  0  0  0  5
0  0  0  0  0  0  0  7
>>> diagBlock [(0><4)[], konst 2 (2,3)]  :: Matrix Double
(2><7)
 [ 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0
 , 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0 ]

repmat :: Element t => Matrix t -> Int -> Int -> Matrix t Source #

creates matrix by repetition of a matrix a given number of rows and columns

>>> repmat (ident 2) 2 3
(4><6)
 [ 1.0, 0.0, 1.0, 0.0, 1.0, 0.0
 , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0
 , 1.0, 0.0, 1.0, 0.0, 1.0, 0.0
 , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0 ]

toBlocks :: Element t => [Int] -> [Int] -> Matrix t -> [[Matrix t]] Source #

Partition a matrix into blocks with the given numbers of rows and columns. The remaining rows and columns are discarded.

toBlocksEvery :: Element t => Int -> Int -> Matrix t -> [[Matrix t]] Source #

Fully partition a matrix into blocks of the same size. If the dimensions are not a multiple of the given size the last blocks will be smaller.

Mapping functions

conj :: Container c e => c e -> c e Source #

complex conjugate

cmap :: (Element b, Container c e) => (e -> b) -> c e -> c b Source #

like fmap (cannot implement instance Functor because of Element class constraint)

cmod :: (Integral e, Container c e) => e -> c e -> c e Source #

mod for integer arrays

>>> cmod 3 (range 5)
fromList [0,1,2,0,1]

step :: (Ord e, Container c e) => c e -> c e Source #

A more efficient implementation of cmap (\x -> if x>0 then 1 else 0)

>>> step $ linspace 5 (-1,1::Double)
5 |> [0.0,0.0,0.0,1.0,1.0]

cond Source #

Arguments

:: (Ord e, Container c e, Container c x) 
=> c e

a

-> c e

b

-> c x

l

-> c x

e

-> c x

g

-> c x

result

Element by element version of case compare a b of {LT -> l; EQ -> e; GT -> g}.

Arguments with any dimension = 1 are automatically expanded:

>>> cond ((1><4)[1..]) ((3><1)[1..]) 0 100 ((3><4)[1..]) :: Matrix Double
(3><4)
[ 100.0,   2.0,   3.0,  4.0
,   0.0, 100.0,   7.0,  8.0
,   0.0,   0.0, 100.0, 12.0 ]
>>> let chop x = cond (abs x) 1E-6 0 0 x

Find elements

find :: Container c e => (e -> Bool) -> c e -> [IndexOf c] Source #

Find index of elements which satisfy a predicate

>>> find (>0) (ident 3 :: Matrix Double)
[(0,0),(1,1),(2,2)]

maxIndex :: Container c e => c e -> IndexOf c Source #

index of maximum element

minIndex :: Container c e => c e -> IndexOf c Source #

index of minimum element

maxElement :: Container c e => c e -> e Source #

value of maximum element

minElement :: Container c e => c e -> e Source #

value of minimum element

sortVector :: (Ord t, Element t) => Vector t -> Vector t Source #

sortIndex :: (Ord t, Element t) => Vector t -> Vector I Source #

>>> m <- randn 4 10
>>> disp 2 m
4x10
-0.31   0.41   0.43  -0.19  -0.17  -0.23  -0.17  -1.04  -0.07  -1.24
 0.26   0.19   0.14   0.83  -1.54  -0.09   0.37  -0.63   0.71  -0.50
-0.11  -0.10  -1.29  -1.40  -1.04  -0.89  -0.68   0.35  -1.46   1.86
 1.04  -0.29   0.19  -0.75  -2.20  -0.01   1.06   0.11  -2.09  -1.58
>>> disp 2 $ m ?? (All, Pos $ sortIndex (m!1))
4x10
-0.17  -1.04  -1.24  -0.23   0.43   0.41  -0.31  -0.17  -0.07  -0.19
-1.54  -0.63  -0.50  -0.09   0.14   0.19   0.26   0.37   0.71   0.83
-1.04   0.35   1.86  -0.89  -1.29  -0.10  -0.11  -0.68  -1.46  -1.40
-2.20   0.11  -1.58  -0.01   0.19  -0.29   1.04   1.06  -2.09  -0.75

Sparse

type AssocMatrix = [((Int, Int), Double)] Source #

IO

disp :: Int -> Matrix Double -> IO () Source #

print a real matrix with given number of digits after the decimal point

>>> disp 5 $ ident 2 / 3
2x2
0.33333  0.00000
0.00000  0.33333

loadMatrix :: FilePath -> IO (Matrix Double) Source #

load a matrix from an ASCII file formatted as a 2D table.

saveMatrix Source #

Arguments

:: FilePath 
-> String

"printf" format (e.g. "%.2f", "%g", etc.)

-> Matrix Double 
-> IO () 

save a matrix as a 2D ASCII table

latexFormat Source #

Arguments

:: String

type of braces: "matrix", "bmatrix", "pmatrix", etc.

-> String

Formatted matrix, with elements separated by spaces and newlines

-> String 

Tool to display matrices with latex syntax.

>>> latexFormat "bmatrix" (dispf 2 $ ident 2)
"\\begin{bmatrix}\n1  &  0\n\\\\\n0  &  1\n\\end{bmatrix}"

dispf :: Int -> Matrix Double -> String Source #

Show a matrix with a given number of decimal places.

>>> dispf 2 (1/3 + ident 3)
"3x3\n1.33  0.33  0.33\n0.33  1.33  0.33\n0.33  0.33  1.33\n"
>>> putStr . dispf 2 $ (3><4)[1,1.5..]
3x4
1.00  1.50  2.00  2.50
3.00  3.50  4.00  4.50
5.00  5.50  6.00  6.50
>>> putStr . unlines . tail . lines . dispf 2 . asRow $ linspace 10 (0,1)
0.00  0.11  0.22  0.33  0.44  0.56  0.67  0.78  0.89  1.00

disps :: Int -> Matrix Double -> String Source #

Show a matrix with "autoscaling" and a given number of decimal places.

>>> putStr . disps 2 $ 120 * (3><4) [1..]
3x4  E3
 0.12  0.24  0.36  0.48
 0.60  0.72  0.84  0.96
 1.08  1.20  1.32  1.44

dispcf :: Int -> Matrix (Complex Double) -> String Source #

Pretty print a complex matrix with at most n decimal digits.

format :: Element t => String -> (t -> String) -> Matrix t -> String Source #

Creates a string from a matrix given a separator and a function to show each entry. Using this function the user can easily define any desired display function:

import Text.Printf(printf)
disp = putStr . format "  " (printf "%.2f")

dispShort :: Int -> Int -> Int -> Matrix Double -> IO () Source #

Element conversion

class Convert t where Source #

Minimal complete definition

real, complex, single, double, toComplex, fromComplex

Methods

real :: Complexable c => c (RealOf t) -> c t Source #

complex :: Complexable c => c t -> c (ComplexOf t) Source #

single :: Complexable c => c t -> c (SingleOf t) Source #

double :: Complexable c => c t -> c (DoubleOf t) Source #

toComplex :: (Complexable c, RealElement t) => (c t, c t) -> c (Complex t) Source #

fromComplex :: (Complexable c, RealElement t) => c (Complex t) -> (c t, c t) Source #

Instances

Convert Double Source # 
Convert Float Source # 
Convert (Complex Double) Source # 
Convert (Complex Float) Source # 

fromInt :: Container c e => c I -> c e Source #

>>> fromInt ((2><2) [0..3]) :: Matrix (Complex Double)
(2><2)
[ 0.0 :+ 0.0, 1.0 :+ 0.0
, 2.0 :+ 0.0, 3.0 :+ 0.0 ]

toInt :: Container c e => c e -> c I Source #

fromZ :: Container c e => c Z -> c e Source #

toZ :: Container c e => c e -> c Z Source #

Misc

arctan2 :: (Fractional e, Container c e) => c e -> c e -> c e Source #

separable :: Element t => (Vector t -> Vector t) -> Matrix t -> Matrix t Source #

matrix computation implemented as separated vector operations by rows and columns.

data Mod n t Source #

Wrapper with a phantom integer for statically checked modular arithmetic.

Instances

KnownNat m => Container Vector (Mod m Z) Source # 

Methods

conj' :: Vector (Mod m Z) -> Vector (Mod m Z)

size' :: Vector (Mod m Z) -> IndexOf Vector

scalar' :: Mod m Z -> Vector (Mod m Z)

scale' :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

addConstant :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

add' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

sub :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

mul :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

equal :: Vector (Mod m Z) -> Vector (Mod m Z) -> Bool

cmap' :: Element b => (Mod m Z -> b) -> Vector (Mod m Z) -> Vector b

konst' :: Mod m Z -> IndexOf Vector -> Vector (Mod m Z)

build' :: IndexOf Vector -> ArgOf Vector (Mod m Z) -> Vector (Mod m Z)

atIndex' :: Vector (Mod m Z) -> IndexOf Vector -> Mod m Z

minIndex' :: Vector (Mod m Z) -> IndexOf Vector

maxIndex' :: Vector (Mod m Z) -> IndexOf Vector

minElement' :: Vector (Mod m Z) -> Mod m Z

maxElement' :: Vector (Mod m Z) -> Mod m Z

sumElements' :: Vector (Mod m Z) -> Mod m Z

prodElements' :: Vector (Mod m Z) -> Mod m Z

step' :: Vector (Mod m Z) -> Vector (Mod m Z)

ccompare' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector I

cselect' :: Vector I -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

find' :: (Mod m Z -> Bool) -> Vector (Mod m Z) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Mod m Z -> [(IndexOf Vector, Mod m Z)] -> Vector (Mod m Z)

accum' :: Vector (Mod m Z) -> (Mod m Z -> Mod m Z -> Mod m Z) -> [(IndexOf Vector, Mod m Z)] -> Vector (Mod m Z)

scaleRecip :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

divide :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

arctan2' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

cmod' :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

fromInt' :: Vector I -> Vector (Mod m Z)

toInt' :: Vector (Mod m Z) -> Vector I

fromZ' :: Vector Z -> Vector (Mod m Z)

toZ' :: Vector (Mod m Z) -> Vector Z

KnownNat m => Container Vector (Mod m I) Source # 

Methods

conj' :: Vector (Mod m I) -> Vector (Mod m I)

size' :: Vector (Mod m I) -> IndexOf Vector

scalar' :: Mod m I -> Vector (Mod m I)

scale' :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

addConstant :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

add' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

sub :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

mul :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

equal :: Vector (Mod m I) -> Vector (Mod m I) -> Bool

cmap' :: Element b => (Mod m I -> b) -> Vector (Mod m I) -> Vector b

konst' :: Mod m I -> IndexOf Vector -> Vector (Mod m I)

build' :: IndexOf Vector -> ArgOf Vector (Mod m I) -> Vector (Mod m I)

atIndex' :: Vector (Mod m I) -> IndexOf Vector -> Mod m I

minIndex' :: Vector (Mod m I) -> IndexOf Vector

maxIndex' :: Vector (Mod m I) -> IndexOf Vector

minElement' :: Vector (Mod m I) -> Mod m I

maxElement' :: Vector (Mod m I) -> Mod m I

sumElements' :: Vector (Mod m I) -> Mod m I

prodElements' :: Vector (Mod m I) -> Mod m I

step' :: Vector (Mod m I) -> Vector (Mod m I)

ccompare' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector I

cselect' :: Vector I -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

find' :: (Mod m I -> Bool) -> Vector (Mod m I) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Mod m I -> [(IndexOf Vector, Mod m I)] -> Vector (Mod m I)

accum' :: Vector (Mod m I) -> (Mod m I -> Mod m I -> Mod m I) -> [(IndexOf Vector, Mod m I)] -> Vector (Mod m I)

scaleRecip :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

divide :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

arctan2' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

cmod' :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

fromInt' :: Vector I -> Vector (Mod m I)

toInt' :: Vector (Mod m I) -> Vector I

fromZ' :: Vector Z -> Vector (Mod m I)

toZ' :: Vector (Mod m I) -> Vector Z

KnownNat m => Num (Vector (Mod m Z)) Source # 

Methods

(+) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

(-) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

(*) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

negate :: Vector (Mod m Z) -> Vector (Mod m Z) #

abs :: Vector (Mod m Z) -> Vector (Mod m Z) #

signum :: Vector (Mod m Z) -> Vector (Mod m Z) #

fromInteger :: Integer -> Vector (Mod m Z) #

KnownNat m => Num (Vector (Mod m I)) Source # 

Methods

(+) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

(-) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

(*) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

negate :: Vector (Mod m I) -> Vector (Mod m I) #

abs :: Vector (Mod m I) -> Vector (Mod m I) #

signum :: Vector (Mod m I) -> Vector (Mod m I) #

fromInteger :: Integer -> Vector (Mod m I) #

KnownNat m => Testable (Matrix (Mod m I)) Source # 

Methods

checkT :: Matrix (Mod m I) -> (Bool, IO ()) Source #

ioCheckT :: Matrix (Mod m I) -> IO (Bool, IO ()) Source #

KnownNat m => Normed (Vector (Mod m Z)) Source # 

Methods

norm_0 :: Vector (Mod m Z) -> R Source #

norm_1 :: Vector (Mod m Z) -> R Source #

norm_2 :: Vector (Mod m Z) -> R Source #

norm_Inf :: Vector (Mod m Z) -> R Source #

KnownNat m => Normed (Vector (Mod m I)) Source # 

Methods

norm_0 :: Vector (Mod m I) -> R Source #

norm_1 :: Vector (Mod m I) -> R Source #

norm_2 :: Vector (Mod m I) -> R Source #

norm_Inf :: Vector (Mod m I) -> R Source #

(Storable t, Indexable (Vector t) t) => Indexable (Vector (Mod m t)) (Mod m t) Source # 

Methods

(!) :: Vector (Mod m t) -> Int -> Mod m t Source #

(Integral t, Enum t, KnownNat m) => Enum (Mod m t) Source # 

Methods

succ :: Mod m t -> Mod m t #

pred :: Mod m t -> Mod m t #

toEnum :: Int -> Mod m t #

fromEnum :: Mod m t -> Int #

enumFrom :: Mod m t -> [Mod m t] #

enumFromThen :: Mod m t -> Mod m t -> [Mod m t] #

enumFromTo :: Mod m t -> Mod m t -> [Mod m t] #

enumFromThenTo :: Mod m t -> Mod m t -> Mod m t -> [Mod m t] #

(Eq t, KnownNat m) => Eq (Mod m t) Source # 

Methods

(==) :: Mod m t -> Mod m t -> Bool #

(/=) :: Mod m t -> Mod m t -> Bool #

(Show (Mod m t), Num (Mod m t), Eq t, KnownNat m) => Fractional (Mod m t) Source #

this instance is only valid for prime m

Methods

(/) :: Mod m t -> Mod m t -> Mod m t #

recip :: Mod m t -> Mod m t #

fromRational :: Rational -> Mod m t #

(Integral t, KnownNat m, Num (Mod m t)) => Integral (Mod m t) Source # 

Methods

quot :: Mod m t -> Mod m t -> Mod m t #

rem :: Mod m t -> Mod m t -> Mod m t #

div :: Mod m t -> Mod m t -> Mod m t #

mod :: Mod m t -> Mod m t -> Mod m t #

quotRem :: Mod m t -> Mod m t -> (Mod m t, Mod m t) #

divMod :: Mod m t -> Mod m t -> (Mod m t, Mod m t) #

toInteger :: Mod m t -> Integer #

(Integral t, KnownNat n) => Num (Mod n t) Source # 

Methods

(+) :: Mod n t -> Mod n t -> Mod n t #

(-) :: Mod n t -> Mod n t -> Mod n t #

(*) :: Mod n t -> Mod n t -> Mod n t #

negate :: Mod n t -> Mod n t #

abs :: Mod n t -> Mod n t #

signum :: Mod n t -> Mod n t #

fromInteger :: Integer -> Mod n t #

(Ord t, KnownNat m) => Ord (Mod m t) Source # 

Methods

compare :: Mod m t -> Mod m t -> Ordering #

(<) :: Mod m t -> Mod m t -> Bool #

(<=) :: Mod m t -> Mod m t -> Bool #

(>) :: Mod m t -> Mod m t -> Bool #

(>=) :: Mod m t -> Mod m t -> Bool #

max :: Mod m t -> Mod m t -> Mod m t #

min :: Mod m t -> Mod m t -> Mod m t #

(Integral t, Real t, KnownNat m, Integral (Mod m t)) => Real (Mod m t) Source # 

Methods

toRational :: Mod m t -> Rational #

Show t => Show (Mod n t) Source # 

Methods

showsPrec :: Int -> Mod n t -> ShowS #

show :: Mod n t -> String #

showList :: [Mod n t] -> ShowS #

Storable t => Storable (Mod n t) Source # 

Methods

sizeOf :: Mod n t -> Int #

alignment :: Mod n t -> Int #

peekElemOff :: Ptr (Mod n t) -> Int -> IO (Mod n t) #

pokeElemOff :: Ptr (Mod n t) -> Int -> Mod n t -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Mod n t) #

pokeByteOff :: Ptr b -> Int -> Mod n t -> IO () #

peek :: Ptr (Mod n t) -> IO (Mod n t) #

poke :: Ptr (Mod n t) -> Mod n t -> IO () #

NFData t => NFData (Mod n t) Source # 

Methods

rnf :: Mod n t -> () #

KnownNat m => Element (Mod m Z) Source # 

Methods

constantD :: Mod m Z -> Int -> Vector (Mod m Z)

extractR :: MatrixOrder -> Matrix (Mod m Z) -> CInt -> Vector CInt -> CInt -> Vector CInt -> IO (Matrix (Mod m Z))

setRect :: Int -> Int -> Matrix (Mod m Z) -> Matrix (Mod m Z) -> IO ()

sortI :: Vector (Mod m Z) -> Vector CInt

sortV :: Vector (Mod m Z) -> Vector (Mod m Z)

compareV :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector CInt

selectV :: Vector CInt -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

remapM :: Matrix CInt -> Matrix CInt -> Matrix (Mod m Z) -> Matrix (Mod m Z)

rowOp :: Int -> Mod m Z -> Int -> Int -> Int -> Int -> Matrix (Mod m Z) -> IO ()

gemm :: Vector (Mod m Z) -> Matrix (Mod m Z) -> Matrix (Mod m Z) -> Matrix (Mod m Z) -> IO ()

KnownNat m => Element (Mod m I) Source # 

Methods

constantD :: Mod m I -> Int -> Vector (Mod m I)

extractR :: MatrixOrder -> Matrix (Mod m I) -> CInt -> Vector CInt -> CInt -> Vector CInt -> IO (Matrix (Mod m I))

setRect :: Int -> Int -> Matrix (Mod m I) -> Matrix (Mod m I) -> IO ()

sortI :: Vector (Mod m I) -> Vector CInt

sortV :: Vector (Mod m I) -> Vector (Mod m I)

compareV :: Vector (Mod m I) -> Vector (Mod m I) -> Vector CInt

selectV :: Vector CInt -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

remapM :: Matrix CInt -> Matrix CInt -> Matrix (Mod m I) -> Matrix (Mod m I)

rowOp :: Int -> Mod m I -> Int -> Int -> Int -> Int -> Matrix (Mod m I) -> IO ()

gemm :: Vector (Mod m I) -> Matrix (Mod m I) -> Matrix (Mod m I) -> Matrix (Mod m I) -> IO ()

KnownNat m => Product (Mod m Z) Source # 

Methods

multiply :: Matrix (Mod m Z) -> Matrix (Mod m Z) -> Matrix (Mod m Z)

absSum :: Vector (Mod m Z) -> RealOf (Mod m Z)

norm1 :: Vector (Mod m Z) -> RealOf (Mod m Z)

norm2 :: Vector (Mod m Z) -> RealOf (Mod m Z)

normInf :: Vector (Mod m Z) -> RealOf (Mod m Z)

KnownNat m => Product (Mod m I) Source # 

Methods

multiply :: Matrix (Mod m I) -> Matrix (Mod m I) -> Matrix (Mod m I)

absSum :: Vector (Mod m I) -> RealOf (Mod m I)

norm1 :: Vector (Mod m I) -> RealOf (Mod m I)

norm2 :: Vector (Mod m I) -> RealOf (Mod m I)

normInf :: Vector (Mod m I) -> RealOf (Mod m I)

KnownNat m => Numeric (Mod m Z) Source # 
KnownNat m => Numeric (Mod m I) Source # 
type RealOf (Mod n Z) Source # 
type RealOf (Mod n Z) = Z
type RealOf (Mod n I) Source # 
type RealOf (Mod n I) = I

data Vector a :: * -> * #

Storable-based vectors

Instances

Complexable Vector Source # 

Methods

toComplex' :: RealElement e => (Vector e, Vector e) -> Vector (Complex e)

fromComplex' :: RealElement e => Vector (Complex e) -> (Vector e, Vector e)

comp' :: RealElement e => Vector e -> Vector (Complex e)

single' :: Precision a b => Vector b -> Vector a

double' :: Precision a b => Vector a -> Vector b

LSDiv Vector Source # 

Methods

linSolve :: Field t => Matrix t -> Vector t -> Vector t

Storable a => Vector Vector a 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) a -> m (Vector a) #

basicUnsafeThaw :: PrimMonad m => Vector a -> m (Mutable Vector (PrimState m) a) #

basicLength :: Vector a -> Int #

basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a #

basicUnsafeIndexM :: Monad m => Vector a -> Int -> m a #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) a -> Vector a -> m () #

elemseq :: Vector a -> a -> b -> b #

Container Vector t => Linear t Vector Source # 

Methods

scale :: t -> Vector t -> Vector t Source #

Container Vector Double Source # 

Methods

conj' :: Vector Double -> Vector Double

size' :: Vector Double -> IndexOf Vector

scalar' :: Double -> Vector Double

scale' :: Double -> Vector Double -> Vector Double

addConstant :: Double -> Vector Double -> Vector Double

add' :: Vector Double -> Vector Double -> Vector Double

sub :: Vector Double -> Vector Double -> Vector Double

mul :: Vector Double -> Vector Double -> Vector Double

equal :: Vector Double -> Vector Double -> Bool

cmap' :: Element b => (Double -> b) -> Vector Double -> Vector b

konst' :: Double -> IndexOf Vector -> Vector Double

build' :: IndexOf Vector -> ArgOf Vector Double -> Vector Double

atIndex' :: Vector Double -> IndexOf Vector -> Double

minIndex' :: Vector Double -> IndexOf Vector

maxIndex' :: Vector Double -> IndexOf Vector

minElement' :: Vector Double -> Double

maxElement' :: Vector Double -> Double

sumElements' :: Vector Double -> Double

prodElements' :: Vector Double -> Double

step' :: Vector Double -> Vector Double

ccompare' :: Vector Double -> Vector Double -> Vector I

cselect' :: Vector I -> Vector Double -> Vector Double -> Vector Double -> Vector Double

find' :: (Double -> Bool) -> Vector Double -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Double -> [(IndexOf Vector, Double)] -> Vector Double

accum' :: Vector Double -> (Double -> Double -> Double) -> [(IndexOf Vector, Double)] -> Vector Double

scaleRecip :: Double -> Vector Double -> Vector Double

divide :: Vector Double -> Vector Double -> Vector Double

arctan2' :: Vector Double -> Vector Double -> Vector Double

cmod' :: Double -> Vector Double -> Vector Double

fromInt' :: Vector I -> Vector Double

toInt' :: Vector Double -> Vector I

fromZ' :: Vector Z -> Vector Double

toZ' :: Vector Double -> Vector Z

Container Vector Float Source # 

Methods

conj' :: Vector Float -> Vector Float

size' :: Vector Float -> IndexOf Vector

scalar' :: Float -> Vector Float

scale' :: Float -> Vector Float -> Vector Float

addConstant :: Float -> Vector Float -> Vector Float

add' :: Vector Float -> Vector Float -> Vector Float

sub :: Vector Float -> Vector Float -> Vector Float

mul :: Vector Float -> Vector Float -> Vector Float

equal :: Vector Float -> Vector Float -> Bool

cmap' :: Element b => (Float -> b) -> Vector Float -> Vector b

konst' :: Float -> IndexOf Vector -> Vector Float

build' :: IndexOf Vector -> ArgOf Vector Float -> Vector Float

atIndex' :: Vector Float -> IndexOf Vector -> Float

minIndex' :: Vector Float -> IndexOf Vector

maxIndex' :: Vector Float -> IndexOf Vector

minElement' :: Vector Float -> Float

maxElement' :: Vector Float -> Float

sumElements' :: Vector Float -> Float

prodElements' :: Vector Float -> Float

step' :: Vector Float -> Vector Float

ccompare' :: Vector Float -> Vector Float -> Vector I

cselect' :: Vector I -> Vector Float -> Vector Float -> Vector Float -> Vector Float

find' :: (Float -> Bool) -> Vector Float -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Float -> [(IndexOf Vector, Float)] -> Vector Float

accum' :: Vector Float -> (Float -> Float -> Float) -> [(IndexOf Vector, Float)] -> Vector Float

scaleRecip :: Float -> Vector Float -> Vector Float

divide :: Vector Float -> Vector Float -> Vector Float

arctan2' :: Vector Float -> Vector Float -> Vector Float

cmod' :: Float -> Vector Float -> Vector Float

fromInt' :: Vector I -> Vector Float

toInt' :: Vector Float -> Vector I

fromZ' :: Vector Z -> Vector Float

toZ' :: Vector Float -> Vector Z

Container Vector Z Source # 
Container Vector I Source # 
Container Vector e => Konst e Int Vector Source # 

Methods

konst :: e -> Int -> Vector e Source #

Container Vector (Complex Double) Source # 

Methods

conj' :: Vector (Complex Double) -> Vector (Complex Double)

size' :: Vector (Complex Double) -> IndexOf Vector

scalar' :: Complex Double -> Vector (Complex Double)

scale' :: Complex Double -> Vector (Complex Double) -> Vector (Complex Double)

addConstant :: Complex Double -> Vector (Complex Double) -> Vector (Complex Double)

add' :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

sub :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

mul :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

equal :: Vector (Complex Double) -> Vector (Complex Double) -> Bool

cmap' :: Element b => (Complex Double -> b) -> Vector (Complex Double) -> Vector b

konst' :: Complex Double -> IndexOf Vector -> Vector (Complex Double)

build' :: IndexOf Vector -> ArgOf Vector (Complex Double) -> Vector (Complex Double)

atIndex' :: Vector (Complex Double) -> IndexOf Vector -> Complex Double

minIndex' :: Vector (Complex Double) -> IndexOf Vector

maxIndex' :: Vector (Complex Double) -> IndexOf Vector

minElement' :: Vector (Complex Double) -> Complex Double

maxElement' :: Vector (Complex Double) -> Complex Double

sumElements' :: Vector (Complex Double) -> Complex Double

prodElements' :: Vector (Complex Double) -> Complex Double

step' :: Vector (Complex Double) -> Vector (Complex Double)

ccompare' :: Vector (Complex Double) -> Vector (Complex Double) -> Vector I

cselect' :: Vector I -> Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

find' :: (Complex Double -> Bool) -> Vector (Complex Double) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Complex Double -> [(IndexOf Vector, Complex Double)] -> Vector (Complex Double)

accum' :: Vector (Complex Double) -> (Complex Double -> Complex Double -> Complex Double) -> [(IndexOf Vector, Complex Double)] -> Vector (Complex Double)

scaleRecip :: Complex Double -> Vector (Complex Double) -> Vector (Complex Double)

divide :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

arctan2' :: Vector (Complex Double) -> Vector (Complex Double) -> Vector (Complex Double)

cmod' :: Complex Double -> Vector (Complex Double) -> Vector (Complex Double)

fromInt' :: Vector I -> Vector (Complex Double)

toInt' :: Vector (Complex Double) -> Vector I

fromZ' :: Vector Z -> Vector (Complex Double)

toZ' :: Vector (Complex Double) -> Vector Z

Container Vector (Complex Float) Source # 

Methods

conj' :: Vector (Complex Float) -> Vector (Complex Float)

size' :: Vector (Complex Float) -> IndexOf Vector

scalar' :: Complex Float -> Vector (Complex Float)

scale' :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)

addConstant :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)

add' :: Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

sub :: Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

mul :: Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

equal :: Vector (Complex Float) -> Vector (Complex Float) -> Bool

cmap' :: Element b => (Complex Float -> b) -> Vector (Complex Float) -> Vector b

konst' :: Complex Float -> IndexOf Vector -> Vector (Complex Float)

build' :: IndexOf Vector -> ArgOf Vector (Complex Float) -> Vector (Complex Float)

atIndex' :: Vector (Complex Float) -> IndexOf Vector -> Complex Float

minIndex' :: Vector (Complex Float) -> IndexOf Vector

maxIndex' :: Vector (Complex Float) -> IndexOf Vector

minElement' :: Vector (Complex Float) -> Complex Float

maxElement' :: Vector (Complex Float) -> Complex Float

sumElements' :: Vector (Complex Float) -> Complex Float

prodElements' :: Vector (Complex Float) -> Complex Float

step' :: Vector (Complex Float) -> Vector (Complex Float)

ccompare' :: Vector (Complex Float) -> Vector (Complex Float) -> Vector I

cselect' :: Vector I -> Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

find' :: (Complex Float -> Bool) -> Vector (Complex Float) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Complex Float -> [(IndexOf Vector, Complex Float)] -> Vector (Complex Float)

accum' :: Vector (Complex Float) -> (Complex Float -> Complex Float -> Complex Float) -> [(IndexOf Vector, Complex Float)] -> Vector (Complex Float)

scaleRecip :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)

divide :: Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

arctan2' :: Vector (Complex Float) -> Vector (Complex Float) -> Vector (Complex Float)

cmod' :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)

fromInt' :: Vector I -> Vector (Complex Float)

toInt' :: Vector (Complex Float) -> Vector I

fromZ' :: Vector Z -> Vector (Complex Float)

toZ' :: Vector (Complex Float) -> Vector Z

KnownNat n => Sized (C n) Vector Source # 
KnownNat n => Sized (R n) Vector Source # 
KnownNat m => Container Vector (Mod m Z) Source # 

Methods

conj' :: Vector (Mod m Z) -> Vector (Mod m Z)

size' :: Vector (Mod m Z) -> IndexOf Vector

scalar' :: Mod m Z -> Vector (Mod m Z)

scale' :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

addConstant :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

add' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

sub :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

mul :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

equal :: Vector (Mod m Z) -> Vector (Mod m Z) -> Bool

cmap' :: Element b => (Mod m Z -> b) -> Vector (Mod m Z) -> Vector b

konst' :: Mod m Z -> IndexOf Vector -> Vector (Mod m Z)

build' :: IndexOf Vector -> ArgOf Vector (Mod m Z) -> Vector (Mod m Z)

atIndex' :: Vector (Mod m Z) -> IndexOf Vector -> Mod m Z

minIndex' :: Vector (Mod m Z) -> IndexOf Vector

maxIndex' :: Vector (Mod m Z) -> IndexOf Vector

minElement' :: Vector (Mod m Z) -> Mod m Z

maxElement' :: Vector (Mod m Z) -> Mod m Z

sumElements' :: Vector (Mod m Z) -> Mod m Z

prodElements' :: Vector (Mod m Z) -> Mod m Z

step' :: Vector (Mod m Z) -> Vector (Mod m Z)

ccompare' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector I

cselect' :: Vector I -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

find' :: (Mod m Z -> Bool) -> Vector (Mod m Z) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Mod m Z -> [(IndexOf Vector, Mod m Z)] -> Vector (Mod m Z)

accum' :: Vector (Mod m Z) -> (Mod m Z -> Mod m Z -> Mod m Z) -> [(IndexOf Vector, Mod m Z)] -> Vector (Mod m Z)

scaleRecip :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

divide :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

arctan2' :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z)

cmod' :: Mod m Z -> Vector (Mod m Z) -> Vector (Mod m Z)

fromInt' :: Vector I -> Vector (Mod m Z)

toInt' :: Vector (Mod m Z) -> Vector I

fromZ' :: Vector Z -> Vector (Mod m Z)

toZ' :: Vector (Mod m Z) -> Vector Z

KnownNat m => Container Vector (Mod m I) Source # 

Methods

conj' :: Vector (Mod m I) -> Vector (Mod m I)

size' :: Vector (Mod m I) -> IndexOf Vector

scalar' :: Mod m I -> Vector (Mod m I)

scale' :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

addConstant :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

add' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

sub :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

mul :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

equal :: Vector (Mod m I) -> Vector (Mod m I) -> Bool

cmap' :: Element b => (Mod m I -> b) -> Vector (Mod m I) -> Vector b

konst' :: Mod m I -> IndexOf Vector -> Vector (Mod m I)

build' :: IndexOf Vector -> ArgOf Vector (Mod m I) -> Vector (Mod m I)

atIndex' :: Vector (Mod m I) -> IndexOf Vector -> Mod m I

minIndex' :: Vector (Mod m I) -> IndexOf Vector

maxIndex' :: Vector (Mod m I) -> IndexOf Vector

minElement' :: Vector (Mod m I) -> Mod m I

maxElement' :: Vector (Mod m I) -> Mod m I

sumElements' :: Vector (Mod m I) -> Mod m I

prodElements' :: Vector (Mod m I) -> Mod m I

step' :: Vector (Mod m I) -> Vector (Mod m I)

ccompare' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector I

cselect' :: Vector I -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

find' :: (Mod m I -> Bool) -> Vector (Mod m I) -> [IndexOf Vector]

assoc' :: IndexOf Vector -> Mod m I -> [(IndexOf Vector, Mod m I)] -> Vector (Mod m I)

accum' :: Vector (Mod m I) -> (Mod m I -> Mod m I -> Mod m I) -> [(IndexOf Vector, Mod m I)] -> Vector (Mod m I)

scaleRecip :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

divide :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

arctan2' :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I)

cmod' :: Mod m I -> Vector (Mod m I) -> Vector (Mod m I)

fromInt' :: Vector I -> Vector (Mod m I)

toInt' :: Vector (Mod m I) -> Vector I

fromZ' :: Vector Z -> Vector (Mod m I)

toZ' :: Vector (Mod m I) -> Vector Z

Container Vector e => Build Int (e -> e) Vector e Source # 

Methods

build :: Int -> (e -> e) -> Vector e Source #

Storable a => IsList (Vector a) 

Associated Types

type Item (Vector a) :: * #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

(Storable a, Eq a) => Eq (Vector a) 

Methods

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

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

(Data a, Storable a) => Data (Vector a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) #

toConstr :: Vector a -> Constr #

dataTypeOf :: Vector a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

KnownNat m => Num (Vector (Mod m Z)) # 

Methods

(+) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

(-) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

(*) :: Vector (Mod m Z) -> Vector (Mod m Z) -> Vector (Mod m Z) #

negate :: Vector (Mod m Z) -> Vector (Mod m Z) #

abs :: Vector (Mod m Z) -> Vector (Mod m Z) #

signum :: Vector (Mod m Z) -> Vector (Mod m Z) #

fromInteger :: Integer -> Vector (Mod m Z) #

KnownNat m => Num (Vector (Mod m I)) # 

Methods

(+) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

(-) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

(*) :: Vector (Mod m I) -> Vector (Mod m I) -> Vector (Mod m I) #

negate :: Vector (Mod m I) -> Vector (Mod m I) #

abs :: Vector (Mod m I) -> Vector (Mod m I) #

signum :: Vector (Mod m I) -> Vector (Mod m I) #

fromInteger :: Integer -> Vector (Mod m I) #

(Storable a, Ord a) => Ord (Vector a) 

Methods

compare :: Vector a -> Vector a -> Ordering #

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

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

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

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

max :: Vector a -> Vector a -> Vector a #

min :: Vector a -> Vector a -> Vector a #

(Read a, Storable a) => Read (Vector a) 
(Show a, Storable a) => Show (Vector a) 

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Storable a => Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

Storable t => TransArray (Vector t) Source # 

Associated Types

type Trans (Vector t) b :: * Source #

type TransRaw (Vector t) b :: * Source #

Methods

apply :: Vector t -> (b -> IO r) -> Trans (Vector t) b -> IO r Source #

applyRaw :: Vector t -> (b -> IO r) -> TransRaw (Vector t) b -> IO r Source #

Container Vector t => Additive (Vector t) Source # 

Methods

add :: Vector t -> Vector t -> Vector t Source #

Normed (Vector Float) Source # 
Normed (Vector (Complex Float)) Source # 
Normed (Vector C) Source # 
Normed (Vector R) Source # 
Normed (Vector Z) Source # 
Normed (Vector I) Source # 
KnownNat m => Normed (Vector (Mod m Z)) Source # 

Methods

norm_0 :: Vector (Mod m Z) -> R Source #

norm_1 :: Vector (Mod m Z) -> R Source #

norm_2 :: Vector (Mod m Z) -> R Source #

norm_Inf :: Vector (Mod m Z) -> R Source #

KnownNat m => Normed (Vector (Mod m I)) Source # 

Methods

norm_0 :: Vector (Mod m I) -> R Source #

norm_1 :: Vector (Mod m I) -> R Source #

norm_2 :: Vector (Mod m I) -> R Source #

norm_Inf :: Vector (Mod m I) -> R Source #

Indexable (Vector Double) Double Source # 

Methods

(!) :: Vector Double -> Int -> Double Source #

Indexable (Vector Float) Float Source # 

Methods

(!) :: Vector Float -> Int -> Float Source #

Indexable (Vector Z) Z Source # 

Methods

(!) :: Vector Z -> Int -> Z Source #

Indexable (Vector I) I Source # 

Methods

(!) :: Vector I -> Int -> I Source #

Indexable (Vector (Complex Double)) (Complex Double) Source # 
Indexable (Vector (Complex Float)) (Complex Float) Source # 
Element t => Indexable (Matrix t) (Vector t) Source # 

Methods

(!) :: Matrix t -> Int -> Vector t Source #

(Storable t, Indexable (Vector t) t) => Indexable (Vector (Mod m t)) (Mod m t) Source # 

Methods

(!) :: Vector (Mod m t) -> Int -> Mod m t Source #

type Mutable Vector 
type IndexOf Vector Source # 
type Item (Vector a) 
type Item (Vector a) = a
type Trans (Vector t) b Source # 
type Trans (Vector t) b = CInt -> Ptr t -> b
type TransRaw (Vector t) b Source # 
type TransRaw (Vector t) b = CInt -> Ptr t -> b

data Matrix t Source #

Matrix representation suitable for BLAS/LAPACK computations.

Instances

Complexable Matrix Source # 

Methods

toComplex' :: RealElement e => (Matrix e, Matrix e) -> Matrix (Complex e)

fromComplex' :: RealElement e => Matrix (Complex e) -> (Matrix e, Matrix e)

comp' :: RealElement e => Matrix e -> Matrix (Complex e)

single' :: Precision a b => Matrix b -> Matrix a

double' :: Precision a b => Matrix a -> Matrix b

LSDiv Matrix Source # 

Methods

linSolve :: Field t => Matrix t -> Matrix t -> Matrix t

Container Matrix t => Linear t Matrix Source # 

Methods

scale :: t -> Matrix t -> Matrix t Source #

(Num a, Element a, Container Vector a) => Container Matrix a Source # 

Methods

conj' :: Matrix a -> Matrix a

size' :: Matrix a -> IndexOf Matrix

scalar' :: a -> Matrix a

scale' :: a -> Matrix a -> Matrix a

addConstant :: a -> Matrix a -> Matrix a

add' :: Matrix a -> Matrix a -> Matrix a

sub :: Matrix a -> Matrix a -> Matrix a

mul :: Matrix a -> Matrix a -> Matrix a

equal :: Matrix a -> Matrix a -> Bool

cmap' :: Element b => (a -> b) -> Matrix a -> Matrix b

konst' :: a -> IndexOf Matrix -> Matrix a

build' :: IndexOf Matrix -> ArgOf Matrix a -> Matrix a

atIndex' :: Matrix a -> IndexOf Matrix -> a

minIndex' :: Matrix a -> IndexOf Matrix

maxIndex' :: Matrix a -> IndexOf Matrix

minElement' :: Matrix a -> a

maxElement' :: Matrix a -> a

sumElements' :: Matrix a -> a

prodElements' :: Matrix a -> a

step' :: Matrix a -> Matrix a

ccompare' :: Matrix a -> Matrix a -> Matrix I

cselect' :: Matrix I -> Matrix a -> Matrix a -> Matrix a -> Matrix a

find' :: (a -> Bool) -> Matrix a -> [IndexOf Matrix]

assoc' :: IndexOf Matrix -> a -> [(IndexOf Matrix, a)] -> Matrix a

accum' :: Matrix a -> (a -> a -> a) -> [(IndexOf Matrix, a)] -> Matrix a

scaleRecip :: a -> Matrix a -> Matrix a

divide :: Matrix a -> Matrix a -> Matrix a

arctan2' :: Matrix a -> Matrix a -> Matrix a

cmod' :: a -> Matrix a -> Matrix a

fromInt' :: Matrix I -> Matrix a

toInt' :: Matrix a -> Matrix I

fromZ' :: Matrix Z -> Matrix a

toZ' :: Matrix a -> Matrix Z

(Num e, Container Vector e) => Konst e (Int, Int) Matrix Source # 

Methods

konst :: e -> (Int, Int) -> Matrix e Source #

(KnownNat m, KnownNat n) => Sized (M m n) Matrix Source # 

Methods

konst :: -> M m n Source #

unwrap :: M m n -> Matrix Source #

fromList :: [] -> M m n Source #

extract :: M m n -> Matrix Source #

create :: Matrix -> Maybe (M m n) Source #

size :: M m n -> IndexOf Matrix Source #

(KnownNat m, KnownNat n) => Sized (L m n) Matrix Source # 

Methods

konst :: -> L m n Source #

unwrap :: L m n -> Matrix Source #

fromList :: [] -> L m n Source #

extract :: L m n -> Matrix Source #

create :: Matrix -> Maybe (L m n) Source #

size :: L m n -> IndexOf Matrix Source #

(Storable t, NFData t) => NFData (Matrix t) Source # 

Methods

rnf :: Matrix t -> () #

Storable t => TransArray (Matrix t) Source # 

Associated Types

type Trans (Matrix t) b :: * Source #

type TransRaw (Matrix t) b :: * Source #

Methods

apply :: Matrix t -> (b -> IO r) -> Trans (Matrix t) b -> IO r Source #

applyRaw :: Matrix t -> (b -> IO r) -> TransRaw (Matrix t) b -> IO r Source #

KnownNat m => Testable (Matrix (Mod m I)) Source # 

Methods

checkT :: Matrix (Mod m I) -> (Bool, IO ()) Source #

ioCheckT :: Matrix (Mod m I) -> IO (Bool, IO ()) Source #

Container Matrix t => Additive (Matrix t) Source # 

Methods

add :: Matrix t -> Matrix t -> Matrix t Source #

Normed (Matrix C) Source # 
Normed (Matrix R) Source # 
(CTrans t, Container Vector t) => Transposable (Matrix t) (Matrix t) Source # 

Methods

tr :: Matrix t -> Matrix t Source #

tr' :: Matrix t -> Matrix t Source #

Element t => Indexable (Matrix t) (Vector t) Source # 

Methods

(!) :: Matrix t -> Int -> Vector t Source #

Container Matrix e => Build (Int, Int) (e -> e -> e) Matrix e Source # 

Methods

build :: (Int, Int) -> (e -> e -> e) -> Matrix e Source #

type IndexOf Matrix Source # 
type IndexOf Matrix = (Int, Int)
type Trans (Matrix t) b Source # 
type Trans (Matrix t) b = CInt -> CInt -> CInt -> CInt -> Ptr t -> b
type TransRaw (Matrix t) b Source # 
type TransRaw (Matrix t) b = CInt -> CInt -> Ptr t -> b

data GMatrix Source #

General matrix with specialized internal representations for dense, sparse, diagonal, banded, and constant elements.

>>> let m = mkSparse [((0,999),1.0),((1,1999),2.0)]
>>> m
SparseR {gmCSR = CSR {csrVals = fromList [1.0,2.0],
                      csrCols = fromList [1000,2000],
                      csrRows = fromList [1,2,3],
                      csrNRows = 2,
                      csrNCols = 2000},
                      nRows = 2,
                      nCols = 2000}
>>> let m = mkDense (mat 2 [1..4])
>>> m
Dense {gmDense = (2><2)
 [ 1.0, 2.0
 , 3.0, 4.0 ], nRows = 2, nCols = 2}