]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/FixedMatrix.hs
1c904f26b7e14516bbadd1a1216bab19cb1dd761
[numerical-analysis.git] / src / FixedMatrix.hs
1 {-# LANGUAGE ScopedTypeVariables #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE TypeFamilies #-}
6
7 module FixedMatrix
8 where
9
10 import FixedVector as FV
11 import qualified Data.Vector.Fixed as V
12 import Data.Vector.Fixed.Internal (arity)
13
14 type Mat v w a = Vn v (Vn w a)
15 type Mat2 a = Mat Vec2D Vec2D a
16 type Mat3 a = Mat Vec3D Vec3D a
17 type Mat4 a = Mat Vec4D Vec4D a
18
19 -- | Convert a matrix to a nested list.
20 toList :: (V.Vector v (Vn w a), V.Vector w a) => Mat v w a -> [[a]]
21 toList m = Prelude.map FV.toList (FV.toList m)
22
23 -- | Create a matrix from a nested list.
24 fromList :: (V.Vector v (Vn w a), V.Vector w a) => [[a]] -> Mat v w a
25 fromList vs = FV.fromList $ Prelude.map FV.fromList vs
26
27
28 -- | Unsafe indexing.
29 (!) :: (V.Vector v (Vn w a), V.Vector w a) => Mat v w a -> (Int, Int) -> a
30 (!) m (i, j) = (row m i) FV.! j
31
32 -- | Safe indexing.
33 (!?) :: (V.Vector v (Vn w a), V.Vector w a) => Mat v w a
34 -> (Int, Int)
35 -> Maybe a
36 (!?) m (i, j)
37 | i < 0 || j < 0 = Nothing
38 | i > FV.length m = Nothing
39 | otherwise = if j > FV.length (row m j)
40 then Nothing
41 else Just $ (row m j) FV.! j
42
43
44 -- | The number of rows in the matrix. Implementation stolen from
45 -- Data.Vector.Fixed.Length.
46 nrows :: forall v w a. (V.Vector v (Vn w a), V.Vector w a) => Mat v w a -> Int
47 nrows _ = arity (undefined :: V.Dim v)
48
49 -- | The number of columns in the first row of the
50 -- matrix. Implementation stolen from
51 ncols :: forall v w a. (V.Vector v (Vn w a), V.Vector w a) => Mat v w a -> Int
52 ncols _ = arity (undefined :: V.Dim w)
53
54 -- | Return the @i@th row of @m@. Unsafe.
55 row :: (V.Vector v (Vn w a), V.Vector w a) => Mat v w a
56 -> Int
57 -> Vn w a
58 row m i = m FV.! i
59
60
61 -- | Return the @j@th column of @m@. Unsafe.
62 column :: (V.Vector v a, V.Vector v (Vn w a), V.Vector w a) => Mat v w a
63 -> Int
64 -> Vn v a
65 column m j =
66 FV.map (element j) m
67 where
68 element = flip (FV.!)
69
70
71 -- | Transose @m@; switch it's columns and its rows. This is a dirty
72 -- implementation.. it would be a little cleaner to use imap, but it
73 -- doesn't seem to work.
74 transpose :: (V.Vector v (Vn w a),
75 V.Vector w (Vn v a),
76 V.Vector v a,
77 V.Vector w a)
78 => Mat v w a
79 -> Mat w v a
80 transpose m = FV.fromList column_list
81 where
82 column_list = [ column m i | i <- [0..(ncols m)-1] ]
83
84 -- | Is @m@ symmetric?
85 symmetric :: (V.Vector v (Vn w a),
86 V.Vector w a,
87 v ~ w,
88 V.Vector w Bool,
89 Eq a)
90 => Mat v w a
91 -> Bool
92 symmetric m =
93 m == (transpose m)
94
95
96 -- | Construct a new matrix from a function @lambda@. The function
97 -- @lambda@ should take two parameters i,j corresponding to the
98 -- entries in the matrix. The i,j entry of the resulting matrix will
99 -- have the value returned by lambda i j.
100 construct :: forall v w a.
101 (V.Vector v (Vn w a),
102 V.Vector w a)
103 => (Int -> Int -> a)
104 -> Mat v w a
105 construct lambda = rows
106 where
107 -- The arity trick is used in Data.Vector.Fixed.length.
108 imax = (arity (undefined :: V.Dim w)) - 1
109 jmax = (arity (undefined :: V.Dim w)) - 1
110 row' i = FV.fromList [ lambda i j | j <- [0..jmax] ]
111 rows = FV.fromList [ row' i | i <- [0..imax] ]