summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--examples/benchmarks.hs19
-rw-r--r--hmatrix.cabal2
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs85
-rw-r--r--lib/Data/Packed/Internal/auxi.c20
-rw-r--r--lib/Data/Packed/Internal/auxi.h3
5 files changed, 54 insertions, 75 deletions
diff --git a/examples/benchmarks.hs b/examples/benchmarks.hs
index 7ba15aa..6490b25 100644
--- a/examples/benchmarks.hs
+++ b/examples/benchmarks.hs
@@ -18,7 +18,9 @@ time act = do
18 18
19-------------------------------------------------------------------------------- 19--------------------------------------------------------------------------------
20 20
21main = sequence_ [bench1,bench2,bench3,bench4,bench5 1000000 3] 21main = sequence_ [bench1,bench2,bench3,bench4,
22 bench5 1000000 3,
23 bench5 100000 50]
22 24
23w :: Vector Double 25w :: Vector Double
24w = constant 1 5000000 26w = constant 1 5000000
@@ -131,19 +133,18 @@ bench4 = do
131-------------------------------------------------------------------------------- 133--------------------------------------------------------------------------------
132 134
133op1 a b = a <> trans b 135op1 a b = a <> trans b
134 136op2 a b = a + trans b
135op2 a b = a + trans b
136 137
137timep = time . print . vectorMax . flatten 138timep = time . print . vectorMax . flatten
138 139
139bench5 n d = do 140bench5 n d = do
140 putStrLn "-------------------------------------------------------" 141 putStrLn "-------------------------------------------------------"
141 putStrLn "transpose in multiply"
142 let ms = replicate n ((ident d :: Matrix Double))
143 let mz = replicate n (diag (constant (0::Double) d))
144 timep $ foldl1' (<>) ms
145 timep $ foldl1' op1 ms
146 putStrLn "-------------------------------------------------------"
147 putStrLn "transpose in add" 142 putStrLn "transpose in add"
143 let ms = replicate n ((ident d :: Matrix Double))
148 timep $ foldl1' (+) ms 144 timep $ foldl1' (+) ms
149 timep $ foldl1' op2 ms 145 timep $ foldl1' op2 ms
146 putStrLn "-------------------------------------------------------"
147 putStrLn "transpose in multiply"
148
149 timep $ foldl1' (<>) ms
150 timep $ foldl1' op1 ms
diff --git a/hmatrix.cabal b/hmatrix.cabal
index 3307870..638358b 100644
--- a/hmatrix.cabal
+++ b/hmatrix.cabal
@@ -13,7 +13,7 @@ Description: A purely functional interface to basic linear algebra comput
13 . 13 .
14 More information: <http://www.hmatrix.googlepages.com> 14 More information: <http://www.hmatrix.googlepages.com>
15Category: Math 15Category: Math
16tested-with: GHC ==6.10.0 16tested-with: GHC ==6.10.1
17 17
18cabal-version: >=1.2 18cabal-version: >=1.2
19build-type: Simple 19build-type: Simple
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index 477b453..a32a782 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -1,5 +1,5 @@
1{-# OPTIONS_GHC -fglasgow-exts #-} 1{-# OPTIONS_GHC -fglasgow-exts #-}
2{-# LANGUAGE CPP #-} 2{-# LANGUAGE CPP, BangPatterns #-}
3----------------------------------------------------------------------------- 3-----------------------------------------------------------------------------
4-- | 4-- |
5-- Module : Data.Packed.Internal.Matrix 5-- Module : Data.Packed.Internal.Matrix
@@ -71,6 +71,12 @@ data Matrix t = MC { rows :: {-# UNPACK #-} !Int
71-- MC: preferred by C, fdat may require a transposition 71-- MC: preferred by C, fdat may require a transposition
72-- MF: preferred by LAPACK, cdat may require a transposition 72-- MF: preferred by LAPACK, cdat may require a transposition
73 73
74xdat MC {cdat = d } = d
75xdat MF {fdat = d } = d
76
77orderOf MF{} = ColumnMajor
78orderOf MC{} = RowMajor
79
74-- | Matrix transpose. 80-- | Matrix transpose.
75trans :: Matrix t -> Matrix t 81trans :: Matrix t -> Matrix t
76trans MC {rows = r, cols = c, cdat = d } = MF {rows = c, cols = r, fdat = d } 82trans MC {rows = r, cols = c, cdat = d } = MF {rows = c, cols = r, fdat = d }
@@ -84,16 +90,10 @@ fmat MC {rows = r, cols = c, cdat = d } = MF {rows = r, cols = c, fdat = transda
84 90
85mat = withMatrix 91mat = withMatrix
86 92
87withMatrix MC {rows = r, cols = c, cdat = d } f = 93withMatrix a f =
88 withForeignPtr (fptr d) $ \p -> do 94 withForeignPtr (fptr (xdat a)) $ \p -> do
89 let m g = do
90 g (fi r) (fi c) p
91 f m
92
93withMatrix MF {rows = r, cols = c, fdat = d } f =
94 withForeignPtr (fptr d) $ \p -> do
95 let m g = do 95 let m g = do
96 g (fi r) (fi c) p 96 g (fi (rows a)) (fi (cols a)) p
97 f m 97 f m
98 98
99{- | Creates a vector by concatenation of rows 99{- | Creates a vector by concatenation of rows
@@ -156,6 +156,11 @@ MF {rows = r, cols = c, fdat = v} @@> (i,j)
156 | otherwise = v `at` (j*r+i) 156 | otherwise = v `at` (j*r+i)
157{-# INLINE (@@>) #-} 157{-# INLINE (@@>) #-}
158 158
159-- | Unsafe matrix access without range checking
160atM' MC {cols = c, cdat = v} i j = v `at'` (i*c+j)
161atM' MF {rows = r, fdat = v} i j = v `at'` (j*r+i)
162{-# INLINE atM' #-}
163
159------------------------------------------------------------------ 164------------------------------------------------------------------
160 165
161matrixFromVector RowMajor c v = MC { rows = r, cols = c, cdat = v } 166matrixFromVector RowMajor c v = MC { rows = r, cols = c, cdat = v }
@@ -204,56 +209,52 @@ liftMatrix2 f m1 m2
204compat :: Matrix a -> Matrix b -> Bool 209compat :: Matrix a -> Matrix b -> Bool
205compat m1 m2 = rows m1 == rows m2 && cols m1 == cols m2 210compat m1 m2 = rows m1 == rows m2 && cols m1 == cols m2
206 211
207---------------------------------------------------------------- 212------------------------------------------------------------------
208 213
209-- | Optimized matrix computations are provided for elements in the Element class. 214-- | Auxiliary class.
210class (Storable a, Floating a) => Element a where 215class (Storable a, Floating a) => Element a where
211 transdata :: Int -> Vector a -> Int -> Vector a
212 subMatrixD :: (Int,Int) -- ^ (r0,c0) starting position 216 subMatrixD :: (Int,Int) -- ^ (r0,c0) starting position
213 -> (Int,Int) -- ^ (rt,ct) dimensions of submatrix 217 -> (Int,Int) -- ^ (rt,ct) dimensions of submatrix
214 -> Matrix a -> Matrix a 218 -> Matrix a -> Matrix a
219 transdata :: Int -> Vector a -> Int -> Vector a
215 220
216instance Element Double where 221instance Element Double where
217 transdata = transdataR
218 subMatrixD = subMatrixR 222 subMatrixD = subMatrixR
223 transdata = transdata'
219 224
220instance Element (Complex Double) where 225instance Element (Complex Double) where
221 transdata = transdataC
222 subMatrixD = subMatrixC 226 subMatrixD = subMatrixC
223 227 transdata = transdata'
224------------------------------------------------------------------
225
226(>|<) :: (Element a) => Int -> Int -> [a] -> Matrix a
227r >|< c = f where
228 f l | dim v == r*c = matrixFromVector ColumnMajor c v
229 | otherwise = error $ "inconsistent list size = "
230 ++show (dim v) ++" in ("++show r++"><"++show c++")"
231 where v = fromList l
232 228
233------------------------------------------------------------------- 229-------------------------------------------------------------------
234 230
235transdataR :: Int -> Vector Double -> Int -> Vector Double 231transdata' :: Storable a => Int -> Vector a -> Int -> Vector a
236transdataR = transdataAux ctransR 232transdata' c1 v c2 =
237
238transdataC :: Int -> Vector (Complex Double) -> Int -> Vector (Complex Double)
239transdataC = transdataAux ctransC
240
241transdataAux fun c1 d c2 =
242 if noneed 233 if noneed
243 then d 234 then v
244 else unsafePerformIO $ do 235 else unsafePerformIO $ do
245 v <- createVector (dim d) 236 w <- createVector (r2*c2)
246 withForeignPtr (fptr d) $ \pd -> 237 let p = unsafeForeignPtrToPtr (fptr v)
247 withForeignPtr (fptr v) $ \pv -> 238 q = unsafeForeignPtrToPtr (fptr w)
248 fun (fi r1) (fi c1) pd (fi r2) (fi c2) pv // check "transdataAux" 239 go (-1) _ = return ()
249 -- putStrLn $ "---> transdataAux" ++ show (toList d) ++ show (toList v) 240 go !i (-1) = go (i-1) (c1-1)
250 return v 241 go !i !j = do x <- peekElemOff p (i*c1+j)
251 where r1 = dim d `div` c1 242 pokeElemOff q (j*c2+i) x
252 r2 = dim d `div` c2 243 go i (j-1)
244 go (r1-1) (c1-1)
245 touchForeignPtr (fptr w)
246 return w
247 where r1 = dim v `div` c1
248 r2 = dim v `div` c2
253 noneed = r1 == 1 || c1 == 1 249 noneed = r1 == 1 || c1 == 1
254 250
255foreign import ccall "auxi.h transR" ctransR :: TMM 251
256foreign import ccall "auxi.h transC" ctransC :: TCMCM 252-- {-# SPECIALIZE transdata' :: Int -> Vector Double -> Int -> Vector Double #-}
253-- {-# SPECIALIZE transdata' :: Int -> Vector (Complex Double) -> Int -> Vector (Complex Double) #-}
254
255-- I don't know how to specialize...
256-- The above pragmas only seem to work on top level defs
257-- Fortunately everything seems to work using the above class
257 258
258---------------------------------------------------------------------- 259----------------------------------------------------------------------
259 260
diff --git a/lib/Data/Packed/Internal/auxi.c b/lib/Data/Packed/Internal/auxi.c
index 48b05e8..562c804 100644
--- a/lib/Data/Packed/Internal/auxi.c
+++ b/lib/Data/Packed/Internal/auxi.c
@@ -51,26 +51,6 @@
51#define MEM 2002 51#define MEM 2002
52#define BAD_FILE 2003 52#define BAD_FILE 2003
53 53
54int transR(KRMAT(x),RMAT(t)) {
55 REQUIRES(xr==tc && xc==tr,BAD_SIZE);
56 DEBUGMSG("transR");
57 KDMVIEW(x);
58 DMVIEW(t);
59 int res = gsl_matrix_transpose_memcpy(M(t),M(x));
60 CHECK(res,res);
61 OK
62}
63
64int transC(KCMAT(x),CMAT(t)) {
65 REQUIRES(xr==tc && xc==tr,BAD_SIZE);
66 DEBUGMSG("transC");
67 KCMVIEW(x);
68 CMVIEW(t);
69 int res = gsl_matrix_complex_transpose_memcpy(M(t),M(x));
70 CHECK(res,res);
71 OK
72}
73
74 54
75int submatrixR(int r1, int r2, int c1, int c2, KRMAT(x),RMAT(r)) { 55int submatrixR(int r1, int r2, int c1, int c2, KRMAT(x),RMAT(r)) {
76 REQUIRES(0<=r1 && r1<=r2 && r2<xr && 0<=c1 && c1<=c2 && c2<xc && 56 REQUIRES(0<=r1 && r1<=r2 && r2<xr && 0<=c1 && c1<=c2 && c2<xc &&
diff --git a/lib/Data/Packed/Internal/auxi.h b/lib/Data/Packed/Internal/auxi.h
index 4698696..e5370b4 100644
--- a/lib/Data/Packed/Internal/auxi.h
+++ b/lib/Data/Packed/Internal/auxi.h
@@ -10,9 +10,6 @@
10#define KCVEC(A) int A##n, const gsl_complex*A##p 10#define KCVEC(A) int A##n, const gsl_complex*A##p
11#define KCMAT(A) int A##r, int A##c, const gsl_complex* A##p 11#define KCMAT(A) int A##r, int A##c, const gsl_complex* A##p
12 12
13int transR(KRMAT(x),RMAT(t));
14int transC(KCMAT(x),CMAT(t));
15
16int submatrixR(int r1, int r2, int c1, int c2, KRMAT(x),RMAT(r)); 13int submatrixR(int r1, int r2, int c1, int c2, KRMAT(x),RMAT(r));
17 14
18const char * gsl_strerror (const int gsl_errno); 15const char * gsl_strerror (const int gsl_errno);