summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
Diffstat (limited to 'lib')
-rw-r--r--lib/Data/Packed/Development.hs1
-rw-r--r--lib/Data/Packed/Internal/Common.hs31
-rw-r--r--lib/Data/Packed/Matrix.hs15
-rw-r--r--lib/Data/Packed/Random.hs1
-rw-r--r--lib/Numeric/GSL/ODE.hs1
-rw-r--r--lib/Numeric/LinearAlgebra/Algorithms.hs44
-rw-r--r--lib/Numeric/LinearAlgebra/LAPACK.hs1
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Properties.hs2
8 files changed, 49 insertions, 47 deletions
diff --git a/lib/Data/Packed/Development.hs b/lib/Data/Packed/Development.hs
index 9f723b4..3eb7552 100644
--- a/lib/Data/Packed/Development.hs
+++ b/lib/Data/Packed/Development.hs
@@ -20,6 +20,7 @@ module Data.Packed.Development (
20 Adapt, 20 Adapt,
21 vec, mat, 21 vec, mat,
22 app1, app2, app3, app4, 22 app1, app2, app3, app4,
23 app5, app6, app7, app8, app9, app10,
23 MatrixOrder(..), orderOf, cmat, fmat, 24 MatrixOrder(..), orderOf, cmat, fmat,
24 unsafeFromForeignPtr, 25 unsafeFromForeignPtr,
25 unsafeToForeignPtr, 26 unsafeToForeignPtr,
diff --git a/lib/Data/Packed/Internal/Common.hs b/lib/Data/Packed/Internal/Common.hs
index 455b176..c348575 100644
--- a/lib/Data/Packed/Internal/Common.hs
+++ b/lib/Data/Packed/Internal/Common.hs
@@ -17,6 +17,7 @@
17module Data.Packed.Internal.Common( 17module Data.Packed.Internal.Common(
18 Adapt, 18 Adapt,
19 app1, app2, app3, app4, 19 app1, app2, app3, app4,
20 app5, app6, app7, app8, app9, app10,
20 (//), check, mbCatch, 21 (//), check, mbCatch,
21 splitEvery, common, compatdim, 22 splitEvery, common, compatdim,
22 fi, 23 fi,
@@ -69,9 +70,15 @@ fi :: Int -> CInt
69fi = fromIntegral 70fi = fromIntegral
70 71
71-- hmm.. 72-- hmm..
72ww2 w1 o1 w2 o2 f = w1 o1 $ \a1 -> w2 o2 $ \a2 -> f a1 a2 73ww2 w1 o1 w2 o2 f = w1 o1 $ w2 o2 . f
73ww3 w1 o1 w2 o2 w3 o3 f = w1 o1 $ \a1 -> ww2 w2 o2 w3 o3 (f a1) 74ww3 w1 o1 w2 o2 w3 o3 f = w1 o1 $ ww2 w2 o2 w3 o3 . f
74ww4 w1 o1 w2 o2 w3 o3 w4 o4 f = w1 o1 $ \a1 -> ww3 w2 o2 w3 o3 w4 o4 (f a1) 75ww4 w1 o1 w2 o2 w3 o3 w4 o4 f = w1 o1 $ ww3 w2 o2 w3 o3 w4 o4 . f
76ww5 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 f = w1 o1 $ ww4 w2 o2 w3 o3 w4 o4 w5 o5 . f
77ww6 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 f = w1 o1 $ ww5 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 . f
78ww7 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 f = w1 o1 $ ww6 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 . f
79ww8 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 f = w1 o1 $ ww7 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 . f
80ww9 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 f = w1 o1 $ ww8 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 . f
81ww10 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 w10 o10 f = w1 o1 $ ww9 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 w10 o10 . f
75 82
76type Adapt f t r = t -> ((f -> r) -> IO()) -> IO() 83type Adapt f t r = t -> ((f -> r) -> IO()) -> IO()
77 84
@@ -115,8 +122,22 @@ app1 f w1 o1 s = w1 o1 $ \a1 -> f // a1 // check s
115app2 f w1 o1 w2 o2 s = ww2 w1 o1 w2 o2 $ \a1 a2 -> f // a1 // a2 // check s 122app2 f w1 o1 w2 o2 s = ww2 w1 o1 w2 o2 $ \a1 a2 -> f // a1 // a2 // check s
116app3 f w1 o1 w2 o2 w3 o3 s = ww3 w1 o1 w2 o2 w3 o3 $ 123app3 f w1 o1 w2 o2 w3 o3 s = ww3 w1 o1 w2 o2 w3 o3 $
117 \a1 a2 a3 -> f // a1 // a2 // a3 // check s 124 \a1 a2 a3 -> f // a1 // a2 // a3 // check s
118app4 f w1 o1 w2 o2 w3 o3 w4 o4 s = ww4 w1 o1 w2 o2 w3 o3 w4 o4 $ 125app4 f w1 o1 w2 o2 w3 o3 w4 o4 s = ww4 w1 o1 w2 o2 w3 o3 w4 o4 $
119 \a1 a2 a3 a4 -> f // a1 // a2 // a3 // a4 // check s 126 \a1 a2 a3 a4 -> f // a1 // a2 // a3 // a4 // check s
127app5 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 s = ww5 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 $
128 \a1 a2 a3 a4 a5 -> f // a1 // a2 // a3 // a4 // a5 // check s
129app6 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 s = ww6 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 $
130 \a1 a2 a3 a4 a5 a6 -> f // a1 // a2 // a3 // a4 // a5 // a6 // check s
131app7 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 s = ww7 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 $
132 \a1 a2 a3 a4 a5 a6 a7 -> f // a1 // a2 // a3 // a4 // a5 // a6 // a7 // check s
133app8 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 s = ww8 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 $
134 \a1 a2 a3 a4 a5 a6 a7 a8 -> f // a1 // a2 // a3 // a4 // a5 // a6 // a7 // a8 // check s
135app9 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 s = ww9 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 $
136 \a1 a2 a3 a4 a5 a6 a7 a8 a9 -> f // a1 // a2 // a3 // a4 // a5 // a6 // a7 // a8 // a9 // check s
137app10 f w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 w10 o10 s = ww10 w1 o1 w2 o2 w3 o3 w4 o4 w5 o5 w6 o6 w7 o7 w8 o8 w9 o9 w10 o10 $
138 \a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 -> f // a1 // a2 // a3 // a4 // a5 // a6 // a7 // a8 // a9 // a10 // check s
139
140
120 141
121-- GSL error codes are <= 1024 142-- GSL error codes are <= 1024
122-- | error codes for the auxiliary functions required by the wrappers 143-- | error codes for the auxiliary functions required by the wrappers
@@ -151,7 +172,7 @@ check msg f = do
151 return () 172 return ()
152 173
153-- | description of GSL error codes 174-- | description of GSL error codes
154foreign import ccall "auxi.h gsl_strerror" gsl_strerror :: CInt -> IO (Ptr CChar) 175foreign import ccall "gsl_strerror" gsl_strerror :: CInt -> IO (Ptr CChar)
155 176
156-- | Error capture and conversion to Maybe 177-- | Error capture and conversion to Maybe
157mbCatch :: IO x -> IO (Maybe x) 178mbCatch :: IO x -> IO (Maybe x)
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index d91a089..4fdd2c6 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -292,21 +292,6 @@ formatScaled dec t = "E"++show o++"\n" ++ ss
292 o = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t 292 o = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t
293 fmt = '%':show (dec+3) ++ '.':show dec ++"f" 293 fmt = '%':show (dec+3) ++ '.':show dec ++"f"
294 294
295{- | Show a vector using a function for showing matrices.
296
297@disp = putStr . vecdisp (dispf 2)
298
299\> disp (linspace 10 (0,1))
30010 |> 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00
301@
302-}
303vecdisp :: (Element t) => (Matrix t -> String) -> Vector t -> String
304vecdisp f v
305 = ((show (dim v) ++ " |> ") ++) . (++"\n")
306 . unwords . lines . tail . dropWhile (not . (`elem` " \n"))
307 . f . trans . reshape 1
308 $ v
309
310-- | Tool to display matrices with latex syntax. 295-- | Tool to display matrices with latex syntax.
311latexFormat :: String -- ^ type of braces: \"matrix\", \"bmatrix\", \"pmatrix\", etc. 296latexFormat :: String -- ^ type of braces: \"matrix\", \"bmatrix\", \"pmatrix\", etc.
312 -> String -- ^ Formatted matrix, with elements separated by spaces and newlines 297 -> String -- ^ Formatted matrix, with elements separated by spaces and newlines
diff --git a/lib/Data/Packed/Random.hs b/lib/Data/Packed/Random.hs
index 7e0f91f..260e4dc 100644
--- a/lib/Data/Packed/Random.hs
+++ b/lib/Data/Packed/Random.hs
@@ -48,7 +48,6 @@ uniformSample :: Int -- ^ seed
48uniformSample seed n rgs = m where 48uniformSample seed n rgs = m where
49 (as,bs) = unzip rgs 49 (as,bs) = unzip rgs
50 a = fromList as 50 a = fromList as
51 b = fromList bs
52 cs = zipWith subtract as bs 51 cs = zipWith subtract as bs
53 d = dim a 52 d = dim a
54 dat = toRows $ reshape n $ randomVector seed Uniform (n*d) 53 dat = toRows $ reshape n $ randomVector seed Uniform (n*d)
diff --git a/lib/Numeric/GSL/ODE.hs b/lib/Numeric/GSL/ODE.hs
index f6f11f9..eca06f8 100644
--- a/lib/Numeric/GSL/ODE.hs
+++ b/lib/Numeric/GSL/ODE.hs
@@ -64,7 +64,6 @@ odeSolve xdot xi ts = odeSolveV RKf45 hi epsAbs epsRel (l2v xdot) Nothing (fromL
64 epsAbs = 1.49012e-08 64 epsAbs = 1.49012e-08
65 epsRel = 1.49012e-08 65 epsRel = 1.49012e-08
66 l2v f = \t -> fromList . f t . toList 66 l2v f = \t -> fromList . f t . toList
67 l2m f = \t -> fromLists . f t . toList
68 67
69-- | Evolution of the system with adaptive step-size control. 68-- | Evolution of the system with adaptive step-size control.
70odeSolveV 69odeSolveV
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs
index 60f5971..580f4bb 100644
--- a/lib/Numeric/LinearAlgebra/Algorithms.hs
+++ b/lib/Numeric/LinearAlgebra/Algorithms.hs
@@ -169,17 +169,17 @@ exactHermitian m = m `equal` ctrans m
169 169
170-- | Full singular value decomposition. 170-- | Full singular value decomposition.
171svd :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t) 171svd :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)
172svd = svd' 172svd = {-# SCC "svd" #-} svd'
173 173
174-- | A version of 'svd' which returns only the @min (rows m) (cols m)@ singular vectors of @m@. 174-- | A version of 'svd' which returns only the @min (rows m) (cols m)@ singular vectors of @m@.
175-- 175--
176-- If @(u,s,v) = thinSVD m@ then @m == u \<> diag s \<> trans v@. 176-- If @(u,s,v) = thinSVD m@ then @m == u \<> diag s \<> trans v@.
177thinSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t) 177thinSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)
178thinSVD = thinSVD' 178thinSVD = {-# SCC "thinSVD" #-} thinSVD'
179 179
180-- | Singular values only. 180-- | Singular values only.
181singularValues :: Field t => Matrix t -> Vector Double 181singularValues :: Field t => Matrix t -> Vector Double
182singularValues = sv' 182singularValues = {-# SCC "singularValues" #-} sv'
183 183
184-- | A version of 'svd' which returns an appropriate diagonal matrix with the singular values. 184-- | A version of 'svd' which returns an appropriate diagonal matrix with the singular values.
185-- 185--
@@ -229,50 +229,50 @@ economy svdFun m = (u', subVector 0 d s, v') where
229-------------------------------------------------------------- 229--------------------------------------------------------------
230 230
231-- | Obtains the LU decomposition of a matrix in a compact data structure suitable for 'luSolve'. 231-- | Obtains the LU decomposition of a matrix in a compact data structure suitable for 'luSolve'.
232luPacked :: Field t => Matrix t -> (Matrix t, [Int]) 232luPacked :: Field t => Matrix t -> (Matrix t, [Int])
233luPacked = luPacked' 233luPacked = {-# SCC "luPacked" #-} luPacked'
234 234
235-- | Solution of a linear system (for several right hand sides) from the precomputed LU factorization obtained by 'luPacked'. 235-- | Solution of a linear system (for several right hand sides) from the precomputed LU factorization obtained by 'luPacked'.
236luSolve :: Field t => (Matrix t, [Int]) -> Matrix t -> Matrix t 236luSolve :: Field t => (Matrix t, [Int]) -> Matrix t -> Matrix t
237luSolve = luSolve' 237luSolve = {-# SCC "luSolve" #-} luSolve'
238 238
239-- | Solve a linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition. For underconstrained or overconstrained systems use 'linearSolveLS' or 'linearSolveSVD'. 239-- | Solve a linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition. For underconstrained or overconstrained systems use 'linearSolveLS' or 'linearSolveSVD'.
240-- It is similar to 'luSolve' . 'luPacked', but @linearSolve@ raises an error if called on a singular system. 240-- It is similar to 'luSolve' . 'luPacked', but @linearSolve@ raises an error if called on a singular system.
241linearSolve :: Field t => Matrix t -> Matrix t -> Matrix t 241linearSolve :: Field t => Matrix t -> Matrix t -> Matrix t
242linearSolve = linearSolve' 242linearSolve = {-# SCC "linearSolve" #-} linearSolve'
243 243
244-- | Solve a symmetric or Hermitian positive definite linear system using a precomputed Cholesky decomposition obtained by 'chol'. 244-- | Solve a symmetric or Hermitian positive definite linear system using a precomputed Cholesky decomposition obtained by 'chol'.
245cholSolve :: Field t => Matrix t -> Matrix t -> Matrix t 245cholSolve :: Field t => Matrix t -> Matrix t -> Matrix t
246cholSolve = cholSolve' 246cholSolve = {-# SCC "cholSolve" #-} cholSolve'
247 247
248-- | Minimum norm solution of a general linear least squares problem Ax=B using the SVD. Admits rank-deficient systems but it is slower than 'linearSolveLS'. The effective rank of A is determined by treating as zero those singular valures which are less than 'eps' times the largest singular value. 248-- | Minimum norm solution of a general linear least squares problem Ax=B using the SVD. Admits rank-deficient systems but it is slower than 'linearSolveLS'. The effective rank of A is determined by treating as zero those singular valures which are less than 'eps' times the largest singular value.
249linearSolveSVD :: Field t => Matrix t -> Matrix t -> Matrix t 249linearSolveSVD :: Field t => Matrix t -> Matrix t -> Matrix t
250linearSolveSVD = linearSolveSVD' 250linearSolveSVD = {-# SCC "linearSolveSVD" #-} linearSolveSVD'
251 251
252 252
253-- | Least squared error solution of an overconstrained linear system, or the minimum norm solution of an underconstrained system. For rank-deficient systems use 'linearSolveSVD'. 253-- | Least squared error solution of an overconstrained linear system, or the minimum norm solution of an underconstrained system. For rank-deficient systems use 'linearSolveSVD'.
254linearSolveLS :: Field t => Matrix t -> Matrix t -> Matrix t 254linearSolveLS :: Field t => Matrix t -> Matrix t -> Matrix t
255linearSolveLS = linearSolveLS' 255linearSolveLS = {-# SCC "linearSolveLS" #-} linearSolveLS'
256 256
257-------------------------------------------------------------- 257--------------------------------------------------------------
258 258
259-- | Eigenvalues and eigenvectors of a general square matrix. 259-- | Eigenvalues and eigenvectors of a general square matrix.
260-- 260--
261-- If @(s,v) = eig m@ then @m \<> v == v \<> diag s@ 261-- If @(s,v) = eig m@ then @m \<> v == v \<> diag s@
262eig :: Field t => Matrix t -> (Vector (Complex Double), Matrix (Complex Double)) 262eig :: Field t => Matrix t -> (Vector (Complex Double), Matrix (Complex Double))
263eig = eig' 263eig = {-# SCC "eig" #-} eig'
264 264
265-- | Eigenvalues of a general square matrix. 265-- | Eigenvalues of a general square matrix.
266eigenvalues :: Field t => Matrix t -> Vector (Complex Double) 266eigenvalues :: Field t => Matrix t -> Vector (Complex Double)
267eigenvalues = eigOnly 267eigenvalues = {-# SCC "eigenvalues" #-} eigOnly
268 268
269-- | Similar to 'eigSH' without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part. 269-- | Similar to 'eigSH' without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.
270eigSH' :: Field t => Matrix t -> (Vector Double, Matrix t) 270eigSH' :: Field t => Matrix t -> (Vector Double, Matrix t)
271eigSH' = eigSH'' 271eigSH' = {-# SCC "eigSH'" #-} eigSH''
272 272
273-- | Similar to 'eigenvaluesSH' without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part. 273-- | Similar to 'eigenvaluesSH' without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.
274eigenvaluesSH' :: Field t => Matrix t -> Vector Double 274eigenvaluesSH' :: Field t => Matrix t -> Vector Double
275eigenvaluesSH' = eigOnlySH 275eigenvaluesSH' = {-# SCC "eigenvaluesSH'" #-} eigOnlySH
276 276
277-- | Eigenvalues and Eigenvectors of a complex hermitian or real symmetric matrix. 277-- | Eigenvalues and Eigenvectors of a complex hermitian or real symmetric matrix.
278-- 278--
@@ -291,14 +291,14 @@ eigenvaluesSH m | exactHermitian m = eigenvaluesSH' m
291-- | QR factorization. 291-- | QR factorization.
292-- 292--
293-- If @(q,r) = qr m@ then @m == q \<> r@, where q is unitary and r is upper triangular. 293-- If @(q,r) = qr m@ then @m == q \<> r@, where q is unitary and r is upper triangular.
294qr :: Field t => Matrix t -> (Matrix t, Matrix t) 294qr :: Field t => Matrix t -> (Matrix t, Matrix t)
295qr = qr' 295qr = {-# SCC "qr" #-} qr'
296 296
297-- | RQ factorization. 297-- | RQ factorization.
298-- 298--
299-- If @(r,q) = rq m@ then @m == r \<> q@, where q is unitary and r is upper triangular. 299-- If @(r,q) = rq m@ then @m == r \<> q@, where q is unitary and r is upper triangular.
300rq :: Field t => Matrix t -> (Matrix t, Matrix t) 300rq :: Field t => Matrix t -> (Matrix t, Matrix t)
301rq m = (r,q) where 301rq m = {-# SCC "rq" #-} (r,q) where
302 (q',r') = qr $ trans $ rev1 m 302 (q',r') = qr $ trans $ rev1 m
303 r = rev2 (trans r') 303 r = rev2 (trans r')
304 q = rev2 (trans q') 304 q = rev2 (trans q')
@@ -474,8 +474,6 @@ nullspaceSVD :: Field t
474 -> (Vector Double, Matrix t) -- ^ 'rightSV' of m 474 -> (Vector Double, Matrix t) -- ^ 'rightSV' of m
475 -> [Vector t] -- ^ list of unitary vectors spanning the nullspace 475 -> [Vector t] -- ^ list of unitary vectors spanning the nullspace
476nullspaceSVD hint a (s,v) = vs where 476nullspaceSVD hint a (s,v) = vs where
477 r = rows a
478 c = cols a
479 tol = case hint of 477 tol = case hint of
480 Left t -> t 478 Left t -> t
481 _ -> eps 479 _ -> eps
@@ -546,7 +544,7 @@ zt k v = join [subVector 0 (dim v - k) v, constant 0 k]
546 544
547 545
548unpackQR :: (Field t) => (Matrix t, Vector t) -> (Matrix t, Matrix t) 546unpackQR :: (Field t) => (Matrix t, Vector t) -> (Matrix t, Matrix t)
549unpackQR (pq, tau) = (q,r) 547unpackQR (pq, tau) = {-# SCC "unpackQR" #-} (q,r)
550 where cs = toColumns pq 548 where cs = toColumns pq
551 m = rows pq 549 m = rows pq
552 n = cols pq 550 n = cols pq
diff --git a/lib/Numeric/LinearAlgebra/LAPACK.hs b/lib/Numeric/LinearAlgebra/LAPACK.hs
index 539ffb9..f5af8be 100644
--- a/lib/Numeric/LinearAlgebra/LAPACK.hs
+++ b/lib/Numeric/LinearAlgebra/LAPACK.hs
@@ -237,7 +237,6 @@ eigR m = (s', v'')
237 s' = fixeig1 s 237 s' = fixeig1 s
238 v' = toRows $ trans v 238 v' = toRows $ trans v
239 v'' = fromColumns $ fixeig (toList s') v' 239 v'' = fromColumns $ fixeig (toList s') v'
240 r = rows m
241 240
242eigRaux :: Matrix Double -> (Vector (Complex Double), Matrix Double) 241eigRaux :: Matrix Double -> (Vector (Complex Double), Matrix Double)
243eigRaux m = unsafePerformIO $ do 242eigRaux m = unsafePerformIO $ do
diff --git a/lib/Numeric/LinearAlgebra/Tests/Properties.hs b/lib/Numeric/LinearAlgebra/Tests/Properties.hs
index 618094b..d29e19a 100644
--- a/lib/Numeric/LinearAlgebra/Tests/Properties.hs
+++ b/lib/Numeric/LinearAlgebra/Tests/Properties.hs
@@ -185,7 +185,7 @@ svdProp6b m = s |~| s' && v |~| v' && s |~| s'' && u |~| u'
185svdProp7 m = s |~| s' && u |~| u' && v |~| v' && s |~| s''' 185svdProp7 m = s |~| s' && u |~| u' && v |~| v' && s |~| s'''
186 where (u,s,v) = svd m 186 where (u,s,v) = svd m
187 (s',v') = rightSV m 187 (s',v') = rightSV m
188 (u',s'') = leftSV m 188 (u',_s'') = leftSV m
189 s''' = singularValues m 189 s''' = singularValues m
190 190
191------------------------------------------------------------------ 191------------------------------------------------------------------