summaryrefslogtreecommitdiff
path: root/lib/Numeric/Container.hs
diff options
context:
space:
mode:
authorVivian McPhail <haskell.vivian.mcphail@gmail.com>2010-09-05 08:11:17 +0000
committerVivian McPhail <haskell.vivian.mcphail@gmail.com>2010-09-05 08:11:17 +0000
commitfa4e2233a873bbfee26939c013b56acc160bca7b (patch)
treeba2152dfd8ae8ffa6ead19c1924747c2134a3190 /lib/Numeric/Container.hs
parentb59a56c22f7e4aa518046c41e049e5bf1cdf8204 (diff)
refactor Numeric Vector/Matrix and classes
Diffstat (limited to 'lib/Numeric/Container.hs')
-rw-r--r--lib/Numeric/Container.hs219
1 files changed, 219 insertions, 0 deletions
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
new file mode 100644
index 0000000..0bec2e8
--- /dev/null
+++ b/lib/Numeric/Container.hs
@@ -0,0 +1,219 @@
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6
7-----------------------------------------------------------------------------
8-- |
9-- Module : Numeric.Container
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 classes for containers of numbers, including conversion routines
18--
19-----------------------------------------------------------------------------
20
21module Numeric.Container (
22 RealElement, AutoReal(..),
23 Container(..), Linear(..),
24 Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, IndexOf,
25 Precision(..), comp,
26 module Data.Complex
27) where
28
29import Data.Packed.Vector
30import Data.Packed.Matrix
31import Data.Packed.Internal.Vector
32import Data.Packed.Internal.Matrix
33--import qualified Data.Packed.ST as ST
34
35import Control.Arrow((***))
36
37import Data.Complex
38
39-------------------------------------------------------------------
40
41-- | Supported single-double precision type pairs
42class (Element s, Element d) => Precision s d | s -> d, d -> s where
43 double2FloatG :: Vector d -> Vector s
44 float2DoubleG :: Vector s -> Vector d
45
46instance Precision Float Double where
47 double2FloatG = double2FloatV
48 float2DoubleG = float2DoubleV
49
50instance Precision (Complex Float) (Complex Double) where
51 double2FloatG = asComplex . double2FloatV . asReal
52 float2DoubleG = asComplex . float2DoubleV . asReal
53
54-- | Supported real types
55class (Element t, Element (Complex t), RealFloat t
56-- , RealOf t ~ t, RealOf (Complex t) ~ t
57 )
58 => RealElement t
59
60instance RealElement Double
61
62instance RealElement Float
63
64-- | Conversion utilities
65class Container c where
66 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e)
67 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e)
68 complex' :: (RealElement e) => c e -> c (Complex e)
69 conj :: (RealElement e) => c (Complex e) -> c (Complex e)
70 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
71 single' :: Precision a b => c b -> c a
72 double' :: Precision a b => c a -> c b
73
74comp x = complex' x
75
76instance Container Vector where
77 toComplex = toComplexV
78 fromComplex = fromComplexV
79 complex' v = toComplex (v,constantD 0 (dim v))
80 conj = conjV
81 cmap = mapVector
82 single' = double2FloatG
83 double' = float2DoubleG
84
85instance Container Matrix where
86 toComplex = uncurry $ liftMatrix2 $ curry toComplex
87 fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z
88 where c = cols z
89 complex' = liftMatrix complex'
90 conj = liftMatrix conj
91 cmap f = liftMatrix (cmap f)
92 single' = liftMatrix single'
93 double' = liftMatrix double'
94
95-------------------------------------------------------------------
96
97type family RealOf x
98
99type instance RealOf Double = Double
100type instance RealOf (Complex Double) = Double
101
102type instance RealOf Float = Float
103type instance RealOf (Complex Float) = Float
104
105type family ComplexOf x
106
107type instance ComplexOf Double = Complex Double
108type instance ComplexOf (Complex Double) = Complex Double
109
110type instance ComplexOf Float = Complex Float
111type instance ComplexOf (Complex Float) = Complex Float
112
113type family SingleOf x
114
115type instance SingleOf Double = Float
116type instance SingleOf Float = Float
117
118type instance SingleOf (Complex a) = Complex (SingleOf a)
119
120type family DoubleOf x
121
122type instance DoubleOf Double = Double
123type instance DoubleOf Float = Double
124
125type instance DoubleOf (Complex a) = Complex (DoubleOf a)
126
127type family ElementOf c
128
129type instance ElementOf (Vector a) = a
130type instance ElementOf (Matrix a) = a
131
132type family IndexOf c
133
134type instance IndexOf Vector = Int
135type instance IndexOf Matrix = (Int,Int)
136
137-------------------------------------------------------------------
138
139-- | generic conversion functions
140class Convert t where
141 real :: Container c => c (RealOf t) -> c t
142 complex :: Container c => c t -> c (ComplexOf t)
143 single :: Container c => c t -> c (SingleOf t)
144 double :: Container c => c t -> c (DoubleOf t)
145
146instance Convert Double where
147 real = id
148 complex = complex'
149 single = single'
150 double = id
151
152instance Convert Float where
153 real = id
154 complex = complex'
155 single = id
156 double = double'
157
158instance Convert (Complex Double) where
159 real = complex'
160 complex = id
161 single = single'
162 double = id
163
164instance Convert (Complex Float) where
165 real = complex'
166 complex = id
167 single = id
168 double = double'
169
170-------------------------------------------------------------------
171
172-- | to be replaced by Convert
173class Convert t => AutoReal t where
174 real'' :: Container c => c Double -> c t
175 complex'' :: Container c => c t -> c (Complex Double)
176
177instance AutoReal Double where
178 real'' = real
179 complex'' = complex
180
181instance AutoReal (Complex Double) where
182 real'' = real
183 complex'' = complex
184
185instance AutoReal Float where
186 real'' = real . single
187 complex'' = double . complex
188
189instance AutoReal (Complex Float) where
190 real'' = real . single
191 complex'' = double . complex
192
193-------------------------------------------------------------------
194
195-- | Basic element-by-element functions.
196class (Element e, Container c) => Linear c e where
197 -- | create a structure with a single element
198 scalar :: e -> c e
199 scale :: e -> c e -> c e
200 -- | scale the element by element reciprocal of the object:
201 --
202 -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@
203 scaleRecip :: e -> c e -> c e
204 addConstant :: e -> c e -> c e
205 add :: c e -> c e -> c e
206 sub :: c e -> c e -> c e
207 -- | element by element multiplication
208 mul :: c e -> c e -> c e
209 -- | element by element division
210 divide :: c e -> c e -> c e
211 equal :: c e -> c e -> Bool
212 --
213 minIndex :: c e -> IndexOf c
214 maxIndex :: c e -> IndexOf c
215 minElement :: c e -> e
216 maxElement :: c e -> e
217
218
219