diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-16 14:13:49 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-16 14:13:49 +0200 |
commit | 51f4cc7b4b301142b8df73568ffaa448f9e6dd50 (patch) | |
tree | 7f9b9a26344a23a0d1e3fb6e4105fe968465cd2a /packages/hmatrix/src/Numeric | |
parent | 1838c4248679b7476bb8716a76171712dc3cd335 (diff) |
license changes, reexport modules
Diffstat (limited to 'packages/hmatrix/src/Numeric')
-rw-r--r-- | packages/hmatrix/src/Numeric/Container.hs | 241 | ||||
-rw-r--r-- | packages/hmatrix/src/Numeric/HMatrix.hs | 139 | ||||
-rw-r--r-- | packages/hmatrix/src/Numeric/HMatrix/Data.hs | 70 | ||||
-rw-r--r-- | packages/hmatrix/src/Numeric/HMatrix/Devel.hs | 69 |
4 files changed, 241 insertions, 278 deletions
diff --git a/packages/hmatrix/src/Numeric/Container.hs b/packages/hmatrix/src/Numeric/Container.hs new file mode 100644 index 0000000..146780d --- /dev/null +++ b/packages/hmatrix/src/Numeric/Container.hs | |||
@@ -0,0 +1,241 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
5 | {-# LANGUAGE FunctionalDependencies #-} | ||
6 | {-# LANGUAGE UndecidableInstances #-} | ||
7 | |||
8 | ----------------------------------------------------------------------------- | ||
9 | -- | | ||
10 | -- Module : Numeric.Container | ||
11 | -- Copyright : (c) Alberto Ruiz 2010-14 | ||
12 | -- License : BSD3 | ||
13 | -- Maintainer : Alberto Ruiz | ||
14 | -- Stability : provisional | ||
15 | -- Portability : portable | ||
16 | -- | ||
17 | -- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines. | ||
18 | -- | ||
19 | -- The 'Container' class is used to define optimized generic functions which work | ||
20 | -- on 'Vector' and 'Matrix' with real or complex elements. | ||
21 | -- | ||
22 | -- Some of these functions are also available in the instances of the standard | ||
23 | -- numeric Haskell classes provided by "Numeric.LinearAlgebra". | ||
24 | -- | ||
25 | ----------------------------------------------------------------------------- | ||
26 | {-# OPTIONS_HADDOCK hide #-} | ||
27 | |||
28 | module Numeric.Container ( | ||
29 | -- * Basic functions | ||
30 | module Data.Packed, | ||
31 | konst, build, | ||
32 | linspace, | ||
33 | diag, ident, | ||
34 | ctrans, | ||
35 | -- * Generic operations | ||
36 | Container(..), | ||
37 | -- * Matrix product | ||
38 | Product(..), udot, dot, (◇), | ||
39 | Mul(..), | ||
40 | Contraction(..), | ||
41 | optimiseMult, | ||
42 | mXm,mXv,vXm,LSDiv(..), | ||
43 | outer, kronecker, | ||
44 | -- * Element conversion | ||
45 | Convert(..), | ||
46 | Complexable(), | ||
47 | RealElement(), | ||
48 | |||
49 | RealOf, ComplexOf, SingleOf, DoubleOf, | ||
50 | |||
51 | IndexOf, | ||
52 | module Data.Complex | ||
53 | ) where | ||
54 | |||
55 | import Data.Packed hiding (stepD, stepF, condD, condF, conjugateC, conjugateQ) | ||
56 | import Data.Packed.Numeric | ||
57 | import Data.Complex | ||
58 | import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD) | ||
59 | import Data.Monoid(Monoid(mconcat)) | ||
60 | |||
61 | ------------------------------------------------------------------ | ||
62 | |||
63 | {- | Creates a real vector containing a range of values: | ||
64 | |||
65 | >>> linspace 5 (-3,7::Double) | ||
66 | fromList [-3.0,-0.5,2.0,4.5,7.0]@ | ||
67 | |||
68 | >>> linspace 5 (8,2+i) :: Vector (Complex Double) | ||
69 | fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0] | ||
70 | |||
71 | Logarithmic spacing can be defined as follows: | ||
72 | |||
73 | @logspace n (a,b) = 10 ** linspace n (a,b)@ | ||
74 | -} | ||
75 | linspace :: (Container Vector e) => Int -> (e, e) -> Vector e | ||
76 | linspace 0 (a,b) = fromList[(a+b)/2] | ||
77 | linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1] | ||
78 | where s = (b-a)/fromIntegral (n-1) | ||
79 | |||
80 | -------------------------------------------------------- | ||
81 | |||
82 | class Contraction a b c | a b -> c | ||
83 | where | ||
84 | infixl 7 <.> | ||
85 | {- | Matrix product, matrix vector product, and dot product | ||
86 | |||
87 | Examples: | ||
88 | |||
89 | >>> let a = (3><4) [1..] :: Matrix Double | ||
90 | >>> let v = fromList [1,0,2,-1] :: Vector Double | ||
91 | >>> let u = fromList [1,2,3] :: Vector Double | ||
92 | |||
93 | >>> a | ||
94 | (3><4) | ||
95 | [ 1.0, 2.0, 3.0, 4.0 | ||
96 | , 5.0, 6.0, 7.0, 8.0 | ||
97 | , 9.0, 10.0, 11.0, 12.0 ] | ||
98 | |||
99 | matrix × matrix: | ||
100 | |||
101 | >>> disp 2 (a <.> trans a) | ||
102 | 3x3 | ||
103 | 30 70 110 | ||
104 | 70 174 278 | ||
105 | 110 278 446 | ||
106 | |||
107 | matrix × vector: | ||
108 | |||
109 | >>> a <.> v | ||
110 | fromList [3.0,11.0,19.0] | ||
111 | |||
112 | dot product: | ||
113 | |||
114 | >>> u <.> fromList[3,2,1::Double] | ||
115 | 10 | ||
116 | |||
117 | For complex vectors the first argument is conjugated: | ||
118 | |||
119 | >>> fromList [1,i] <.> fromList[2*i+1,3] | ||
120 | 1.0 :+ (-1.0) | ||
121 | |||
122 | >>> fromList [1,i,1-i] <.> complex a | ||
123 | fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0] | ||
124 | |||
125 | -} | ||
126 | (<.>) :: a -> b -> c | ||
127 | |||
128 | |||
129 | instance (Product t, Container Vector t) => Contraction (Vector t) (Vector t) t where | ||
130 | u <.> v = conj u `udot` v | ||
131 | |||
132 | instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where | ||
133 | (<.>) = mXv | ||
134 | |||
135 | instance (Container Vector t, Product t) => Contraction (Vector t) (Matrix t) (Vector t) where | ||
136 | (<.>) v m = (conj v) `vXm` m | ||
137 | |||
138 | instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where | ||
139 | (<.>) = mXm | ||
140 | |||
141 | |||
142 | -------------------------------------------------------------------------------- | ||
143 | |||
144 | class Mul a b c | a b -> c where | ||
145 | infixl 7 <> | ||
146 | -- | Matrix-matrix, matrix-vector, and vector-matrix products. | ||
147 | (<>) :: Product t => a t -> b t -> c t | ||
148 | |||
149 | instance Mul Matrix Matrix Matrix where | ||
150 | (<>) = mXm | ||
151 | |||
152 | instance Mul Matrix Vector Vector where | ||
153 | (<>) m v = flatten $ m <> asColumn v | ||
154 | |||
155 | instance Mul Vector Matrix Vector where | ||
156 | (<>) v m = flatten $ asRow v <> m | ||
157 | |||
158 | -------------------------------------------------------------------------------- | ||
159 | |||
160 | class LSDiv c where | ||
161 | infixl 7 <\> | ||
162 | -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD) | ||
163 | (<\>) :: Field t => Matrix t -> c t -> c t | ||
164 | |||
165 | instance LSDiv Vector where | ||
166 | m <\> v = flatten (linearSolveSVD m (reshape 1 v)) | ||
167 | |||
168 | instance LSDiv Matrix where | ||
169 | (<\>) = linearSolveSVD | ||
170 | |||
171 | -------------------------------------------------------------------------------- | ||
172 | |||
173 | class Konst e d c | d -> c, c -> d | ||
174 | where | ||
175 | -- | | ||
176 | -- >>> konst 7 3 :: Vector Float | ||
177 | -- fromList [7.0,7.0,7.0] | ||
178 | -- | ||
179 | -- >>> konst i (3::Int,4::Int) | ||
180 | -- (3><4) | ||
181 | -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 | ||
182 | -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 | ||
183 | -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ] | ||
184 | -- | ||
185 | konst :: e -> d -> c e | ||
186 | |||
187 | instance Container Vector e => Konst e Int Vector | ||
188 | where | ||
189 | konst = konst' | ||
190 | |||
191 | instance Container Vector e => Konst e (Int,Int) Matrix | ||
192 | where | ||
193 | konst = konst' | ||
194 | |||
195 | -------------------------------------------------------------------------------- | ||
196 | |||
197 | class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f | ||
198 | where | ||
199 | -- | | ||
200 | -- >>> build 5 (**2) :: Vector Double | ||
201 | -- fromList [0.0,1.0,4.0,9.0,16.0] | ||
202 | -- | ||
203 | -- Hilbert matrix of order N: | ||
204 | -- | ||
205 | -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double | ||
206 | -- >>> putStr . dispf 2 $ hilb 3 | ||
207 | -- 3x3 | ||
208 | -- 1.00 0.50 0.33 | ||
209 | -- 0.50 0.33 0.25 | ||
210 | -- 0.33 0.25 0.20 | ||
211 | -- | ||
212 | build :: d -> f -> c e | ||
213 | |||
214 | instance Container Vector e => Build Int (e -> e) Vector e | ||
215 | where | ||
216 | build = build' | ||
217 | |||
218 | instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e | ||
219 | where | ||
220 | build = build' | ||
221 | |||
222 | -------------------------------------------------------------------------------- | ||
223 | |||
224 | {- | alternative operator for '(\<.\>)' | ||
225 | |||
226 | x25c7, white diamond | ||
227 | |||
228 | -} | ||
229 | (◇) :: Contraction a b c => a -> b -> c | ||
230 | infixl 7 ◇ | ||
231 | (◇) = (<.>) | ||
232 | |||
233 | -- | dot product: @cdot u v = 'udot' ('conj' u) v@ | ||
234 | dot :: (Container Vector t, Product t) => Vector t -> Vector t -> t | ||
235 | dot u v = udot (conj u) v | ||
236 | |||
237 | -------------------------------------------------------------------------------- | ||
238 | |||
239 | optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t | ||
240 | optimiseMult = mconcat | ||
241 | |||
diff --git a/packages/hmatrix/src/Numeric/HMatrix.hs b/packages/hmatrix/src/Numeric/HMatrix.hs deleted file mode 100644 index fcd3e02..0000000 --- a/packages/hmatrix/src/Numeric/HMatrix.hs +++ /dev/null | |||
@@ -1,139 +0,0 @@ | |||
1 | ----------------------------------------------------------------------------- | ||
2 | {- | | ||
3 | Module : Numeric.HMatrix | ||
4 | Copyright : (c) Alberto Ruiz 2006-14 | ||
5 | License : GPL | ||
6 | |||
7 | Maintainer : Alberto Ruiz | ||
8 | Stability : provisional | ||
9 | |||
10 | This module reexports the most common Linear Algebra functions. | ||
11 | |||
12 | -} | ||
13 | ----------------------------------------------------------------------------- | ||
14 | module Numeric.HMatrix ( | ||
15 | |||
16 | -- * Basic types and data processing | ||
17 | module Numeric.HMatrix.Data, | ||
18 | |||
19 | -- | The standard numeric classes are defined elementwise: | ||
20 | -- | ||
21 | -- >>> fromList [1,2,3] * fromList [3,0,-2 :: Double] | ||
22 | -- fromList [3.0,0.0,-6.0] | ||
23 | -- | ||
24 | -- >>> (3><3) [1..9] * ident 3 :: Matrix Double | ||
25 | -- (3><3) | ||
26 | -- [ 1.0, 0.0, 0.0 | ||
27 | -- , 0.0, 5.0, 0.0 | ||
28 | -- , 0.0, 0.0, 9.0 ] | ||
29 | -- | ||
30 | -- In arithmetic operations single-element vectors and matrices | ||
31 | -- (created from numeric literals or using 'scalar') automatically | ||
32 | -- expand to match the dimensions of the other operand: | ||
33 | -- | ||
34 | -- >>> 5 + 2*ident 3 :: Matrix Double | ||
35 | -- (3><3) | ||
36 | -- [ 7.0, 5.0, 5.0 | ||
37 | -- , 5.0, 7.0, 5.0 | ||
38 | -- , 5.0, 5.0, 7.0 ] | ||
39 | -- | ||
40 | |||
41 | -- * Products | ||
42 | (<.>), | ||
43 | |||
44 | -- | The matrix product is also implemented in the "Data.Monoid" instance for Matrix, where | ||
45 | -- single-element matrices (created from numeric literals or using 'scalar') | ||
46 | -- are used for scaling. | ||
47 | -- | ||
48 | -- >>> let m = (2><3)[1..] :: Matrix Double | ||
49 | -- >>> m <> 2 <> diagl[0.5,1,0] | ||
50 | -- (2><3) | ||
51 | -- [ 1.0, 4.0, 0.0 | ||
52 | -- , 4.0, 10.0, 0.0 ] | ||
53 | -- | ||
54 | -- mconcat uses 'optimiseMult' to get the optimal association order. | ||
55 | |||
56 | (◇), | ||
57 | outer, kronecker, cross, | ||
58 | scale, | ||
59 | sumElements, prodElements, absSum, | ||
60 | |||
61 | -- * Linear Systems | ||
62 | (<\>), | ||
63 | linearSolve, | ||
64 | linearSolveLS, | ||
65 | linearSolveSVD, | ||
66 | luSolve, | ||
67 | cholSolve, | ||
68 | |||
69 | -- * Inverse and pseudoinverse | ||
70 | inv, pinv, pinvTol, | ||
71 | |||
72 | -- * Determinant and rank | ||
73 | rcond, rank, ranksv, | ||
74 | det, invlndet, | ||
75 | |||
76 | -- * Singular value decomposition | ||
77 | svd, | ||
78 | fullSVD, | ||
79 | thinSVD, | ||
80 | compactSVD, | ||
81 | singularValues, | ||
82 | leftSV, rightSV, | ||
83 | |||
84 | -- * Eigensystems | ||
85 | eig, eigSH, eigSH', | ||
86 | eigenvalues, eigenvaluesSH, eigenvaluesSH', | ||
87 | geigSH', | ||
88 | |||
89 | -- * QR | ||
90 | qr, rq, qrRaw, qrgr, | ||
91 | |||
92 | -- * Cholesky | ||
93 | chol, cholSH, mbCholSH, | ||
94 | |||
95 | -- * Hessenberg | ||
96 | hess, | ||
97 | |||
98 | -- * Schur | ||
99 | schur, | ||
100 | |||
101 | -- * LU | ||
102 | lu, luPacked, | ||
103 | |||
104 | -- * Matrix functions | ||
105 | expm, | ||
106 | sqrtm, | ||
107 | matFunc, | ||
108 | |||
109 | -- * Nullspace | ||
110 | nullspacePrec, | ||
111 | nullVector, | ||
112 | nullspaceSVD, | ||
113 | null1, null1sym, | ||
114 | |||
115 | orth, | ||
116 | |||
117 | -- * Norms | ||
118 | norm1, norm2, normInf, pnorm, NormType(..), | ||
119 | |||
120 | -- * Correlation and Convolution | ||
121 | corr, conv, corrMin, corr2, conv2, | ||
122 | |||
123 | -- * Random arrays | ||
124 | rand, randn, RandDist(..), randomVector, gaussianSample, uniformSample, | ||
125 | |||
126 | -- * Misc | ||
127 | meanCov, peps, relativeError, haussholder, optimiseMult, udot | ||
128 | ) where | ||
129 | |||
130 | import Numeric.HMatrix.Data | ||
131 | |||
132 | --import Numeric.Matrix() | ||
133 | --import Numeric.Vector() | ||
134 | import Numeric.Container | ||
135 | import Numeric.LinearAlgebra.Algorithms | ||
136 | import Numeric.LinearAlgebra.Util | ||
137 | import Numeric.Random | ||
138 | |||
139 | |||
diff --git a/packages/hmatrix/src/Numeric/HMatrix/Data.hs b/packages/hmatrix/src/Numeric/HMatrix/Data.hs deleted file mode 100644 index 5d7ce4f..0000000 --- a/packages/hmatrix/src/Numeric/HMatrix/Data.hs +++ /dev/null | |||
@@ -1,70 +0,0 @@ | |||
1 | -------------------------------------------------------------------------------- | ||
2 | {- | | ||
3 | Module : Numeric.HMatrix.Data | ||
4 | Copyright : (c) Alberto Ruiz 2014 | ||
5 | License : GPL | ||
6 | |||
7 | Maintainer : Alberto Ruiz | ||
8 | Stability : provisional | ||
9 | |||
10 | Basic data processing. | ||
11 | |||
12 | -} | ||
13 | -------------------------------------------------------------------------------- | ||
14 | |||
15 | module Numeric.HMatrix.Data( | ||
16 | |||
17 | -- * Vector | ||
18 | -- | 1D arrays are storable vectors from the vector package. | ||
19 | |||
20 | Vector, (|>), dim, (@>), | ||
21 | |||
22 | -- * Matrix | ||
23 | Matrix, (><), size, (@@>), trans, ctrans, | ||
24 | |||
25 | -- * Construction | ||
26 | scalar, konst, build, assoc, accum, linspace, -- ones, zeros, | ||
27 | |||
28 | -- * Diagonal | ||
29 | ident, diag, diagl, diagRect, takeDiag, | ||
30 | |||
31 | -- * Data manipulation | ||
32 | fromList, toList, subVector, takesV, vjoin, | ||
33 | flatten, reshape, asRow, asColumn, row, col, | ||
34 | fromRows, toRows, fromColumns, toColumns, fromLists, toLists, fromArray2D, | ||
35 | takeRows, dropRows, takeColumns, dropColumns, subMatrix, (?), (¿), fliprl, flipud, | ||
36 | |||
37 | -- * Block matrix | ||
38 | fromBlocks, (¦), (——), diagBlock, repmat, toBlocks, toBlocksEvery, | ||
39 | |||
40 | -- * Mapping functions | ||
41 | conj, cmap, step, cond, | ||
42 | |||
43 | -- * Find elements | ||
44 | find, maxIndex, minIndex, maxElement, minElement, atIndex, | ||
45 | |||
46 | -- * IO | ||
47 | disp, dispf, disps, dispcf, latexFormat, format, | ||
48 | loadMatrix, saveMatrix, fromFile, fileDimensions, | ||
49 | readMatrix, | ||
50 | fscanfVector, fprintfVector, freadVector, fwriteVector, | ||
51 | |||
52 | -- * Conversion | ||
53 | Convert(..), | ||
54 | |||
55 | -- * Misc | ||
56 | arctan2, | ||
57 | rows, cols, | ||
58 | separable, | ||
59 | |||
60 | module Data.Complex | ||
61 | |||
62 | ) where | ||
63 | |||
64 | import Data.Packed.Vector | ||
65 | import Data.Packed.Matrix | ||
66 | import Numeric.Container | ||
67 | import Numeric.IO | ||
68 | import Numeric.LinearAlgebra.Util | ||
69 | import Data.Complex | ||
70 | |||
diff --git a/packages/hmatrix/src/Numeric/HMatrix/Devel.hs b/packages/hmatrix/src/Numeric/HMatrix/Devel.hs deleted file mode 100644 index b921f44..0000000 --- a/packages/hmatrix/src/Numeric/HMatrix/Devel.hs +++ /dev/null | |||
@@ -1,69 +0,0 @@ | |||
1 | -------------------------------------------------------------------------------- | ||
2 | {- | | ||
3 | Module : Numeric.HMatrix.Devel | ||
4 | Copyright : (c) Alberto Ruiz 2014 | ||
5 | License : GPL | ||
6 | |||
7 | Maintainer : Alberto Ruiz | ||
8 | Stability : provisional | ||
9 | |||
10 | The library can be easily extended using the tools in this module. | ||
11 | |||
12 | -} | ||
13 | -------------------------------------------------------------------------------- | ||
14 | |||
15 | module Numeric.HMatrix.Devel( | ||
16 | -- * FFI helpers | ||
17 | -- | Sample usage, to upload a perspective matrix to a shader. | ||
18 | -- | ||
19 | -- @ glUniformMatrix4fv 0 1 (fromIntegral gl_TRUE) \`appMatrix\` perspective 0.01 100 (pi\/2) (4\/3) | ||
20 | -- @ | ||
21 | module Data.Packed.Foreign, | ||
22 | |||
23 | -- * FFI tools | ||
24 | -- | Illustrative usage examples can be found | ||
25 | -- in the @examples\/devel@ folder included in the package. | ||
26 | module Data.Packed.Development, | ||
27 | |||
28 | -- * ST | ||
29 | -- | In-place manipulation inside the ST monad. | ||
30 | -- See examples\/inplace.hs in the distribution. | ||
31 | |||
32 | -- ** Mutable Vectors | ||
33 | STVector, newVector, thawVector, freezeVector, runSTVector, | ||
34 | readVector, writeVector, modifyVector, liftSTVector, | ||
35 | -- ** Mutable Matrices | ||
36 | STMatrix, newMatrix, thawMatrix, freezeMatrix, runSTMatrix, | ||
37 | readMatrix, writeMatrix, modifyMatrix, liftSTMatrix, | ||
38 | -- ** Unsafe functions | ||
39 | newUndefinedVector, | ||
40 | unsafeReadVector, unsafeWriteVector, | ||
41 | unsafeThawVector, unsafeFreezeVector, | ||
42 | newUndefinedMatrix, | ||
43 | unsafeReadMatrix, unsafeWriteMatrix, | ||
44 | unsafeThawMatrix, unsafeFreezeMatrix, | ||
45 | |||
46 | -- * Special maps and zips | ||
47 | mapVectorWithIndex, zipVector, zipVectorWith, unzipVector, unzipVectorWith, | ||
48 | mapVectorM, mapVectorM_, mapVectorWithIndexM, mapVectorWithIndexM_, | ||
49 | foldLoop, foldVector, foldVectorG, foldVectorWithIndex, | ||
50 | mapMatrixWithIndex, mapMatrixWithIndexM, mapMatrixWithIndexM_, | ||
51 | liftMatrix, liftMatrix2, liftMatrix2Auto, | ||
52 | |||
53 | -- * Auxiliary classes | ||
54 | Element, Container, Product, Contraction, LSDiv, | ||
55 | Complexable(), RealElement(), | ||
56 | RealOf, ComplexOf, SingleOf, DoubleOf, | ||
57 | IndexOf, | ||
58 | Field, Normed | ||
59 | ) where | ||
60 | |||
61 | import Data.Packed.Foreign | ||
62 | import Data.Packed.Development | ||
63 | import Data.Packed.ST | ||
64 | import Numeric.Container(Container,Contraction,LSDiv,Product, | ||
65 | Complexable(),RealElement(), | ||
66 | RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf) | ||
67 | import Data.Packed | ||
68 | import Numeric.LinearAlgebra.Algorithms(Field,Normed) | ||
69 | |||