summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--packages/base/CHANGELOG26
-rw-r--r--packages/base/hmatrix.cabal4
-rw-r--r--packages/base/src/Internal/Algorithms.hs89
-rw-r--r--packages/base/src/Internal/Modular.hs2
-rw-r--r--packages/base/src/Internal/Util.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra.hs21
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static.hs2
-rw-r--r--packages/tests/src/Numeric/LinearAlgebra/Tests.hs6
-rw-r--r--packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs13
-rw-r--r--packages/tests/src/Numeric/LinearAlgebra/Tests/Properties.hs2
10 files changed, 95 insertions, 72 deletions
diff --git a/packages/base/CHANGELOG b/packages/base/CHANGELOG
index 0336a28..581d2ac 100644
--- a/packages/base/CHANGELOG
+++ b/packages/base/CHANGELOG
@@ -1,24 +1,32 @@
10.17.0.0 10.17.0.0
2-------- 2--------
3 3
4 * improved matrix extraction (??) and rectangular matrix slices without data copy 4 * eigSH, chol, and other functions that work with Hermitian or symmetric matrices
5 now take a special "Herm" argument that can be created by means of "sym"
6 or "mTm". The unchecked versions of those functions have been removed and we
7 use "trustSym" to create the Herm type when the matrix is known to be Hermitian/symmetric.
8
9 * Improved matrix extraction (??) and rectangular matrix slices without data copy
10
11 * Basic support of Int32 and Int64 elements
5 12
6 * basic support of Int32 and Int64 elements
7
8 * remap, more general cond, sortIndex 13 * remap, more general cond, sortIndex
9 14
10 * experimental support of type safe modular arithmetic, including linear 15 * Experimental support of type safe modular arithmetic, including linear
11 systems and lu factorization 16 system solver and LU factorization
12 17
13 * elementary row operations and inplace matrix slice products in the ST monad 18 * Elementary row operations and inplace matrix slice products in the ST monad
14 19
15 * Improved development tools. 20 * Improved development tools.
16 21
17 * old compatibility modules removed, simpler organization of internal modules 22 * Old compatibility modules removed, simpler organization of internal modules
18 23
19 * unitary, pairwiseD2, tr' 24 * unitary, pairwiseD2, tr'
20 25
21 * ldlPacked, ldlSolve 26 * ldlPacked, ldlSolve for indefinite symmetric systems (apparently not faster
27 than the general solver based on the LU)
28
29 * LU, LDL, and QR types for these compact decompositions.
22 30
230.16.1.0 310.16.1.0
24-------- 32--------
diff --git a/packages/base/hmatrix.cabal b/packages/base/hmatrix.cabal
index 93ca3d7..e248886 100644
--- a/packages/base/hmatrix.cabal
+++ b/packages/base/hmatrix.cabal
@@ -9,9 +9,9 @@ Homepage: https://github.com/albertoruiz/hmatrix
9Synopsis: Numeric Linear Algebra 9Synopsis: Numeric Linear Algebra
10Description: Linear systems, matrix decompositions, and other numerical computations based on BLAS and LAPACK. 10Description: Linear systems, matrix decompositions, and other numerical computations based on BLAS and LAPACK.
11 . 11 .
12 The standard interface is provided by the module "Numeric.LinearAlgebra". 12 Standard interface: "Numeric.LinearAlgebra".
13 . 13 .
14 A safer interface with statically checked dimensions is provided by "Numeric.LinearAlgebra.Static". 14 Safer interface with statically checked dimensions: "Numeric.LinearAlgebra.Static".
15 . 15 .
16 Code examples: <http://dis.um.es/~alberto/hmatrix/hmatrix.html> 16 Code examples: <http://dis.um.es/~alberto/hmatrix/hmatrix.html>
17 17
diff --git a/packages/base/src/Internal/Algorithms.hs b/packages/base/src/Internal/Algorithms.hs
index d2f17f4..c4f1a60 100644
--- a/packages/base/src/Internal/Algorithms.hs
+++ b/packages/base/src/Internal/Algorithms.hs
@@ -4,12 +4,6 @@
4{-# LANGUAGE UndecidableInstances #-} 4{-# LANGUAGE UndecidableInstances #-}
5{-# LANGUAGE TypeFamilies #-} 5{-# LANGUAGE TypeFamilies #-}
6 6
7{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
8{-# LANGUAGE CPP #-}
9{-# LANGUAGE MultiParamTypeClasses #-}
10{-# LANGUAGE UndecidableInstances #-}
11{-# LANGUAGE TypeFamilies #-}
12
13----------------------------------------------------------------------------- 7-----------------------------------------------------------------------------
14{- | 8{- |
15Module : Internal.Algorithms 9Module : Internal.Algorithms
@@ -376,8 +370,8 @@ ldlPackedSH x = {-# SCC "ldlPacked" #-} LDL m p
376 (m,p) = ldlPacked' x 370 (m,p) = ldlPacked' x
377 371
378-- | Obtains the LDL decomposition of a matrix in a compact data structure suitable for 'ldlSolve'. 372-- | Obtains the LDL decomposition of a matrix in a compact data structure suitable for 'ldlSolve'.
379ldlPacked :: Field t => Her t -> LDL t 373ldlPacked :: Field t => Herm t -> LDL t
380ldlPacked (Her m) = ldlPackedSH m 374ldlPacked (Herm m) = ldlPackedSH m
381 375
382-- | Solution of a linear system (for several right hand sides) from a precomputed LDL factorization obtained by 'ldlPacked'. 376-- | Solution of a linear system (for several right hand sides) from a precomputed LDL factorization obtained by 'ldlPacked'.
383-- 377--
@@ -461,26 +455,39 @@ fromList [11.344814282762075,0.17091518882717918,-0.5157294715892575]
4613.000 5.000 6.000 4553.000 5.000 6.000
462 456
463-} 457-}
464eigSH :: Field t => Her t -> (Vector Double, Matrix t) 458eigSH :: Field t => Herm t -> (Vector Double, Matrix t)
465eigSH (Her m) = eigSH' m 459eigSH (Herm m) = eigSH' m
466 460
467-- | Eigenvalues (in descending order) of a complex hermitian or real symmetric matrix. 461-- | Eigenvalues (in descending order) of a complex hermitian or real symmetric matrix.
468eigenvaluesSH :: Field t => Her t -> Vector Double 462eigenvaluesSH :: Field t => Herm t -> Vector Double
469eigenvaluesSH (Her m) = eigenvaluesSH' m 463eigenvaluesSH (Herm m) = eigenvaluesSH' m
470 464
471-------------------------------------------------------------- 465--------------------------------------------------------------
472 466
467-- | QR decomposition of a matrix in compact form. (The orthogonal matrix is not explicitly formed.)
468data QR t = QR (Matrix t) (Vector t)
469
470instance (NFData t, Numeric t) => NFData (QR t)
471 where
472 rnf (QR m _) = rnf m
473
474
473-- | QR factorization. 475-- | QR factorization.
474-- 476--
475-- If @(q,r) = qr m@ then @m == q \<> r@, where q is unitary and r is upper triangular. 477-- If @(q,r) = qr m@ then @m == q \<> r@, where q is unitary and r is upper triangular.
476qr :: Field t => Matrix t -> (Matrix t, Matrix t) 478qr :: Field t => Matrix t -> (Matrix t, Matrix t)
477qr = {-# SCC "qr" #-} unpackQR . qr' 479qr = {-# SCC "qr" #-} unpackQR . qr'
478 480
479qrRaw m = qr' m 481-- | Compute the QR decomposition of a matrix in compact form.
482qrRaw :: Field t => Matrix t -> QR t
483qrRaw m = QR x v
484 where
485 (x,v) = qr' m
480 486
481{- | generate a matrix with k orthogonal columns from the output of qrRaw 487-- | generate a matrix with k orthogonal columns from the compact QR decomposition obtained by 'qrRaw'.
482-} 488--
483qrgr n (a,t) 489qrgr :: Field t => Int -> QR t -> Matrix t
490qrgr n (QR a t)
484 | dim t > min (cols a) (rows a) || n < 0 || n > dim t = error "qrgr expects k <= min(rows,cols)" 491 | dim t > min (cols a) (rows a) || n < 0 || n > dim t = error "qrgr expects k <= min(rows,cols)"
485 | otherwise = qrgr' n (a,t) 492 | otherwise = qrgr' n (a,t)
486 493
@@ -525,12 +532,12 @@ cholSH = cholSH'
525-- | Cholesky factorization of a positive definite hermitian or symmetric matrix. 532-- | Cholesky factorization of a positive definite hermitian or symmetric matrix.
526-- 533--
527-- If @c = chol m@ then @c@ is upper triangular and @m == tr c \<> c@. 534-- If @c = chol m@ then @c@ is upper triangular and @m == tr c \<> c@.
528chol :: Field t => Her t -> Matrix t 535chol :: Field t => Herm t -> Matrix t
529chol (Her m) = {-# SCC "chol" #-} cholSH' m 536chol (Herm m) = {-# SCC "chol" #-} cholSH' m
530 537
531-- | Similar to 'chol', but instead of an error (e.g., caused by a matrix not positive definite) it returns 'Nothing'. 538-- | Similar to 'chol', but instead of an error (e.g., caused by a matrix not positive definite) it returns 'Nothing'.
532mbChol :: Field t => Her t -> Maybe (Matrix t) 539mbChol :: Field t => Herm t -> Maybe (Matrix t)
533mbChol (Her m) = {-# SCC "mbChol" #-} mbCholSH' m 540mbChol (Herm m) = {-# SCC "mbChol" #-} mbCholSH' m
534 541
535 542
536 543
@@ -870,6 +877,8 @@ fixPerm' s = res $ mutable f s0
870triang r c h v = (r><c) [el s t | s<-[0..r-1], t<-[0..c-1]] 877triang r c h v = (r><c) [el s t | s<-[0..r-1], t<-[0..c-1]]
871 where el p q = if q-p>=h then v else 1 - v 878 where el p q = if q-p>=h then v else 1 - v
872 879
880-- | Compute the explicit LU decomposition from the compact one obtained by 'luPacked'.
881luFact :: Numeric t => LU t -> (Matrix t, Matrix t, Matrix t, t)
873luFact (LU l_u perm) 882luFact (LU l_u perm)
874 | r <= c = (l ,u ,p, s) 883 | r <= c = (l ,u ,p, s)
875 | otherwise = (l',u',p, s) 884 | otherwise = (l',u',p, s)
@@ -967,10 +976,10 @@ relativeError norm a b = r
967-- | Generalized symmetric positive definite eigensystem Av = lBv, 976-- | Generalized symmetric positive definite eigensystem Av = lBv,
968-- for A and B symmetric, B positive definite. 977-- for A and B symmetric, B positive definite.
969geigSH :: Field t 978geigSH :: Field t
970 => Her t -- ^ A 979 => Herm t -- ^ A
971 -> Her t -- ^ B 980 -> Herm t -- ^ B
972 -> (Vector Double, Matrix t) 981 -> (Vector Double, Matrix t)
973geigSH (Her a) (Her b) = geigSH' a b 982geigSH (Herm a) (Herm b) = geigSH' a b
974 983
975geigSH' :: Field t 984geigSH' :: Field t
976 => Matrix t -- ^ A 985 => Matrix t -- ^ A
@@ -989,29 +998,33 @@ geigSH' a b = (l,v')
989 998
990-- | A matrix that, by construction, it is known to be complex Hermitian or real symmetric. 999-- | A matrix that, by construction, it is known to be complex Hermitian or real symmetric.
991-- 1000--
992-- It can be created using 'sym', 'xTx', or 'trustSym', and the matrix can be extracted using 'her'. 1001-- It can be created using 'sym', 'mTm', or 'trustSym', and the matrix can be extracted using 'unSym'.
993data Her t = Her (Matrix t) deriving Show 1002newtype Herm t = Herm (Matrix t) deriving Show
1003
1004instance (NFData t, Numeric t) => NFData (Herm t)
1005 where
1006 rnf (Herm m) = rnf m
994 1007
995-- | Extract the general matrix from a 'Her' structure, forgetting its symmetric or Hermitian property. 1008-- | Extract the general matrix from a 'Herm' structure, forgetting its symmetric or Hermitian property.
996her :: Her t -> Matrix t 1009unSym :: Herm t -> Matrix t
997her (Her x) = x 1010unSym (Herm x) = x
998 1011
999-- | Compute the complex Hermitian or real symmetric part of a square matrix (@(x + tr x)/2@). 1012-- | Compute the complex Hermitian or real symmetric part of a square matrix (@(x + tr x)/2@).
1000sym :: Field t => Matrix t -> Her t 1013sym :: Field t => Matrix t -> Herm t
1001sym x = Her (scale 0.5 (tr x `add` x)) 1014sym x = Herm (scale 0.5 (tr x `add` x))
1002 1015
1003-- | Compute the contraction @tr x <> x@ of a general matrix. 1016-- | Compute the contraction @tr x <> x@ of a general matrix.
1004xTx :: Numeric t => Matrix t -> Her t 1017mTm :: Numeric t => Matrix t -> Herm t
1005xTx x = Her (tr x `mXm` x) 1018mTm x = Herm (tr x `mXm` x)
1006 1019
1007instance Field t => Linear t Her where 1020instance Field t => Linear t Herm where
1008 scale x (Her m) = Her (scale x m) 1021 scale x (Herm m) = Herm (scale x m)
1009 1022
1010instance Field t => Additive (Her t) where 1023instance Field t => Additive (Herm t) where
1011 add (Her a) (Her b) = Her (a `add` b) 1024 add (Herm a) (Herm b) = Herm (a `add` b)
1012 1025
1013-- | At your own risk, declare that a matrix is complex Hermitian or real symmetric 1026-- | At your own risk, declare that a matrix is complex Hermitian or real symmetric
1014-- for usage in 'chol', 'eigSH', etc. Only a triangular part of the matrix will be used. 1027-- for usage in 'chol', 'eigSH', etc. Only a triangular part of the matrix will be used.
1015trustSym :: Matrix t -> Her t 1028trustSym :: Matrix t -> Herm t
1016trustSym x = (Her x) 1029trustSym x = (Herm x)
1017 1030
diff --git a/packages/base/src/Internal/Modular.hs b/packages/base/src/Internal/Modular.hs
index a3421a8..239c742 100644
--- a/packages/base/src/Internal/Modular.hs
+++ b/packages/base/src/Internal/Modular.hs
@@ -371,7 +371,7 @@ test = (ok, info)
371 371
372 checkLU okf t = norm_Inf $ flatten (l <> u <> p - t) 372 checkLU okf t = norm_Inf $ flatten (l <> u <> p - t)
373 where 373 where
374 (l,u,p,_ :: Int) = luFact (LU x' p') 374 (l,u,p,_) = luFact (LU x' p')
375 where 375 where
376 (x',p') = mutable (luST okf) t 376 (x',p') = mutable (luST okf) t
377 377
diff --git a/packages/base/src/Internal/Util.hs b/packages/base/src/Internal/Util.hs
index 36b7855..cf42961 100644
--- a/packages/base/src/Internal/Util.hs
+++ b/packages/base/src/Internal/Util.hs
@@ -462,7 +462,7 @@ null1 :: Matrix R -> Vector R
462null1 = last . toColumns . snd . rightSV 462null1 = last . toColumns . snd . rightSV
463 463
464-- | solution of overconstrained homogeneous symmetric linear system 464-- | solution of overconstrained homogeneous symmetric linear system
465null1sym :: Her R -> Vector R 465null1sym :: Herm R -> Vector R
466null1sym = last . toColumns . snd . eigSH 466null1sym = last . toColumns . snd . eigSH
467 467
468-------------------------------------------------------------------------------- 468--------------------------------------------------------------------------------
diff --git a/packages/base/src/Numeric/LinearAlgebra.hs b/packages/base/src/Numeric/LinearAlgebra.hs
index 7be2600..6a9c33a 100644
--- a/packages/base/src/Numeric/LinearAlgebra.hs
+++ b/packages/base/src/Numeric/LinearAlgebra.hs
@@ -35,8 +35,9 @@ module Numeric.LinearAlgebra (
35 35
36 -- * Autoconformable dimensions 36 -- * Autoconformable dimensions
37 -- | 37 -- |
38 -- In arithmetic operations single-element vectors and matrices 38 -- In most operations, single-element vectors and matrices
39 -- (created from numeric literals or using 'scalar') automatically 39 -- (created from numeric literals or using 'scalar'), and matrices
40 -- with just one row or column, automatically
40 -- expand to match the dimensions of the other operand: 41 -- expand to match the dimensions of the other operand:
41 -- 42 --
42 -- >>> 5 + 2*ident 3 :: Matrix Double 43 -- >>> 5 + 2*ident 3 :: Matrix Double
@@ -45,11 +46,12 @@ module Numeric.LinearAlgebra (
45 -- , 5.0, 7.0, 5.0 46 -- , 5.0, 7.0, 5.0
46 -- , 5.0, 5.0, 7.0 ] 47 -- , 5.0, 5.0, 7.0 ]
47 -- 48 --
48 -- >>> matrix 3 [1..9] + matrix 1 [10,20,30] 49 -- >>> (4><3) [1..] + row [10,20,30]
49 -- (3><3) 50 -- (4><3)
50 -- [ 11.0, 12.0, 13.0 51 -- [ 11.0, 22.0, 33.0
51 -- , 24.0, 25.0, 26.0 52 -- , 14.0, 25.0, 36.0
52 -- , 37.0, 38.0, 39.0 ] 53 -- , 17.0, 28.0, 39.0
54 -- , 20.0, 31.0, 42.0 ]
53 -- 55 --
54 56
55 -- * Products 57 -- * Products
@@ -152,9 +154,9 @@ module Numeric.LinearAlgebra (
152 -- * Misc 154 -- * Misc
153 meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, magnit, 155 meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, magnit,
154 haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, 156 haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv,
155 iC, sym, xTx, trustSym, her, 157 iC, sym, mTm, trustSym, unSym,
156 -- * Auxiliary classes 158 -- * Auxiliary classes
157 Element, Container, Product, Numeric, LSDiv, Her, 159 Element, Container, Product, Numeric, LSDiv, Herm,
158 Complexable, RealElement, 160 Complexable, RealElement,
159 RealOf, ComplexOf, SingleOf, DoubleOf, 161 RealOf, ComplexOf, SingleOf, DoubleOf,
160 IndexOf, 162 IndexOf,
@@ -162,6 +164,7 @@ module Numeric.LinearAlgebra (
162 Transposable, 164 Transposable,
163 LU(..), 165 LU(..),
164 LDL(..), 166 LDL(..),
167 QR(..),
165 CGState(..), 168 CGState(..),
166 Testable(..) 169 Testable(..)
167) where 170) where
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs
index ded69fa..843c727 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Static.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs
@@ -65,7 +65,7 @@ import Numeric.LinearAlgebra hiding (
65 row,col,vector,matrix,linspace,toRows,toColumns, 65 row,col,vector,matrix,linspace,toRows,toColumns,
66 (<\>),fromList,takeDiag,svd,eig,eigSH, 66 (<\>),fromList,takeDiag,svd,eig,eigSH,
67 eigenvalues,eigenvaluesSH,build, 67 eigenvalues,eigenvaluesSH,build,
68 qr,size,dot,chol,range,R,C,Her,her,sym) 68 qr,size,dot,chol,range,R,C,sym,mTm,unSym)
69import qualified Numeric.LinearAlgebra as LA 69import qualified Numeric.LinearAlgebra as LA
70import Data.Proxy(Proxy) 70import Data.Proxy(Proxy)
71import Internal.Static 71import Internal.Static
diff --git a/packages/tests/src/Numeric/LinearAlgebra/Tests.hs b/packages/tests/src/Numeric/LinearAlgebra/Tests.hs
index 30480d7..ecda6c1 100644
--- a/packages/tests/src/Numeric/LinearAlgebra/Tests.hs
+++ b/packages/tests/src/Numeric/LinearAlgebra/Tests.hs
@@ -500,10 +500,10 @@ sliceTest = utest "slice test" $ and
500 , testSlice (test_qrgr 4 tau2) qrr2 500 , testSlice (test_qrgr 4 tau2) qrr2
501 ] 501 ]
502 where 502 where
503 (qrr1,tau1) = qrRaw (rec :: Matrix R) 503 QR qrr1 tau1 = qrRaw (rec :: Matrix R)
504 (qrr2,tau2) = qrRaw (rec :: Matrix C) 504 QR qrr2 tau2 = qrRaw (rec :: Matrix C)
505 505
506 test_qrgr n t x = qrgr n (x,t) 506 test_qrgr n t x = qrgr n (QR x t)
507 507
508 ok_qrgr x = simeq 1E-15 q q' 508 ok_qrgr x = simeq 1E-15 q q'
509 where 509 where
diff --git a/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs b/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
index 4704989..3d5441d 100644
--- a/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
+++ b/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
@@ -81,8 +81,7 @@ instance (Field a, Arbitrary a) => Arbitrary (Rot a) where
81 81
82 82
83-- a complex hermitian or real symmetric matrix 83-- a complex hermitian or real symmetric matrix
84--newtype (Her a) = Her (Matrix a) deriving Show 84instance (Field a, Arbitrary a, Num (Vector a)) => Arbitrary (Herm a) where
85instance (Field a, Arbitrary a, Num (Vector a)) => Arbitrary (Her a) where
86 arbitrary = do 85 arbitrary = do
87 Sq m <- arbitrary 86 Sq m <- arbitrary
88 let m' = m/2 87 let m' = m/2
@@ -127,7 +126,7 @@ instance (Numeric a, ArbitraryField a, Num (Vector a))
127 arbitrary = do 126 arbitrary = do
128 m <- arbitrary 127 m <- arbitrary
129 let (_,v) = eigSH m 128 let (_,v) = eigSH m
130 n = rows (her m) 129 n = rows (unSym m)
131 l <- replicateM n (choose (0,100)) 130 l <- replicateM n (choose (0,100))
132 let s = diag (fromList l) 131 let s = diag (fromList l)
133 p = v <> real s <> tr v 132 p = v <> real s <> tr v
@@ -161,8 +160,8 @@ fM m = m :: FM
161zM m = m :: ZM 160zM m = m :: ZM
162 161
163 162
164rHer m = her m :: RM 163rHer m = unSym m :: RM
165cHer m = her m :: CM 164cHer m = unSym m :: CM
166 165
167rRot (Rot m) = m :: RM 166rRot (Rot m) = m :: RM
168cRot (Rot m) = m :: CM 167cRot (Rot m) = m :: CM
@@ -176,8 +175,8 @@ cWC (WC m) = m :: CM
176rSqWC (SqWC m) = m :: RM 175rSqWC (SqWC m) = m :: RM
177cSqWC (SqWC m) = m :: CM 176cSqWC (SqWC m) = m :: CM
178 177
179rSymWC (SqWC m) = sym m :: Her R 178rSymWC (SqWC m) = sym m :: Herm R
180cSymWC (SqWC m) = sym m :: Her C 179cSymWC (SqWC m) = sym m :: Herm C
181 180
182rPosDef (PosDef m) = m :: RM 181rPosDef (PosDef m) = m :: RM
183cPosDef (PosDef m) = m :: CM 182cPosDef (PosDef m) = m :: CM
diff --git a/packages/tests/src/Numeric/LinearAlgebra/Tests/Properties.hs b/packages/tests/src/Numeric/LinearAlgebra/Tests/Properties.hs
index 2ac3588..720b7bd 100644
--- a/packages/tests/src/Numeric/LinearAlgebra/Tests/Properties.hs
+++ b/packages/tests/src/Numeric/LinearAlgebra/Tests/Properties.hs
@@ -263,7 +263,7 @@ multProp2 p (a,b) = (tr (a <> b)) :~p~: (tr b <> tr a)
263 263
264linearSolveProp f m = f m m |~| ident (rows m) 264linearSolveProp f m = f m m |~| ident (rows m)
265 265
266linearSolvePropH f m = f m (her m) |~| ident (rows (her m)) 266linearSolvePropH f m = f m (unSym m) |~| ident (rows (unSym m))
267 267
268linearSolveProp2 f (a,x) = not wc `trivial` (not wc || a <> f a b |~| b) 268linearSolveProp2 f (a,x) = not wc `trivial` (not wc || a <> f a b |~| b)
269 where q = min (rows a) (cols a) 269 where q = min (rows a) (cols a)