summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/LinearAlgebra/Static.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-04-10 09:53:23 +0200
committerAlberto Ruiz <aruiz@um.es>2015-04-10 09:53:23 +0200
commite499467d2c67f214b0871376b068c5b6fc7896a1 (patch)
tree166021773cbb2c066811ee27830dd5618114ab10 /packages/base/src/Numeric/LinearAlgebra/Static.hs
parentdcc03a4a764cb8683b80758af97fcbcc9aadba73 (diff)
merge recent
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra/Static.hs')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static.hs30
1 files changed, 6 insertions, 24 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs
index a26cc4c..4c3186f 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Static.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs
@@ -1,5 +1,3 @@
1#if __GLASGOW_HASKELL__ >= 708
2
3{-# LANGUAGE DataKinds #-} 1{-# LANGUAGE DataKinds #-}
4{-# LANGUAGE KindSignatures #-} 2{-# LANGUAGE KindSignatures #-}
5{-# LANGUAGE GeneralizedNewtypeDeriving #-} 3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
@@ -51,7 +49,7 @@ module Numeric.LinearAlgebra.Static(
51 linSolve, (<\>), 49 linSolve, (<\>),
52 -- * Factorizations 50 -- * Factorizations
53 svd, withCompactSVD, svdTall, svdFlat, Eigen(..), 51 svd, withCompactSVD, svdTall, svdFlat, Eigen(..),
54 withNullspace, qr, 52 withNullspace, qr, chol,
55 -- * Misc 53 -- * Misc
56 mean, 54 mean,
57 Disp(..), Domain(..), 55 Disp(..), Domain(..),
@@ -67,7 +65,7 @@ import Numeric.LinearAlgebra.HMatrix hiding (
67 row,col,vector,matrix,linspace,toRows,toColumns, 65 row,col,vector,matrix,linspace,toRows,toColumns,
68 (<\>),fromList,takeDiag,svd,eig,eigSH,eigSH', 66 (<\>),fromList,takeDiag,svd,eig,eigSH,eigSH',
69 eigenvalues,eigenvaluesSH,eigenvaluesSH',build, 67 eigenvalues,eigenvaluesSH,eigenvaluesSH',build,
70 qr,size,app,mul,dot) 68 qr,size,app,mul,dot,chol)
71import qualified Numeric.LinearAlgebra.HMatrix as LA 69import qualified Numeric.LinearAlgebra.HMatrix as LA
72import Data.Proxy(Proxy) 70import Data.Proxy(Proxy)
73import Numeric.LinearAlgebra.Static.Internal 71import Numeric.LinearAlgebra.Static.Internal
@@ -183,6 +181,7 @@ a ¦ b = tr (tr a —— tr b)
183type Sq n = L n n 181type Sq n = L n n
184--type CSq n = CL n n 182--type CSq n = CL n n
185 183
184
186type GL = forall n m . (KnownNat n, KnownNat m) => L m n 185type GL = forall n m . (KnownNat n, KnownNat m) => L m n
187type GSq = forall n . KnownNat n => Sq n 186type GSq = forall n . KnownNat n => Sq n
188 187
@@ -305,6 +304,9 @@ instance KnownNat n => Eigen (Sq n) (C n) (M n n)
305 where 304 where
306 (l,v) = LA.eig m 305 (l,v) = LA.eig m
307 306
307chol :: KnownNat n => Sym n -> Sq n
308chol (extract . unSym -> m) = mkL $ LA.cholSH m
309
308-------------------------------------------------------------------------------- 310--------------------------------------------------------------------------------
309 311
310withNullspace 312withNullspace
@@ -614,23 +616,3 @@ instance (KnownNat n', KnownNat m') => Testable (L n' m')
614 where 616 where
615 checkT _ = test 617 checkT _ = test
616 618
617#else
618
619{- |
620Module : Numeric.LinearAlgebra.Static
621Copyright : (c) Alberto Ruiz 2014
622License : BSD3
623Stability : experimental
624
625Experimental interface with statically checked dimensions.
626
627This module requires GHC >= 7.8
628
629-}
630
631module Numeric.LinearAlgebra.Static
632{-# WARNING "This module requires GHC >= 7.8" #-}
633where
634
635#endif
636