summaryrefslogtreecommitdiff
path: root/lib/Data
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-11-23 13:25:42 +0000
committerAlberto Ruiz <aruiz@um.es>2007-11-23 13:25:42 +0000
commit30fdf02aff2ac1c4da2bb9292fc08cc8330580d0 (patch)
tree82b062214626c20922959c82581decb3df2ba5ec /lib/Data
parent48139eb50c9052406839ee8375e378374e973207 (diff)
removed many -Wall warnings
Diffstat (limited to 'lib/Data')
-rw-r--r--lib/Data/Packed/Internal/Common.hs3
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs19
-rw-r--r--lib/Data/Packed/Internal/Vector.hs7
-rw-r--r--lib/Data/Packed/Matrix.hs22
-rw-r--r--lib/Data/Packed/Vector.hs1
5 files changed, 24 insertions, 28 deletions
diff --git a/lib/Data/Packed/Internal/Common.hs b/lib/Data/Packed/Internal/Common.hs
index dc1c2b4..7305d8c 100644
--- a/lib/Data/Packed/Internal/Common.hs
+++ b/lib/Data/Packed/Internal/Common.hs
@@ -20,9 +20,6 @@ import Foreign
20import Complex 20import Complex
21import Control.Monad(when) 21import Control.Monad(when)
22import Debug.Trace 22import Debug.Trace
23import Data.List(transpose,intersperse)
24import Data.Typeable
25import Data.Maybe(fromJust)
26import Foreign.C.String(peekCString) 23import Foreign.C.String(peekCString)
27import Foreign.C.Types 24import Foreign.C.Types
28 25
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index 0519603..4cc94b7 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -22,7 +22,6 @@ import Data.Packed.Internal.Vector
22import Foreign hiding (xor) 22import Foreign hiding (xor)
23import Complex 23import Complex
24import Control.Monad(when) 24import Control.Monad(when)
25import Data.Maybe(fromJust)
26import Foreign.C.String 25import Foreign.C.String
27import Foreign.C.Types 26import Foreign.C.Types
28import Data.List(transpose) 27import Data.List(transpose)
@@ -83,14 +82,14 @@ mat = withMatrix
83 82
84withMatrix MC {rows = r, cols = c, cdat = d } f = 83withMatrix MC {rows = r, cols = c, cdat = d } f =
85 withForeignPtr (fptr d) $ \p -> do 84 withForeignPtr (fptr d) $ \p -> do
86 let m f = do 85 let m g = do
87 f r c p 86 g r c p
88 f m 87 f m
89 88
90withMatrix MF {rows = r, cols = c, fdat = d } f = 89withMatrix MF {rows = r, cols = c, fdat = d } f =
91 withForeignPtr (fptr d) $ \p -> do 90 withForeignPtr (fptr d) $ \p -> do
92 let m f = do 91 let m g = do
93 f r c p 92 g r c p
94 f m 93 f m
95 94
96{- | Creates a vector by concatenation of rows 95{- | Creates a vector by concatenation of rows
@@ -262,8 +261,8 @@ foreign import ccall safe "auxi.h transC"
262 261
263------------------------------------------------------------------ 262------------------------------------------------------------------
264 263
265gmatC MF {rows = r, cols = c, fdat = d} p f = f 1 c r p 264gmatC MF { rows = r, cols = c } p f = f 1 c r p
266gmatC MC {rows = r, cols = c, cdat = d} p f = f 0 r c p 265gmatC MC { rows = r, cols = c } p f = f 0 r c p
267 266
268dtt MC { cdat = d } = d 267dtt MC { cdat = d } = d
269dtt MF { fdat = d } = d 268dtt MF { fdat = d } = d
@@ -273,8 +272,8 @@ multiplyAux fun a b = unsafePerformIO $ do
273 show (rows a,cols a) ++ " x " ++ show (rows b, cols b) 272 show (rows a,cols a) ++ " x " ++ show (rows b, cols b)
274 r <- createMatrix RowMajor (rows a) (cols b) 273 r <- createMatrix RowMajor (rows a) (cols b)
275 withForeignPtr (fptr (dtt a)) $ \pa -> withForeignPtr (fptr (dtt b)) $ \pb -> 274 withForeignPtr (fptr (dtt a)) $ \pa -> withForeignPtr (fptr (dtt b)) $ \pb ->
276 withMatrix r $ \r -> 275 withMatrix r $ \r' ->
277 fun // gmatC a pa // gmatC b pb // r // check "multiplyAux" 276 fun // gmatC a pa // gmatC b pb // r' // check "multiplyAux"
278 return r 277 return r
279 278
280multiplyR = multiplyAux cmultiplyR 279multiplyR = multiplyAux cmultiplyR
@@ -421,7 +420,7 @@ diagG v = matrixFromVector RowMajor c $ fromList $ [ l!!(i-1) * delta k i | k <-
421 | otherwise = 0 420 | otherwise = 0
422-} 421-}
423 422
424transdataG c1 d c2 = fromList . concat . transpose . partit c1 . toList $ d 423transdataG c1 d _ = fromList . concat . transpose . partit c1 . toList $ d
425 424
426dotL a b = sum (zipWith (*) a b) 425dotL a b = sum (zipWith (*) a b)
427 426
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs
index 7eee5fe..ac6588b 100644
--- a/lib/Data/Packed/Internal/Vector.hs
+++ b/lib/Data/Packed/Internal/Vector.hs
@@ -20,7 +20,6 @@ import Data.Packed.Internal.Common
20import Foreign 20import Foreign
21import Complex 21import Complex
22import Control.Monad(when) 22import Control.Monad(when)
23import Data.List(transpose)
24 23
25-- | A one-dimensional array of objects stored in a contiguous memory block. 24-- | A one-dimensional array of objects stored in a contiguous memory block.
26data Vector t = V { dim :: Int -- ^ number of elements 25data Vector t = V { dim :: Int -- ^ number of elements
@@ -39,8 +38,8 @@ type Vc t s = Int -> Ptr t -> s
39vec = withVector 38vec = withVector
40 39
41withVector (V n fp) f = withForeignPtr fp $ \p -> do 40withVector (V n fp) f = withForeignPtr fp $ \p -> do
42 let v f = do 41 let v g = do
43 f n p 42 g n p
44 f v 43 f v
45 44
46-- | allocates memory for a new vector 45-- | allocates memory for a new vector
@@ -132,7 +131,7 @@ join as = unsafePerformIO $ do
132 joiner as tot ptr 131 joiner as tot ptr
133 return r 132 return r
134 where joiner [] _ _ = return () 133 where joiner [] _ _ = return ()
135 joiner (r@V {dim = n, fptr = b} : cs) _ p = do 134 joiner (V {dim = n, fptr = b} : cs) _ p = do
136 withForeignPtr b $ \pb -> copyArray p pb n 135 withForeignPtr b $ \pb -> copyArray p pb n
137 joiner cs 0 (advancePtr p n) 136 joiner cs 0 (advancePtr p n)
138 137
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index 7b6bf29..62d28b1 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -33,10 +33,7 @@ module Data.Packed.Matrix (
33) where 33) where
34 34
35import Data.Packed.Internal 35import Data.Packed.Internal
36import Foreign(Storable)
37import Complex
38import Data.Packed.Vector 36import Data.Packed.Vector
39import Numeric(showGFloat)
40import Data.List(transpose,intersperse) 37import Data.List(transpose,intersperse)
41import Data.Array 38import Data.Array
42 39
@@ -89,8 +86,8 @@ diagRect s r c
89 | dim s < min r c = error "diagRect" 86 | dim s < min r c = error "diagRect"
90 | r == c = diag s 87 | r == c = diag s
91 | r < c = trans $ diagRect s c r 88 | r < c = trans $ diagRect s c r
92 | r > c = joinVert [diag s , zeros (r-c,c)] 89 | otherwise = joinVert [diag s , zeros (r-c,c)]
93 where zeros (r,c) = reshape c $ constantD 0 (r*c) 90 where zeros (r',c') = reshape c' $ constantD 0 (r'*c')
94 91
95-- | extracts the diagonal from a rectangular matrix 92-- | extracts the diagonal from a rectangular matrix
96takeDiag :: (Element t) => Matrix t -> Vector t 93takeDiag :: (Element t) => Matrix t -> Vector t
@@ -123,16 +120,16 @@ r >< c = f where
123 120
124-- | Creates a matrix with the first n rows of another matrix 121-- | Creates a matrix with the first n rows of another matrix
125takeRows :: Element t => Int -> Matrix t -> Matrix t 122takeRows :: Element t => Int -> Matrix t -> Matrix t
126takeRows n mat = subMatrix (0,0) (n, cols mat) mat 123takeRows n mt = subMatrix (0,0) (n, cols mt) mt
127-- | Creates a copy of a matrix without the first n rows 124-- | Creates a copy of a matrix without the first n rows
128dropRows :: Element t => Int -> Matrix t -> Matrix t 125dropRows :: Element t => Int -> Matrix t -> Matrix t
129dropRows n mat = subMatrix (n,0) (rows mat - n, cols mat) mat 126dropRows n mt = subMatrix (n,0) (rows mt - n, cols mt) mt
130-- |Creates a matrix with the first n columns of another matrix 127-- |Creates a matrix with the first n columns of another matrix
131takeColumns :: Element t => Int -> Matrix t -> Matrix t 128takeColumns :: Element t => Int -> Matrix t -> Matrix t
132takeColumns n mat = subMatrix (0,0) (rows mat, n) mat 129takeColumns n mt = subMatrix (0,0) (rows mt, n) mt
133-- | Creates a copy of a matrix without the first n columns 130-- | Creates a copy of a matrix without the first n columns
134dropColumns :: Element t => Int -> Matrix t -> Matrix t 131dropColumns :: Element t => Int -> Matrix t -> Matrix t
135dropColumns n mat = subMatrix (0,n) (rows mat, cols mat - n) mat 132dropColumns n mt = subMatrix (0,n) (rows mt, cols mt - n) mt
136 133
137---------------------------------------------------------------- 134----------------------------------------------------------------
138 135
@@ -164,6 +161,7 @@ fromArray2D m = (r><c) (elems m)
164 c = c1-c0+1 161 c = c1-c0+1
165 162
166------------------------------------------------------ 163------------------------------------------------------
164{-
167-- shows a Double with n digits after the decimal point 165-- shows a Double with n digits after the decimal point
168shf :: (RealFloat a) => Int -> a -> String 166shf :: (RealFloat a) => Int -> a -> String
169shf dec n | abs n < 1e-10 = "0." 167shf dec n | abs n < 1e-10 = "0."
@@ -177,6 +175,8 @@ shfc n z@ (a:+b)
177 | b > 0 = shf n a ++"+"++shf n b ++"i" 175 | b > 0 = shf n a ++"+"++shf n b ++"i"
178 | otherwise = shf n a ++shf n b ++"i" 176 | otherwise = shf n a ++shf n b ++"i"
179 177
178-}
179
180dsp' :: String -> [[String]] -> String 180dsp' :: String -> [[String]] -> String
181dsp' sep as = unlines . map unwords' $ transpose mtp where 181dsp' sep as = unlines . map unwords' $ transpose mtp where
182 mt = transpose as 182 mt = transpose as
@@ -196,6 +196,7 @@ this function the user can easily define any desired display function:
196format :: (Element t) => String -> (t -> String) -> Matrix t -> String 196format :: (Element t) => String -> (t -> String) -> Matrix t -> String
197format sep f m = dsp' sep . map (map f) . toLists $ m 197format sep f m = dsp' sep . map (map f) . toLists $ m
198 198
199{-
199disp m f = putStrLn $ "matrix ("++show (rows m) ++"x"++ show (cols m) ++")\n"++format " | " f m 200disp m f = putStrLn $ "matrix ("++show (rows m) ++"x"++ show (cols m) ++")\n"++format " | " f m
200 201
201dispR :: Int -> Matrix Double -> IO () 202dispR :: Int -> Matrix Double -> IO ()
@@ -203,6 +204,7 @@ dispR d m = disp m (shf d)
203 204
204dispC :: Int -> Matrix (Complex Double) -> IO () 205dispC :: Int -> Matrix (Complex Double) -> IO ()
205dispC d m = disp m (shfc d) 206dispC d m = disp m (shfc d)
207-}
206 208
207-- | creates a matrix from a table of numbers. 209-- | creates a matrix from a table of numbers.
208readMatrix :: String -> Matrix Double 210readMatrix :: String -> Matrix Double
@@ -211,7 +213,7 @@ readMatrix = fromLists . map (map read). map words . filter (not.null) . lines
211-- | rearranges the rows of a matrix according to the order given in a list of integers. 213-- | rearranges the rows of a matrix according to the order given in a list of integers.
212extractRows :: Element t => [Int] -> Matrix t -> Matrix t 214extractRows :: Element t => [Int] -> Matrix t -> Matrix t
213extractRows l m = fromRows $ extract (toRows $ m) l 215extractRows l m = fromRows $ extract (toRows $ m) l
214 where extract l is = [l!!i |i<-is] 216 where extract l' is = [l'!!i |i<-is]
215 217
216{- | creates matrix by repetition of a matrix a given number of rows and columns 218{- | creates matrix by repetition of a matrix a given number of rows and columns
217 219
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index 60fa7c1..6415c5c 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -23,7 +23,6 @@ module Data.Packed.Vector (
23) where 23) where
24 24
25import Data.Packed.Internal 25import Data.Packed.Internal
26import Complex
27import Numeric.GSL.Vector 26import Numeric.GSL.Vector
28 27
29{- | Creates a real vector containing a range of values: 28{- | Creates a real vector containing a range of values: