summaryrefslogtreecommitdiff
path: root/packages/hmatrix/src/Numeric/Container.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/hmatrix/src/Numeric/Container.hs')
-rw-r--r--packages/hmatrix/src/Numeric/Container.hs241
1 files changed, 241 insertions, 0 deletions
diff --git a/packages/hmatrix/src/Numeric/Container.hs b/packages/hmatrix/src/Numeric/Container.hs
new file mode 100644
index 0000000..146780d
--- /dev/null
+++ b/packages/hmatrix/src/Numeric/Container.hs
@@ -0,0 +1,241 @@
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6{-# LANGUAGE UndecidableInstances #-}
7
8-----------------------------------------------------------------------------
9-- |
10-- Module : Numeric.Container
11-- Copyright : (c) Alberto Ruiz 2010-14
12-- License : BSD3
13-- Maintainer : Alberto Ruiz
14-- Stability : provisional
15-- Portability : portable
16--
17-- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines.
18--
19-- The 'Container' class is used to define optimized generic functions which work
20-- on 'Vector' and 'Matrix' with real or complex elements.
21--
22-- Some of these functions are also available in the instances of the standard
23-- numeric Haskell classes provided by "Numeric.LinearAlgebra".
24--
25-----------------------------------------------------------------------------
26{-# OPTIONS_HADDOCK hide #-}
27
28module Numeric.Container (
29 -- * Basic functions
30 module Data.Packed,
31 konst, build,
32 linspace,
33 diag, ident,
34 ctrans,
35 -- * Generic operations
36 Container(..),
37 -- * Matrix product
38 Product(..), udot, dot, (◇),
39 Mul(..),
40 Contraction(..),
41 optimiseMult,
42 mXm,mXv,vXm,LSDiv(..),
43 outer, kronecker,
44 -- * Element conversion
45 Convert(..),
46 Complexable(),
47 RealElement(),
48
49 RealOf, ComplexOf, SingleOf, DoubleOf,
50
51 IndexOf,
52 module Data.Complex
53) where
54
55import Data.Packed hiding (stepD, stepF, condD, condF, conjugateC, conjugateQ)
56import Data.Packed.Numeric
57import Data.Complex
58import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
59import Data.Monoid(Monoid(mconcat))
60
61------------------------------------------------------------------
62
63{- | Creates a real vector containing a range of values:
64
65>>> linspace 5 (-3,7::Double)
66fromList [-3.0,-0.5,2.0,4.5,7.0]@
67
68>>> linspace 5 (8,2+i) :: Vector (Complex Double)
69fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
70
71Logarithmic spacing can be defined as follows:
72
73@logspace n (a,b) = 10 ** linspace n (a,b)@
74-}
75linspace :: (Container Vector e) => Int -> (e, e) -> Vector e
76linspace 0 (a,b) = fromList[(a+b)/2]
77linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
78 where s = (b-a)/fromIntegral (n-1)
79
80--------------------------------------------------------
81
82class Contraction a b c | a b -> c
83 where
84 infixl 7 <.>
85 {- | Matrix product, matrix vector product, and dot product
86
87Examples:
88
89>>> let a = (3><4) [1..] :: Matrix Double
90>>> let v = fromList [1,0,2,-1] :: Vector Double
91>>> let u = fromList [1,2,3] :: Vector Double
92
93>>> a
94(3><4)
95 [ 1.0, 2.0, 3.0, 4.0
96 , 5.0, 6.0, 7.0, 8.0
97 , 9.0, 10.0, 11.0, 12.0 ]
98
99matrix × matrix:
100
101>>> disp 2 (a <.> trans a)
1023x3
103 30 70 110
104 70 174 278
105110 278 446
106
107matrix × vector:
108
109>>> a <.> v
110fromList [3.0,11.0,19.0]
111
112dot product:
113
114>>> u <.> fromList[3,2,1::Double]
11510
116
117For complex vectors the first argument is conjugated:
118
119>>> fromList [1,i] <.> fromList[2*i+1,3]
1201.0 :+ (-1.0)
121
122>>> fromList [1,i,1-i] <.> complex a
123fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0]
124
125-}
126 (<.>) :: a -> b -> c
127
128
129instance (Product t, Container Vector t) => Contraction (Vector t) (Vector t) t where
130 u <.> v = conj u `udot` v
131
132instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
133 (<.>) = mXv
134
135instance (Container Vector t, Product t) => Contraction (Vector t) (Matrix t) (Vector t) where
136 (<.>) v m = (conj v) `vXm` m
137
138instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
139 (<.>) = mXm
140
141
142--------------------------------------------------------------------------------
143
144class Mul a b c | a b -> c where
145 infixl 7 <>
146 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
147 (<>) :: Product t => a t -> b t -> c t
148
149instance Mul Matrix Matrix Matrix where
150 (<>) = mXm
151
152instance Mul Matrix Vector Vector where
153 (<>) m v = flatten $ m <> asColumn v
154
155instance Mul Vector Matrix Vector where
156 (<>) v m = flatten $ asRow v <> m
157
158--------------------------------------------------------------------------------
159
160class LSDiv c where
161 infixl 7 <\>
162 -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD)
163 (<\>) :: Field t => Matrix t -> c t -> c t
164
165instance LSDiv Vector where
166 m <\> v = flatten (linearSolveSVD m (reshape 1 v))
167
168instance LSDiv Matrix where
169 (<\>) = linearSolveSVD
170
171--------------------------------------------------------------------------------
172
173class Konst e d c | d -> c, c -> d
174 where
175 -- |
176 -- >>> konst 7 3 :: Vector Float
177 -- fromList [7.0,7.0,7.0]
178 --
179 -- >>> konst i (3::Int,4::Int)
180 -- (3><4)
181 -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
182 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
183 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]
184 --
185 konst :: e -> d -> c e
186
187instance Container Vector e => Konst e Int Vector
188 where
189 konst = konst'
190
191instance Container Vector e => Konst e (Int,Int) Matrix
192 where
193 konst = konst'
194
195--------------------------------------------------------------------------------
196
197class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
198 where
199 -- |
200 -- >>> build 5 (**2) :: Vector Double
201 -- fromList [0.0,1.0,4.0,9.0,16.0]
202 --
203 -- Hilbert matrix of order N:
204 --
205 -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
206 -- >>> putStr . dispf 2 $ hilb 3
207 -- 3x3
208 -- 1.00 0.50 0.33
209 -- 0.50 0.33 0.25
210 -- 0.33 0.25 0.20
211 --
212 build :: d -> f -> c e
213
214instance Container Vector e => Build Int (e -> e) Vector e
215 where
216 build = build'
217
218instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
219 where
220 build = build'
221
222--------------------------------------------------------------------------------
223
224{- | alternative operator for '(\<.\>)'
225
226x25c7, white diamond
227
228-}
229(◇) :: Contraction a b c => a -> b -> c
230infixl 7 ◇
231(◇) = (<.>)
232
233-- | dot product: @cdot u v = 'udot' ('conj' u) v@
234dot :: (Container Vector t, Product t) => Vector t -> Vector t -> t
235dot u v = udot (conj u) v
236
237--------------------------------------------------------------------------------
238
239optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t
240optimiseMult = mconcat
241