{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RebindableSyntax #-}
)
import qualified Data.Vector.Fixed as V (
and,
+ foldl,
fromList,
head,
length,
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