diff options
Diffstat (limited to 'lib/Numeric/Matrix.hs')
-rw-r--r-- | lib/Numeric/Matrix.hs | 97 |
1 files changed, 97 insertions, 0 deletions
diff --git a/lib/Numeric/Matrix.hs b/lib/Numeric/Matrix.hs new file mode 100644 index 0000000..8d3764a --- /dev/null +++ b/lib/Numeric/Matrix.hs | |||
@@ -0,0 +1,97 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE UndecidableInstances #-} | ||
5 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
6 | |||
7 | ----------------------------------------------------------------------------- | ||
8 | -- | | ||
9 | -- Module : Numeric.Matrix | ||
10 | -- Copyright : (c) Alberto Ruiz 2007 | ||
11 | -- License : GPL-style | ||
12 | -- | ||
13 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
14 | -- Stability : provisional | ||
15 | -- Portability : portable | ||
16 | -- | ||
17 | -- Numeric instances and functions for 'Data.Packed.Matrix's | ||
18 | -- | ||
19 | ----------------------------------------------------------------------------- | ||
20 | |||
21 | module Numeric.Matrix ( | ||
22 | module Data.Packed.Matrix, | ||
23 | ) where | ||
24 | |||
25 | ------------------------------------------------------------------- | ||
26 | |||
27 | import Data.Packed.Vector | ||
28 | import Data.Packed.Matrix | ||
29 | import Numeric.Container | ||
30 | import Numeric.Vector() | ||
31 | |||
32 | import Control.Monad(ap) | ||
33 | |||
34 | ------------------------------------------------------------------- | ||
35 | |||
36 | instance Linear Matrix a => Eq (Matrix a) where | ||
37 | (==) = equal | ||
38 | |||
39 | instance (Linear Matrix a, Num (Vector a)) => Num (Matrix a) where | ||
40 | (+) = liftMatrix2Auto (+) | ||
41 | (-) = liftMatrix2Auto (-) | ||
42 | negate = liftMatrix negate | ||
43 | (*) = liftMatrix2Auto (*) | ||
44 | signum = liftMatrix signum | ||
45 | abs = liftMatrix abs | ||
46 | fromInteger = (1><1) . return . fromInteger | ||
47 | |||
48 | --------------------------------------------------- | ||
49 | |||
50 | instance (Linear Vector a, Fractional (Vector a), Num (Matrix a)) => Fractional (Matrix a) where | ||
51 | fromRational n = (1><1) [fromRational n] | ||
52 | (/) = liftMatrix2Auto (/) | ||
53 | |||
54 | --------------------------------------------------------- | ||
55 | |||
56 | instance (Linear Vector a, Floating (Vector a), Fractional (Matrix a)) => Floating (Matrix a) where | ||
57 | sin = liftMatrix sin | ||
58 | cos = liftMatrix cos | ||
59 | tan = liftMatrix tan | ||
60 | asin = liftMatrix asin | ||
61 | acos = liftMatrix acos | ||
62 | atan = liftMatrix atan | ||
63 | sinh = liftMatrix sinh | ||
64 | cosh = liftMatrix cosh | ||
65 | tanh = liftMatrix tanh | ||
66 | asinh = liftMatrix asinh | ||
67 | acosh = liftMatrix acosh | ||
68 | atanh = liftMatrix atanh | ||
69 | exp = liftMatrix exp | ||
70 | log = liftMatrix log | ||
71 | (**) = liftMatrix2Auto (**) | ||
72 | sqrt = liftMatrix sqrt | ||
73 | pi = (1><1) [pi] | ||
74 | |||
75 | --------------------------------------------------------------- | ||
76 | |||
77 | instance (Linear Vector a, Container Matrix) => (Linear Matrix a) where | ||
78 | scale x = liftMatrix (scale x) | ||
79 | scaleRecip x = liftMatrix (scaleRecip x) | ||
80 | addConstant x = liftMatrix (addConstant x) | ||
81 | add = liftMatrix2 add | ||
82 | sub = liftMatrix2 sub | ||
83 | mul = liftMatrix2 mul | ||
84 | divide = liftMatrix2 divide | ||
85 | equal a b = cols a == cols b && flatten a `equal` flatten b | ||
86 | scalar x = (1><1) [x] | ||
87 | minIndex m = let (r,c) = (rows m,cols m) | ||
88 | i = 1 + (minIndex $ flatten m) | ||
89 | in (i `div` r,i `mod` r) | ||
90 | maxIndex m = let (r,c) = (rows m,cols m) | ||
91 | i = 1 + (maxIndex $ flatten m) | ||
92 | in (i `div` r,i `mod` r) | ||
93 | minElement = ap (@@>) minIndex | ||
94 | maxElement = ap (@@>) maxIndex | ||
95 | |||
96 | ---------------------------------------------------- | ||
97 | |||