Wrote firstMinorMatrix
[rootstock.git] / IndexedMatrix.hs
blobc6b7a604ff784973b223543a08512592575dcabc
1 module IndexedMatrix where
2 import Data.Set (Set)
3 import qualified Data.Set as Set
4 import Numeric.Matrix (Matrix, MatrixElement)
5 import qualified Numeric.Matrix as Matrix
7 data IndexedMatrix r c e = IndexedMatrix
8 { rowIndices :: Set r
9 , columnIndices :: Set c
10 , stripIndices :: Matrix e
11 } deriving Show
13 indexedMatrix :: MatrixElement e =>
14 Set r -> Set c -> (r -> c -> e) -> IndexedMatrix r c e
15 indexedMatrix rs cs f = IndexedMatrix
16 { rowIndices = rs
17 , columnIndices = cs
18 , stripIndices = Matrix.matrix (Set.size rs, Set.size cs) $ \(i, j) ->
19 f (Set.elemAt (i - 1) rs) $ Set.elemAt (j - 1) cs
22 firstMinorMatrix :: (Ord r, Ord c, MatrixElement e) =>
23 IndexedMatrix r c e -> r -> c -> Maybe (IndexedMatrix r c e)
24 firstMinorMatrix m r c =
25 let
26 rs = rowIndices m
27 cs = columnIndices m
29 if (Set.member r rs && Set.member c cs)
30 then Just $ IndexedMatrix
31 { rowIndices = Set.delete r rs
32 , columnIndices = Set.delete c cs
33 , stripIndices = Matrix.minorMatrix (stripIndices m)
34 (Set.findIndex r rs + 1, Set.findIndex c cs + 1)
36 else Nothing