summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/Vector.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Numeric/Vector.hs')
-rw-r--r--packages/base/src/Numeric/Vector.hs159
1 files changed, 159 insertions, 0 deletions
diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs
new file mode 100644
index 0000000..2769cd9
--- /dev/null
+++ b/packages/base/src/Numeric/Vector.hs
@@ -0,0 +1,159 @@
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE UndecidableInstances #-}
5{-# LANGUAGE MultiParamTypeClasses #-}
6-----------------------------------------------------------------------------
7-- |
8-- Module : Numeric.Vector
9-- Copyright : (c) Alberto Ruiz 2011
10-- License : GPL-style
11--
12-- Maintainer : Alberto Ruiz <aruiz@um.es>
13-- Stability : provisional
14-- Portability : portable
15--
16-- Provides instances of standard classes 'Show', 'Read', 'Eq',
17-- 'Num', 'Fractional', and 'Floating' for 'Vector'.
18--
19-----------------------------------------------------------------------------
20
21module Numeric.Vector () where
22
23import Numeric.Vectorized
24import Data.Packed.Vector
25import Data.Packed.Numeric
26
27-------------------------------------------------------------------
28
29adaptScalar f1 f2 f3 x y
30 | dim x == 1 = f1 (x@>0) y
31 | dim y == 1 = f3 x (y@>0)
32 | otherwise = f2 x y
33
34------------------------------------------------------------------
35
36instance Num (Vector Float) where
37 (+) = adaptScalar addConstant add (flip addConstant)
38 negate = scale (-1)
39 (*) = adaptScalar scale mul (flip scale)
40 signum = vectorMapF Sign
41 abs = vectorMapF Abs
42 fromInteger = fromList . return . fromInteger
43
44instance Num (Vector Double) where
45 (+) = adaptScalar addConstant add (flip addConstant)
46 negate = scale (-1)
47 (*) = adaptScalar scale mul (flip scale)
48 signum = vectorMapR Sign
49 abs = vectorMapR Abs
50 fromInteger = fromList . return . fromInteger
51
52instance Num (Vector (Complex Double)) where
53 (+) = adaptScalar addConstant add (flip addConstant)
54 negate = scale (-1)
55 (*) = adaptScalar scale mul (flip scale)
56 signum = vectorMapC Sign
57 abs = vectorMapC Abs
58 fromInteger = fromList . return . fromInteger
59
60instance Num (Vector (Complex Float)) where
61 (+) = adaptScalar addConstant add (flip addConstant)
62 negate = scale (-1)
63 (*) = adaptScalar scale mul (flip scale)
64 signum = vectorMapQ Sign
65 abs = vectorMapQ Abs
66 fromInteger = fromList . return . fromInteger
67
68---------------------------------------------------
69
70instance (Container Vector a, Num (Vector a)) => Fractional (Vector a) where
71 fromRational n = fromList [fromRational n]
72 (/) = adaptScalar f divide g where
73 r `f` v = scaleRecip r v
74 v `g` r = scale (recip r) v
75
76-------------------------------------------------------
77
78instance Floating (Vector Float) where
79 sin = vectorMapF Sin
80 cos = vectorMapF Cos
81 tan = vectorMapF Tan
82 asin = vectorMapF ASin
83 acos = vectorMapF ACos
84 atan = vectorMapF ATan
85 sinh = vectorMapF Sinh
86 cosh = vectorMapF Cosh
87 tanh = vectorMapF Tanh
88 asinh = vectorMapF ASinh
89 acosh = vectorMapF ACosh
90 atanh = vectorMapF ATanh
91 exp = vectorMapF Exp
92 log = vectorMapF Log
93 sqrt = vectorMapF Sqrt
94 (**) = adaptScalar (vectorMapValF PowSV) (vectorZipF Pow) (flip (vectorMapValF PowVS))
95 pi = fromList [pi]
96
97-------------------------------------------------------------
98
99instance Floating (Vector Double) where
100 sin = vectorMapR Sin
101 cos = vectorMapR Cos
102 tan = vectorMapR Tan
103 asin = vectorMapR ASin
104 acos = vectorMapR ACos
105 atan = vectorMapR ATan
106 sinh = vectorMapR Sinh
107 cosh = vectorMapR Cosh
108 tanh = vectorMapR Tanh
109 asinh = vectorMapR ASinh
110 acosh = vectorMapR ACosh
111 atanh = vectorMapR ATanh
112 exp = vectorMapR Exp
113 log = vectorMapR Log
114 sqrt = vectorMapR Sqrt
115 (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS))
116 pi = fromList [pi]
117
118-------------------------------------------------------------
119
120instance Floating (Vector (Complex Double)) where
121 sin = vectorMapC Sin
122 cos = vectorMapC Cos
123 tan = vectorMapC Tan
124 asin = vectorMapC ASin
125 acos = vectorMapC ACos
126 atan = vectorMapC ATan
127 sinh = vectorMapC Sinh
128 cosh = vectorMapC Cosh
129 tanh = vectorMapC Tanh
130 asinh = vectorMapC ASinh
131 acosh = vectorMapC ACosh
132 atanh = vectorMapC ATanh
133 exp = vectorMapC Exp
134 log = vectorMapC Log
135 sqrt = vectorMapC Sqrt
136 (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS))
137 pi = fromList [pi]
138
139-----------------------------------------------------------
140
141instance Floating (Vector (Complex Float)) where
142 sin = vectorMapQ Sin
143 cos = vectorMapQ Cos
144 tan = vectorMapQ Tan
145 asin = vectorMapQ ASin
146 acos = vectorMapQ ACos
147 atan = vectorMapQ ATan
148 sinh = vectorMapQ Sinh
149 cosh = vectorMapQ Cosh
150 tanh = vectorMapQ Tanh
151 asinh = vectorMapQ ASinh
152 acosh = vectorMapQ ACosh
153 atanh = vectorMapQ ATanh
154 exp = vectorMapQ Exp
155 log = vectorMapQ Log
156 sqrt = vectorMapQ Sqrt
157 (**) = adaptScalar (vectorMapValQ PowSV) (vectorZipQ Pow) (flip (vectorMapValQ PowVS))
158 pi = fromList [pi]
159