summaryrefslogtreecommitdiff
path: root/lib/Numeric/LinearAlgebra/Linear.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2010-08-31 16:52:26 +0000
committerAlberto Ruiz <aruiz@um.es>2010-08-31 16:52:26 +0000
commit4486e93da02c7ef9e1fdf785c88f78986048c332 (patch)
treec0d84fce23a39a307fd12041fdd570be93aca15d /lib/Numeric/LinearAlgebra/Linear.hs
parent0b48e6b34a1a4ec590f2d17833f713f42f5e0955 (diff)
refactoring norms
Diffstat (limited to 'lib/Numeric/LinearAlgebra/Linear.hs')
-rw-r--r--lib/Numeric/LinearAlgebra/Linear.hs63
1 files changed, 52 insertions, 11 deletions
diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs
index 67921d8..6c21a16 100644
--- a/lib/Numeric/LinearAlgebra/Linear.hs
+++ b/lib/Numeric/LinearAlgebra/Linear.hs
@@ -1,5 +1,6 @@
1{-# LANGUAGE UndecidableInstances, MultiParamTypeClasses, FlexibleInstances #-} 1{-# LANGUAGE UndecidableInstances, MultiParamTypeClasses, FlexibleInstances #-}
2{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE TypeFamilies #-}
3----------------------------------------------------------------------------- 4-----------------------------------------------------------------------------
4{- | 5{- |
5Module : Numeric.LinearAlgebra.Linear 6Module : Numeric.LinearAlgebra.Linear
@@ -20,9 +21,11 @@ module Numeric.LinearAlgebra.Linear (
20 Vectors(..), 21 Vectors(..),
21 Linear(..), 22 Linear(..),
22 -- * Products 23 -- * Products
23 Prod(..), 24 Product(..),
24 mXm,mXv,vXm, 25 mXm,mXv,vXm,
25 outer, kronecker, 26 outer, kronecker,
27 -- * Norms
28 Norm(..), Norm2(..),
26 -- * Creation of numeric vectors 29 -- * Creation of numeric vectors
27 constant, linspace 30 constant, linspace
28) where 31) where
@@ -190,38 +193,38 @@ linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1]
190 193
191---------------------------------------------------- 194----------------------------------------------------
192 195
193class Element t => Prod t where 196class Element t => Product t where
194 multiply :: Matrix t -> Matrix t -> Matrix t 197 multiply :: Matrix t -> Matrix t -> Matrix t
195 ctrans :: Matrix t -> Matrix t 198 ctrans :: Matrix t -> Matrix t
196 199
197instance Prod Double where 200instance Product Double where
198 multiply = multiplyR 201 multiply = multiplyR
199 ctrans = trans 202 ctrans = trans
200 203
201instance Prod (Complex Double) where 204instance Product (Complex Double) where
202 multiply = multiplyC 205 multiply = multiplyC
203 ctrans = conj . trans 206 ctrans = conj . trans
204 207
205instance Prod Float where 208instance Product Float where
206 multiply = multiplyF 209 multiply = multiplyF
207 ctrans = trans 210 ctrans = trans
208 211
209instance Prod (Complex Float) where 212instance Product (Complex Float) where
210 multiply = multiplyQ 213 multiply = multiplyQ
211 ctrans = conj . trans 214 ctrans = conj . trans
212 215
213---------------------------------------------------------- 216----------------------------------------------------------
214 217
215-- synonym for matrix product 218-- synonym for matrix product
216mXm :: Prod t => Matrix t -> Matrix t -> Matrix t 219mXm :: Product t => Matrix t -> Matrix t -> Matrix t
217mXm = multiply 220mXm = multiply
218 221
219-- matrix - vector product 222-- matrix - vector product
220mXv :: Prod t => Matrix t -> Vector t -> Vector t 223mXv :: Product t => Matrix t -> Vector t -> Vector t
221mXv m v = flatten $ m `mXm` (asColumn v) 224mXv m v = flatten $ m `mXm` (asColumn v)
222 225
223-- vector - matrix product 226-- vector - matrix product
224vXm :: Prod t => Vector t -> Matrix t -> Vector t 227vXm :: Product t => Vector t -> Matrix t -> Vector t
225vXm v m = flatten $ (asRow v) `mXm` m 228vXm v m = flatten $ (asRow v) `mXm` m
226 229
227{- | Outer product of two vectors. 230{- | Outer product of two vectors.
@@ -232,7 +235,7 @@ vXm v m = flatten $ (asRow v) `mXm` m
232 , 10.0, 4.0, 6.0 235 , 10.0, 4.0, 6.0
233 , 15.0, 6.0, 9.0 ]@ 236 , 15.0, 6.0, 9.0 ]@
234-} 237-}
235outer :: (Prod t) => Vector t -> Vector t -> Matrix t 238outer :: (Product t) => Vector t -> Vector t -> Matrix t
236outer u v = asColumn u `multiply` asRow v 239outer u v = asColumn u `multiply` asRow v
237 240
238{- | Kronecker product of two matrices. 241{- | Kronecker product of two matrices.
@@ -257,9 +260,47 @@ m2=(4><3)
257 , 0.0, 0.0, 0.0, -7.0, -8.0, -9.0, 21.0, 24.0, 27.0 260 , 0.0, 0.0, 0.0, -7.0, -8.0, -9.0, 21.0, 24.0, 27.0
258 , 0.0, 0.0, 0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]@ 261 , 0.0, 0.0, 0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]@
259-} 262-}
260kronecker :: (Prod t) => Matrix t -> Matrix t -> Matrix t 263kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t
261kronecker a b = fromBlocks 264kronecker a b = fromBlocks
262 . splitEvery (cols a) 265 . splitEvery (cols a)
263 . map (reshape (cols b)) 266 . map (reshape (cols b))
264 . toRows 267 . toRows
265 $ flatten a `outer` flatten b 268 $ flatten a `outer` flatten b
269
270--------------------------------------------------
271
272-- | simple norms
273class (Element t, RealFloat (RealOf t)) => Norm c t where
274 norm1 :: c t -> RealOf t
275 normInf :: c t -> RealOf t
276 normFrob :: c t -> RealOf t
277
278instance Norm Vector Double where
279 normFrob = toScalarR Norm2
280 norm1 = toScalarR AbsSum
281 normInf = vectorMax . vectorMapR Abs
282
283instance Norm Vector Float where
284 normFrob = toScalarF Norm2
285 norm1 = toScalarF AbsSum
286 normInf = vectorMax . vectorMapF Abs
287
288instance (Norm Vector t, Vectors Vector t, RealElement t
289 , RealOf t ~ t, RealOf (Complex t) ~ t
290 ) => Norm Vector (Complex t) where
291 normFrob = normFrob . asReal
292 norm1 = norm1 . mapVector magnitude
293 normInf = vectorMax . mapVector magnitude
294
295instance Norm Vector t => Norm Matrix t where
296 normFrob = normFrob . flatten
297 norm1 = maximum . map norm1 . toColumns
298 normInf = norm1 . trans
299
300class Norm2 c t where
301 norm2 :: c t -> RealOf t
302
303instance Norm Vector t => Norm2 Vector t where
304 norm2 = normFrob
305
306-- (the instance Norm2 Matrix t requires singular values and is defined later)