diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
commit | 1925c123d7d8184a1d2ddc0a413e0fd2776e1083 (patch) | |
tree | fad79f909d9c3be53d68e6ebd67202650536d387 /packages/hmatrix/src/Numeric/Vector.hs | |
parent | eb3f702d065a4a967bb754977233e6eec408fd1f (diff) |
empty hmatrix-base
Diffstat (limited to 'packages/hmatrix/src/Numeric/Vector.hs')
-rw-r--r-- | packages/hmatrix/src/Numeric/Vector.hs | 158 |
1 files changed, 158 insertions, 0 deletions
diff --git a/packages/hmatrix/src/Numeric/Vector.hs b/packages/hmatrix/src/Numeric/Vector.hs new file mode 100644 index 0000000..3f480a0 --- /dev/null +++ b/packages/hmatrix/src/Numeric/Vector.hs | |||
@@ -0,0 +1,158 @@ | |||
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 | |||
21 | module Numeric.Vector () where | ||
22 | |||
23 | import Numeric.GSL.Vector | ||
24 | import Numeric.Container | ||
25 | |||
26 | ------------------------------------------------------------------- | ||
27 | |||
28 | adaptScalar f1 f2 f3 x y | ||
29 | | dim x == 1 = f1 (x@>0) y | ||
30 | | dim y == 1 = f3 x (y@>0) | ||
31 | | otherwise = f2 x y | ||
32 | |||
33 | ------------------------------------------------------------------ | ||
34 | |||
35 | instance Num (Vector Float) where | ||
36 | (+) = adaptScalar addConstant add (flip addConstant) | ||
37 | negate = scale (-1) | ||
38 | (*) = adaptScalar scale mul (flip scale) | ||
39 | signum = vectorMapF Sign | ||
40 | abs = vectorMapF Abs | ||
41 | fromInteger = fromList . return . fromInteger | ||
42 | |||
43 | instance Num (Vector Double) where | ||
44 | (+) = adaptScalar addConstant add (flip addConstant) | ||
45 | negate = scale (-1) | ||
46 | (*) = adaptScalar scale mul (flip scale) | ||
47 | signum = vectorMapR Sign | ||
48 | abs = vectorMapR Abs | ||
49 | fromInteger = fromList . return . fromInteger | ||
50 | |||
51 | instance Num (Vector (Complex Double)) where | ||
52 | (+) = adaptScalar addConstant add (flip addConstant) | ||
53 | negate = scale (-1) | ||
54 | (*) = adaptScalar scale mul (flip scale) | ||
55 | signum = vectorMapC Sign | ||
56 | abs = vectorMapC Abs | ||
57 | fromInteger = fromList . return . fromInteger | ||
58 | |||
59 | instance Num (Vector (Complex Float)) where | ||
60 | (+) = adaptScalar addConstant add (flip addConstant) | ||
61 | negate = scale (-1) | ||
62 | (*) = adaptScalar scale mul (flip scale) | ||
63 | signum = vectorMapQ Sign | ||
64 | abs = vectorMapQ Abs | ||
65 | fromInteger = fromList . return . fromInteger | ||
66 | |||
67 | --------------------------------------------------- | ||
68 | |||
69 | instance (Container Vector a, Num (Vector a)) => Fractional (Vector a) where | ||
70 | fromRational n = fromList [fromRational n] | ||
71 | (/) = adaptScalar f divide g where | ||
72 | r `f` v = scaleRecip r v | ||
73 | v `g` r = scale (recip r) v | ||
74 | |||
75 | ------------------------------------------------------- | ||
76 | |||
77 | instance Floating (Vector Float) where | ||
78 | sin = vectorMapF Sin | ||
79 | cos = vectorMapF Cos | ||
80 | tan = vectorMapF Tan | ||
81 | asin = vectorMapF ASin | ||
82 | acos = vectorMapF ACos | ||
83 | atan = vectorMapF ATan | ||
84 | sinh = vectorMapF Sinh | ||
85 | cosh = vectorMapF Cosh | ||
86 | tanh = vectorMapF Tanh | ||
87 | asinh = vectorMapF ASinh | ||
88 | acosh = vectorMapF ACosh | ||
89 | atanh = vectorMapF ATanh | ||
90 | exp = vectorMapF Exp | ||
91 | log = vectorMapF Log | ||
92 | sqrt = vectorMapF Sqrt | ||
93 | (**) = adaptScalar (vectorMapValF PowSV) (vectorZipF Pow) (flip (vectorMapValF PowVS)) | ||
94 | pi = fromList [pi] | ||
95 | |||
96 | ------------------------------------------------------------- | ||
97 | |||
98 | instance Floating (Vector Double) where | ||
99 | sin = vectorMapR Sin | ||
100 | cos = vectorMapR Cos | ||
101 | tan = vectorMapR Tan | ||
102 | asin = vectorMapR ASin | ||
103 | acos = vectorMapR ACos | ||
104 | atan = vectorMapR ATan | ||
105 | sinh = vectorMapR Sinh | ||
106 | cosh = vectorMapR Cosh | ||
107 | tanh = vectorMapR Tanh | ||
108 | asinh = vectorMapR ASinh | ||
109 | acosh = vectorMapR ACosh | ||
110 | atanh = vectorMapR ATanh | ||
111 | exp = vectorMapR Exp | ||
112 | log = vectorMapR Log | ||
113 | sqrt = vectorMapR Sqrt | ||
114 | (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS)) | ||
115 | pi = fromList [pi] | ||
116 | |||
117 | ------------------------------------------------------------- | ||
118 | |||
119 | instance Floating (Vector (Complex Double)) where | ||
120 | sin = vectorMapC Sin | ||
121 | cos = vectorMapC Cos | ||
122 | tan = vectorMapC Tan | ||
123 | asin = vectorMapC ASin | ||
124 | acos = vectorMapC ACos | ||
125 | atan = vectorMapC ATan | ||
126 | sinh = vectorMapC Sinh | ||
127 | cosh = vectorMapC Cosh | ||
128 | tanh = vectorMapC Tanh | ||
129 | asinh = vectorMapC ASinh | ||
130 | acosh = vectorMapC ACosh | ||
131 | atanh = vectorMapC ATanh | ||
132 | exp = vectorMapC Exp | ||
133 | log = vectorMapC Log | ||
134 | sqrt = vectorMapC Sqrt | ||
135 | (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS)) | ||
136 | pi = fromList [pi] | ||
137 | |||
138 | ----------------------------------------------------------- | ||
139 | |||
140 | instance Floating (Vector (Complex Float)) where | ||
141 | sin = vectorMapQ Sin | ||
142 | cos = vectorMapQ Cos | ||
143 | tan = vectorMapQ Tan | ||
144 | asin = vectorMapQ ASin | ||
145 | acos = vectorMapQ ACos | ||
146 | atan = vectorMapQ ATan | ||
147 | sinh = vectorMapQ Sinh | ||
148 | cosh = vectorMapQ Cosh | ||
149 | tanh = vectorMapQ Tanh | ||
150 | asinh = vectorMapQ ASinh | ||
151 | acosh = vectorMapQ ACosh | ||
152 | atanh = vectorMapQ ATanh | ||
153 | exp = vectorMapQ Exp | ||
154 | log = vectorMapQ Log | ||
155 | sqrt = vectorMapQ Sqrt | ||
156 | (**) = adaptScalar (vectorMapValQ PowSV) (vectorZipQ Pow) (flip (vectorMapValQ PowVS)) | ||
157 | pi = fromList [pi] | ||
158 | |||