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