X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FLinear%2FMatrix.hs;h=69a74b50eeacf7ea944c790d3858dd0cba12c266;hb=d8dc884aa9b16c7bbd88c4c107ddd684a339a191;hp=c48f722265b19e3bd195ce5dc16e3ab44162d137;hpb=504257320e56784b914ff69e8efb22d6191e3372;p=numerical-analysis.git diff --git a/src/Linear/Matrix.hs b/src/Linear/Matrix.hs index c48f722..69a74b5 100644 --- a/src/Linear/Matrix.hs +++ b/src/Linear/Matrix.hs @@ -2,6 +2,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RebindableSyntax #-} @@ -43,7 +44,6 @@ import qualified Data.Vector.Fixed as V ( toList, zipWith ) -import Data.Vector.Fixed.Boxed (Vec) import Data.Vector.Fixed.Cont (Arity, arity) import Linear.Vector import Normed @@ -213,6 +213,18 @@ construct lambda = Mat $ generate make_row 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 @@ -416,8 +428,8 @@ instance (Algebraic.C a, ToRational.C a, Arity m) => Normed (Mat (S m) N1 a) where - -- | Generic p-norms. The usual norm in R^n is (norm_p 2). We treat - -- all matrices as big vectors. + -- | Generic p-norms for vectors in R^n that are represented as nx1 + -- matrices. -- -- Examples: -- @@ -445,7 +457,26 @@ 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 $ element_sum $ V.map row_sum rows + where + -- | Square and add up the entries of a row. + row_sum = element_sum . V.map (^2) -- Vector helpers. We want it to be easy to create low-dimension