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