summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2014-05-16 20:57:13 +0200
committerAlberto Ruiz <aruiz@um.es>2014-05-16 20:57:13 +0200
commitfd94ecb3c3032beccdca4a4dee38bb306f57cd8b (patch)
tree81d7318217d6da4a057e587003b44425afe6ddcd /packages/base/src/Numeric
parentd4d9082a8d7d3eed6cb5f188fc3b476847dcac27 (diff)
Numeric.Container compatible
Diffstat (limited to 'packages/base/src/Numeric')
-rw-r--r--packages/base/src/Numeric/Chain.hs2
-rw-r--r--packages/base/src/Numeric/Container.hs240
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Algorithms.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Base.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Data.hs3
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Devel.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util.hs14
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs2
-rw-r--r--packages/base/src/Numeric/Matrix.hs2
-rw-r--r--packages/base/src/Numeric/Vector.hs2
10 files changed, 10 insertions, 261 deletions
diff --git a/packages/base/src/Numeric/Chain.hs b/packages/base/src/Numeric/Chain.hs
index fbdb01b..c6160e9 100644
--- a/packages/base/src/Numeric/Chain.hs
+++ b/packages/base/src/Numeric/Chain.hs
@@ -19,7 +19,7 @@ module Numeric.Chain (
19import Data.Maybe 19import Data.Maybe
20 20
21import Data.Packed.Matrix 21import Data.Packed.Matrix
22import Data.Packed.Numeric 22import Data.Packed.Internal.Numeric
23 23
24import qualified Data.Array.IArray as A 24import qualified Data.Array.IArray as A
25 25
diff --git a/packages/base/src/Numeric/Container.hs b/packages/base/src/Numeric/Container.hs
deleted file mode 100644
index 240e5f5..0000000
--- a/packages/base/src/Numeric/Container.hs
+++ /dev/null
@@ -1,240 +0,0 @@
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) where
53
54import Data.Packed hiding (stepD, stepF, condD, condF, conjugateC, conjugateQ)
55import Data.Packed.Numeric
56import Data.Complex
57import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
58import Data.Monoid(Monoid(mconcat))
59
60------------------------------------------------------------------
61
62{- | Creates a real vector containing a range of values:
63
64>>> linspace 5 (-3,7::Double)
65fromList [-3.0,-0.5,2.0,4.5,7.0]@
66
67>>> linspace 5 (8,2+i) :: Vector (Complex Double)
68fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
69
70Logarithmic spacing can be defined as follows:
71
72@logspace n (a,b) = 10 ** linspace n (a,b)@
73-}
74linspace :: (Container Vector e) => Int -> (e, e) -> Vector e
75linspace 0 (a,b) = fromList[(a+b)/2]
76linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
77 where s = (b-a)/fromIntegral (n-1)
78
79--------------------------------------------------------
80
81class Contraction a b c | a b -> c
82 where
83 infixl 7 <.>
84 {- | Matrix product, matrix vector product, and dot product
85
86Examples:
87
88>>> let a = (3><4) [1..] :: Matrix Double
89>>> let v = fromList [1,0,2,-1] :: Vector Double
90>>> let u = fromList [1,2,3] :: Vector Double
91
92>>> a
93(3><4)
94 [ 1.0, 2.0, 3.0, 4.0
95 , 5.0, 6.0, 7.0, 8.0
96 , 9.0, 10.0, 11.0, 12.0 ]
97
98matrix × matrix:
99
100>>> disp 2 (a <.> trans a)
1013x3
102 30 70 110
103 70 174 278
104110 278 446
105
106matrix × vector:
107
108>>> a <.> v
109fromList [3.0,11.0,19.0]
110
111dot product:
112
113>>> u <.> fromList[3,2,1::Double]
11410
115
116For complex vectors the first argument is conjugated:
117
118>>> fromList [1,i] <.> fromList[2*i+1,3]
1191.0 :+ (-1.0)
120
121>>> fromList [1,i,1-i] <.> complex a
122fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0]
123
124-}
125 (<.>) :: a -> b -> c
126
127
128instance (Product t, Container Vector t) => Contraction (Vector t) (Vector t) t where
129 u <.> v = conj u `udot` v
130
131instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
132 (<.>) = mXv
133
134instance (Container Vector t, Product t) => Contraction (Vector t) (Matrix t) (Vector t) where
135 (<.>) v m = (conj v) `vXm` m
136
137instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
138 (<.>) = mXm
139
140
141--------------------------------------------------------------------------------
142
143class Mul a b c | a b -> c where
144 infixl 7 <>
145 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
146 (<>) :: Product t => a t -> b t -> c t
147
148instance Mul Matrix Matrix Matrix where
149 (<>) = mXm
150
151instance Mul Matrix Vector Vector where
152 (<>) m v = flatten $ m <> asColumn v
153
154instance Mul Vector Matrix Vector where
155 (<>) v m = flatten $ asRow v <> m
156
157--------------------------------------------------------------------------------
158
159class LSDiv c where
160 infixl 7 <\>
161 -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD)
162 (<\>) :: Field t => Matrix t -> c t -> c t
163
164instance LSDiv Vector where
165 m <\> v = flatten (linearSolveSVD m (reshape 1 v))
166
167instance LSDiv Matrix where
168 (<\>) = linearSolveSVD
169
170--------------------------------------------------------------------------------
171
172class Konst e d c | d -> c, c -> d
173 where
174 -- |
175 -- >>> konst 7 3 :: Vector Float
176 -- fromList [7.0,7.0,7.0]
177 --
178 -- >>> konst i (3::Int,4::Int)
179 -- (3><4)
180 -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
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 --
184 konst :: e -> d -> c e
185
186instance Container Vector e => Konst e Int Vector
187 where
188 konst = konst'
189
190instance Container Vector e => Konst e (Int,Int) Matrix
191 where
192 konst = konst'
193
194--------------------------------------------------------------------------------
195
196class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
197 where
198 -- |
199 -- >>> build 5 (**2) :: Vector Double
200 -- fromList [0.0,1.0,4.0,9.0,16.0]
201 --
202 -- Hilbert matrix of order N:
203 --
204 -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
205 -- >>> putStr . dispf 2 $ hilb 3
206 -- 3x3
207 -- 1.00 0.50 0.33
208 -- 0.50 0.33 0.25
209 -- 0.33 0.25 0.20
210 --
211 build :: d -> f -> c e
212
213instance Container Vector e => Build Int (e -> e) Vector e
214 where
215 build = build'
216
217instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
218 where
219 build = build'
220
221--------------------------------------------------------------------------------
222
223{- | alternative operator for '(\<.\>)'
224
225x25c7, white diamond
226
227-}
228(◇) :: Contraction a b c => a -> b -> c
229infixl 7 ◇
230(◇) = (<.>)
231
232-- | dot product: @cdot u v = 'udot' ('conj' u) v@
233dot :: (Container Vector t, Product t) => Vector t -> Vector t -> t
234dot u v = udot (conj u) v
235
236--------------------------------------------------------------------------------
237
238optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t
239optimiseMult = mconcat
240
diff --git a/packages/base/src/Numeric/LinearAlgebra/Algorithms.hs b/packages/base/src/Numeric/LinearAlgebra/Algorithms.hs
index 92761be..063bfc9 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Algorithms.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Algorithms.hs
@@ -81,7 +81,7 @@ import Data.Packed
81import Numeric.LinearAlgebra.LAPACK as LAPACK 81import Numeric.LinearAlgebra.LAPACK as LAPACK
82import Data.List(foldl1') 82import Data.List(foldl1')
83import Data.Array 83import Data.Array
84import Data.Packed.Numeric 84import Data.Packed.Internal.Numeric
85 85
86 86
87{- | Generic linear algebra functions for double precision real and complex matrices. 87{- | Generic linear algebra functions for double precision real and complex matrices.
diff --git a/packages/base/src/Numeric/LinearAlgebra/Base.hs b/packages/base/src/Numeric/LinearAlgebra/Base.hs
index 1af4711..395c84a 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Base.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Base.hs
@@ -129,7 +129,7 @@ import Numeric.LinearAlgebra.Data
129 129
130import Numeric.Matrix() 130import Numeric.Matrix()
131import Numeric.Vector() 131import Numeric.Vector()
132import Numeric.Container 132import Data.Packed.Numeric
133import Numeric.LinearAlgebra.Algorithms 133import Numeric.LinearAlgebra.Algorithms
134import Numeric.LinearAlgebra.Util 134import Numeric.LinearAlgebra.Util
135 135
diff --git a/packages/base/src/Numeric/LinearAlgebra/Data.hs b/packages/base/src/Numeric/LinearAlgebra/Data.hs
index 3bc88f9..2754576 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Data.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Data.hs
@@ -61,8 +61,7 @@ module Numeric.LinearAlgebra.Data(
61 61
62import Data.Packed.Vector 62import Data.Packed.Vector
63import Data.Packed.Matrix 63import Data.Packed.Matrix
64import Numeric.Container 64import Data.Packed.Numeric
65import Data.Packed.IO
66import Numeric.LinearAlgebra.Util 65import Numeric.LinearAlgebra.Util
67import Data.Complex 66import Data.Complex
68 67
diff --git a/packages/base/src/Numeric/LinearAlgebra/Devel.hs b/packages/base/src/Numeric/LinearAlgebra/Devel.hs
index c41db2d..b5ef60d 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Devel.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Devel.hs
@@ -60,7 +60,7 @@ module Numeric.LinearAlgebra.Devel(
60import Data.Packed.Foreign 60import Data.Packed.Foreign
61import Data.Packed.Development 61import Data.Packed.Development
62import Data.Packed.ST 62import Data.Packed.ST
63import Numeric.Container(Container,Contraction,LSDiv,Product, 63import Data.Packed.Numeric(Container,Contraction,LSDiv,Product,
64 Complexable(),RealElement(), 64 Complexable(),RealElement(),
65 RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf) 65 RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf)
66import Data.Packed 66import Data.Packed
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs
index f0470ab..440f6d1 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Util.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs
@@ -45,25 +45,15 @@ module Numeric.LinearAlgebra.Util(
45 vec, 45 vec,
46 vech, 46 vech,
47 dup, 47 dup,
48 vtrans, 48 vtrans
49{- -- * Plot
50 mplot,
51 plot, parametricPlot,
52 splot, mesh, meshdom,
53 matrixToPGM, imshow,
54 gnuplotX, gnuplotpdf, gnuplotWin
55-}
56) where 49) where
57 50
58import Numeric.Container 51import Data.Packed.Numeric
59import Data.Packed.IO
60import Numeric.LinearAlgebra.Algorithms hiding (i) 52import Numeric.LinearAlgebra.Algorithms hiding (i)
61import Numeric.Matrix() 53import Numeric.Matrix()
62import Numeric.Vector() 54import Numeric.Vector()
63 55
64import Numeric.LinearAlgebra.Util.Convolution 56import Numeric.LinearAlgebra.Util.Convolution
65--import Graphics.Plot
66
67 57
68{- | print a real matrix with given number of digits after the decimal point 58{- | print a real matrix with given number of digits after the decimal point
69 59
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs b/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs
index 1775f14..3cad8d7 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Util/Convolution.hs
@@ -16,7 +16,7 @@ module Numeric.LinearAlgebra.Util.Convolution(
16 corr2, conv2, separable 16 corr2, conv2, separable
17) where 17) where
18 18
19import Numeric.Container 19import Data.Packed.Numeric
20 20
21 21
22vectSS :: Element t => Int -> Vector t -> Matrix t 22vectSS :: Element t => Int -> Vector t -> Matrix t
diff --git a/packages/base/src/Numeric/Matrix.hs b/packages/base/src/Numeric/Matrix.hs
index 962ee84..719b591 100644
--- a/packages/base/src/Numeric/Matrix.hs
+++ b/packages/base/src/Numeric/Matrix.hs
@@ -27,7 +27,7 @@ module Numeric.Matrix (
27------------------------------------------------------------------- 27-------------------------------------------------------------------
28 28
29import Data.Packed 29import Data.Packed
30import Data.Packed.Numeric 30import Data.Packed.Internal.Numeric
31import qualified Data.Monoid as M 31import qualified Data.Monoid as M
32import Data.List(partition) 32import Data.List(partition)
33import Numeric.Chain 33import Numeric.Chain
diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs
index 3a425f5..28b453f 100644
--- a/packages/base/src/Numeric/Vector.hs
+++ b/packages/base/src/Numeric/Vector.hs
@@ -21,7 +21,7 @@ module Numeric.Vector () where
21 21
22import Numeric.Vectorized 22import Numeric.Vectorized
23import Data.Packed.Vector 23import Data.Packed.Vector
24import Data.Packed.Numeric 24import Data.Packed.Internal.Numeric
25 25
26------------------------------------------------------------------- 26-------------------------------------------------------------------
27 27