]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Linear/System.hs
Replace the whole Matrix implementation with something a little better.
[numerical-analysis.git] / src / Linear / System.hs
1 {-# LANGUAGE RebindableSyntax #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 {-# LANGUAGE TypeFamilies #-}
4
5 module Linear.System
6 where
7
8 import Data.Vector.Fixed (Arity, N1)
9
10 import Linear.Matrix
11
12 import NumericPrelude hiding ((*), abs)
13 import qualified NumericPrelude as NP ((*))
14 import qualified Algebra.Field as Field
15
16
17 -- | Solve the system m' * x = b', where m' is upper-triangular. Will
18 -- probably crash if m' is non-singular. The result is the vector x.
19 --
20 -- Examples:
21 --
22 -- >>> let identity = fromList [[1,0,0],[0,1,0],[0,0,1]] :: Mat3 Double
23 -- >>> let b = vec3d (1, 2, 3::Double)
24 -- >>> forward_substitute identity b
25 -- ((1.0),(2.0),(3.0))
26 -- >>> (forward_substitute identity b) == b
27 -- True
28 --
29 -- >>> let m = fromList [[1,0],[1,1]] :: Mat2 Double
30 -- >>> let b = vec2d (1, 1::Double)
31 -- >>> forward_substitute m b
32 -- ((1.0),(0.0))
33 --
34 forward_substitute :: forall a m. (Field.C a, Arity m)
35 => Mat m m a
36 -> Mat m N1 a
37 -> Mat m N1 a
38 forward_substitute m' b' = x'
39 where
40 x' = construct lambda
41
42 -- Convenient accessor for the elements of b'.
43 b :: Int -> a
44 b k = b' !!! (k, 0)
45
46 -- Convenient accessor for the elements of m'.
47 m :: Int -> Int -> a
48 m i j = m' !!! (i, j)
49
50 -- Convenient accessor for the elements of x'.
51 x :: Int -> a
52 x k = x' !!! (k, 0)
53
54 -- The second argument to lambda should always be zero here, so we
55 -- ignore it.
56 lambda :: Int -> Int -> a
57 lambda 0 _ = (b 0) / (m 0 0)
58 lambda k _ = ((b k) - sum [ (m k j) NP.* (x j) |
59 j <- [0..k-1] ]) / (m k k)
60
61
62 -- | Solve the system m*x = b, where m is lower-triangular. Will
63 -- probably crash if m is non-singular. The result is the vector x.
64 --
65 -- Examples:
66 --
67 -- >>> let identity = fromList [[1,0,0],[0,1,0],[0,0,1]] :: Mat3 Double
68 -- >>> let b = vec3d (1, 2, 3::Double)
69 -- >>> backward_substitute identity b
70 -- ((1.0),(2.0),(3.0))
71 -- >>> (backward_substitute identity b) == b
72 -- True
73 --
74 backward_substitute :: (Field.C a, Arity m)
75 => Mat m m a
76 -> Mat m N1 a
77 -> Mat m N1 a
78 backward_substitute m b =
79 forward_substitute (transpose m) b
80
81
82 -- | Solve the linear system m*x = b where m is positive definite.
83 {-
84 solve_positive_definite :: Mat v w a -> Mat w z a
85 solve_positive_definite m b = x
86 where
87 r = cholesky m
88 -- First we solve r^T * y == b for y. Then let y=r*x
89 rx = forward_substitute (transpose r) b
90 -- Now solve r*x == b.
91 -}