summaryrefslogtreecommitdiff
path: root/packages/base/src/Internal/Conversion.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-06-05 16:49:59 +0200
committerAlberto Ruiz <aruiz@um.es>2015-06-05 16:49:59 +0200
commit45ccf2b25783c656b5ecd48027d8f3a3f2dea001 (patch)
tree799674c6a7d12a6859f23905626048d7f9dc2083 /packages/base/src/Internal/Conversion.hs
parentbfa68b73572538d56038b3350ce46d2b3af19dba (diff)
move conversion
Diffstat (limited to 'packages/base/src/Internal/Conversion.hs')
-rw-r--r--packages/base/src/Internal/Conversion.hs89
1 files changed, 89 insertions, 0 deletions
diff --git a/packages/base/src/Internal/Conversion.hs b/packages/base/src/Internal/Conversion.hs
new file mode 100644
index 0000000..2f4a9c7
--- /dev/null
+++ b/packages/base/src/Internal/Conversion.hs
@@ -0,0 +1,89 @@
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6{-# LANGUAGE UndecidableInstances #-}
7
8-----------------------------------------------------------------------------
9-- |
10-- Module : Numeric.Conversion
11-- Copyright : (c) Alberto Ruiz 2010
12-- License : BSD3
13-- Maintainer : Alberto Ruiz
14-- Stability : provisional
15--
16-- Conversion routines
17--
18-----------------------------------------------------------------------------
19
20
21module Internal.Conversion (
22 Complexable(..), RealElement,
23 module Data.Complex
24) where
25
26import Internal.Vector
27import Internal.Matrix
28import Internal.Vectorized
29import Data.Complex
30import Control.Arrow((***))
31
32-------------------------------------------------------------------
33
34-- | Supported single-double precision type pairs
35class (Element s, Element d) => Precision s d | s -> d, d -> s where
36 double2FloatG :: Vector d -> Vector s
37 float2DoubleG :: Vector s -> Vector d
38
39instance Precision Float Double where
40 double2FloatG = double2FloatV
41 float2DoubleG = float2DoubleV
42
43instance Precision (Complex Float) (Complex Double) where
44 double2FloatG = asComplex . double2FloatV . asReal
45 float2DoubleG = asComplex . float2DoubleV . asReal
46
47-- | Supported real types
48class (Element t, Element (Complex t), RealFloat t)
49 => RealElement t
50
51instance RealElement Double
52instance RealElement Float
53
54
55-- | Structures that may contain complex numbers
56class Complexable c where
57 toComplex' :: (RealElement e) => (c e, c e) -> c (Complex e)
58 fromComplex' :: (RealElement e) => c (Complex e) -> (c e, c e)
59 comp' :: (RealElement e) => c e -> c (Complex e)
60 single' :: Precision a b => c b -> c a
61 double' :: Precision a b => c a -> c b
62
63
64instance Complexable Vector where
65 toComplex' = toComplexV
66 fromComplex' = fromComplexV
67 comp' v = toComplex' (v,constantD 0 (dim v))
68 single' = double2FloatG
69 double' = float2DoubleG
70
71
72-- | creates a complex vector from vectors with real and imaginary parts
73toComplexV :: (RealElement a) => (Vector a, Vector a) -> Vector (Complex a)
74toComplexV (r,i) = asComplex $ flatten $ fromColumns [r,i]
75
76-- | the inverse of 'toComplex'
77fromComplexV :: (RealElement a) => Vector (Complex a) -> (Vector a, Vector a)
78fromComplexV z = (r,i) where
79 [r,i] = toColumns $ reshape 2 $ asReal z
80
81
82instance Complexable Matrix where
83 toComplex' = uncurry $ liftMatrix2 $ curry toComplex'
84 fromComplex' z = (reshape c *** reshape c) . fromComplex' . flatten $ z
85 where c = cols z
86 comp' = liftMatrix comp'
87 single' = liftMatrix single'
88 double' = liftMatrix double'
89