summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2010-09-08 08:36:11 +0000
committerAlberto Ruiz <aruiz@um.es>2010-09-08 08:36:11 +0000
commit06a4d3fecb9b918e4c0497269484b00c814605a4 (patch)
tree12dec0a6d617159299422355d1c21f44ccfaff62 /lib
parenta858bf910291b63603a226c3190ecb36de01b5ba (diff)
add Conversion.hs
Diffstat (limited to 'lib')
-rw-r--r--lib/Numeric/Conversion.hs205
1 files changed, 205 insertions, 0 deletions
diff --git a/lib/Numeric/Conversion.hs b/lib/Numeric/Conversion.hs
new file mode 100644
index 0000000..b05069c
--- /dev/null
+++ b/lib/Numeric/Conversion.hs
@@ -0,0 +1,205 @@
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 2007
12-- License : GPL-style
13--
14-- Maintainer : Alberto Ruiz <aruiz@um.es>
15-- Stability : provisional
16-- Portability : portable
17--
18-- Numeric classes for containers of numbers, including conversion routines
19--
20-----------------------------------------------------------------------------
21
22module Numeric.Conversion (
23 RealElement, --Precision,
24 ComplexContainer(toComplex,fromComplex,conj,comp),
25 Convert(..), --AutoReal(..),
26 RealOf, ComplexOf, SingleOf, DoubleOf,
27 module Data.Complex
28) where
29
30
31import Data.Packed.Internal.Vector
32import Data.Packed.Internal.Matrix
33--import Numeric.GSL.Vector
34
35import Data.Complex
36--import Control.Monad(ap)
37import Control.Arrow((***))
38
39--import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ)
40
41-------------------------------------------------------------------
42
43-- | Supported single-double precision type pairs
44class (Element s, Element d) => Precision s d | s -> d, d -> s where
45 double2FloatG :: Vector d -> Vector s
46 float2DoubleG :: Vector s -> Vector d
47
48instance Precision Float Double where
49 double2FloatG = double2FloatV
50 float2DoubleG = float2DoubleV
51
52instance Precision (Complex Float) (Complex Double) where
53 double2FloatG = asComplex . double2FloatV . asReal
54 float2DoubleG = asComplex . float2DoubleV . asReal
55
56-- | Supported real types
57class (Element t, Element (Complex t), RealFloat t
58-- , RealOf t ~ t, RealOf (Complex t) ~ t
59 )
60 => RealElement t
61
62instance RealElement Double
63
64instance RealElement Float
65
66-- | Conversion utilities
67class ComplexContainer c where
68 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e)
69 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e)
70 comp :: (RealElement e) => c e -> c (Complex e)
71 conj :: (RealElement e) => c (Complex e) -> c (Complex e)
72-- cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
73 single' :: Precision a b => c b -> c a
74 double' :: Precision a b => c a -> c b
75
76
77instance ComplexContainer Vector where
78 toComplex = toComplexV
79 fromComplex = fromComplexV
80 comp v = toComplex (v,constantD 0 (dim v))
81 conj = conjV
82-- cmap = mapVector
83 single' = double2FloatG
84 double' = float2DoubleG
85
86
87-- | obtains the complex conjugate of a complex vector
88conjV :: (RealElement a) => Vector (Complex a) -> Vector (Complex a)
89conjV = mapVector conjugate
90
91-- | creates a complex vector from vectors with real and imaginary parts
92toComplexV :: (RealElement a) => (Vector a, Vector a) -> Vector (Complex a)
93toComplexV (r,i) = asComplex $ flatten $ fromColumns [r,i]
94
95-- | the inverse of 'toComplex'
96fromComplexV :: (RealElement a) => Vector (Complex a) -> (Vector a, Vector a)
97fromComplexV z = (r,i) where
98 [r,i] = toColumns $ reshape 2 $ asReal z
99
100
101instance ComplexContainer Matrix where
102 toComplex = uncurry $ liftMatrix2 $ curry toComplex
103 fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z
104 where c = cols z
105 comp = liftMatrix comp
106 conj = liftMatrix conj
107-- cmap f = liftMatrix (cmap f)
108 single' = liftMatrix single'
109 double' = liftMatrix double'
110
111-------------------------------------------------------------------
112
113type family RealOf x
114
115type instance RealOf Double = Double
116type instance RealOf (Complex Double) = Double
117
118type instance RealOf Float = Float
119type instance RealOf (Complex Float) = Float
120
121type family ComplexOf x
122
123type instance ComplexOf Double = Complex Double
124type instance ComplexOf (Complex Double) = Complex Double
125
126type instance ComplexOf Float = Complex Float
127type instance ComplexOf (Complex Float) = Complex Float
128
129type family SingleOf x
130
131type instance SingleOf Double = Float
132type instance SingleOf Float = Float
133
134type instance SingleOf (Complex a) = Complex (SingleOf a)
135
136type family DoubleOf x
137
138type instance DoubleOf Double = Double
139type instance DoubleOf Float = Double
140
141type instance DoubleOf (Complex a) = Complex (DoubleOf a)
142
143type family ElementOf c
144
145type instance ElementOf (Vector a) = a
146type instance ElementOf (Matrix a) = a
147
148
149-------------------------------------------------------------------
150
151class (Element t, Element (RealOf t)) => Convert t where
152 real :: ComplexContainer c => c (RealOf t) -> c t
153 complex :: ComplexContainer c => c t -> c (ComplexOf t)
154 single :: ComplexContainer c => c t -> c (SingleOf t)
155 double :: ComplexContainer c => c t -> c (DoubleOf t)
156
157
158instance Convert Double where
159 real = id
160 complex = comp
161 single = single'
162 double = id
163
164instance Convert Float where
165 real = id
166 complex = comp
167 single = id
168 double = double'
169
170instance Convert (Complex Double) where
171 real = comp
172 complex = id
173 single = single'
174 double = id
175
176instance Convert (Complex Float) where
177 real = comp
178 complex = id
179 single = id
180 double = double'
181
182-------------------------------------------------------------------
183
184-- | to be replaced by Convert
185class Convert t => AutoReal t where
186 real'' :: ComplexContainer c => c Double -> c t
187 complex'' :: ComplexContainer c => c t -> c (Complex Double)
188
189
190instance AutoReal Double where
191 real'' = real
192 complex'' = complex
193
194instance AutoReal (Complex Double) where
195 real'' = real
196 complex'' = complex
197
198instance AutoReal Float where
199 real'' = real . single
200 complex'' = double . complex
201
202instance AutoReal (Complex Float) where
203 real'' = real . single
204 complex'' = double . complex
205