]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Linear/Matrix.hs
Add the Frobenius norm to Linear.Matrix.
[numerical-analysis.git] / src / Linear / Matrix.hs
index e4743b5f7e6f00a5cdae3b3f2ef28c0abb8c98ee..66b22f9f9d964e843e596678c0f7ebe34e8e9a22 100644 (file)
@@ -2,6 +2,7 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE RebindableSyntax #-}
@@ -25,6 +26,7 @@ import Data.Vector.Fixed (
   N5,
   S,
   Z,
+  generate,
   mk1,
   mk2,
   mk3,
@@ -33,6 +35,7 @@ import Data.Vector.Fixed (
   )
 import qualified Data.Vector.Fixed as V (
   and,
+  foldl,
   fromList,
   head,
   length,
@@ -43,7 +46,7 @@ import qualified Data.Vector.Fixed as V (
   zipWith
   )
 import Data.Vector.Fixed.Boxed (Vec)
-import Data.Vector.Fixed.Internal.Arity (Arity, arity)
+import Data.Vector.Fixed.Cont (Arity, arity)
 import Linear.Vector
 import Normed
 
@@ -198,8 +201,6 @@ symmetric m =
 --   entries in the matrix. The i,j entry of the resulting matrix will
 --   have the value returned by lambda i j.
 --
---   TODO: Don't cheat with fromList.
---
 --   Examples:
 --
 --   >>> let lambda i j = i + j
@@ -208,15 +209,25 @@ symmetric m =
 --
 construct :: forall m n a. (Arity m, Arity n)
           => (Int -> Int -> a) -> Mat m n a
-construct lambda = Mat rows
+construct lambda = Mat $ generate make_row
   where
-    -- The arity trick is used in Data.Vector.Fixed.length.
-    imax = (arity (undefined :: m)) - 1
-    jmax = (arity (undefined :: n)) - 1
-    row' i = V.fromList [ lambda i j | j <- [0..jmax] ]
-    rows = V.fromList [ row' i | i <- [0..imax] ]
+    make_row :: Int -> Vec n a
+    make_row i = generate (lambda i)
 
 
+-- | Create an identity matrix with the right dimensions.
+--
+--   Examples:
+--
+--   >>> identity_matrix :: Mat3 Int
+--   ((1,0,0),(0,1,0),(0,0,1))
+--   >>> identity_matrix :: Mat3 Double
+--   ((1.0,0.0,0.0),(0.0,1.0,0.0),(0.0,0.0,1.0))
+--
+identity_matrix :: (Arity m, Ring.C a) => Mat m m a
+identity_matrix =
+  construct (\i j -> if i == j then (fromInteger 1) else (fromInteger 0))
+
 -- | Given a positive-definite matrix @m@, computes the
 --   upper-triangular matrix @r@ with (transpose r)*r == m and all
 --   values on the diagonal of @r@ positive.
@@ -448,7 +459,31 @@ instance (Algebraic.C a,
     fromRational' $ toRational $ V.maximum $ V.map V.maximum rows
 
 
+-- | Compute the Frobenius norm of a matrix. This essentially treats
+--   the matrix as one long vector containing all of its entries (in
+--   any order, it doesn't matter).
+--
+--   Examples:
+--
+--   >>> let m = fromList [[1, 2, 3],[4,5,6],[7,8,9]] :: Mat3 Double
+--   >>> frobenius_norm m == sqrt 285
+--   True
+--
+--   >>> let m = fromList [[1, -1, 1],[-1,1,-1],[1,-1,1]] :: Mat3 Double
+--   >>> frobenius_norm m == 3
+--   True
+--
+frobenius_norm :: (Algebraic.C a, Ring.C a) => Mat m n a -> a
+frobenius_norm (Mat rows) =
+  sqrt $ vsum $ V.map row_sum rows
+  where
+    -- | The \"sum\" function defined in fixed-vector requires a 'Num'
+    --   constraint whereas we want to use the classes from
+    --   numeric-prelude.
+    vsum = V.foldl (+) (fromInteger 0)
 
+    -- | Square and add up the entries of a row.
+    row_sum = vsum . V.map (^2)
 
 
 -- Vector helpers. We want it to be easy to create low-dimension