summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
authorKhudyakov Alexey <alexey.skladnoy@gmail.com>2010-09-29 12:35:11 +0000
committerKhudyakov Alexey <alexey.skladnoy@gmail.com>2010-09-29 12:35:11 +0000
commit49df400d892d4f51cbe724f5677aec70753b0408 (patch)
treea49eaa7f4bb6301c4225aab8ec25718bc4870634 /lib
parenta3d3e0bd63a1c8215d4138195d128201ffa424e8 (diff)
[hlint] Remove redundant brackets and $'s
Diffstat (limited to 'lib')
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs2
-rw-r--r--lib/Data/Packed/Matrix.hs4
-rw-r--r--lib/Data/Packed/Random.hs2
-rw-r--r--lib/Graphics/Plot.hs10
-rw-r--r--lib/Numeric/Chain.hs14
-rw-r--r--lib/Numeric/Container.hs4
-rw-r--r--lib/Numeric/LinearAlgebra/Algorithms.hs5
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Instances.hs2
8 files changed, 21 insertions, 22 deletions
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index c4491fb..29aba51 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -160,7 +160,7 @@ fromRows vs = case compatdim (map dim vs) of
160-- | extracts the rows of a matrix as a list of vectors 160-- | extracts the rows of a matrix as a list of vectors
161toRows :: Element t => Matrix t -> [Vector t] 161toRows :: Element t => Matrix t -> [Vector t]
162toRows m = toRows' 0 where 162toRows m = toRows' 0 where
163 v = flatten $ m 163 v = flatten m
164 r = rows m 164 r = rows m
165 c = cols m 165 c = cols m
166 toRows' k | k == r*c = [] 166 toRows' k | k == r*c = []
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index 2efb08d..de2300a 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -269,7 +269,7 @@ Hilbert matrix of order N:
269-} 269-}
270buildMatrix :: Element a => Int -> Int -> ((Int, Int) -> a) -> Matrix a 270buildMatrix :: Element a => Int -> Int -> ((Int, Int) -> a) -> Matrix a
271buildMatrix rc cc f = 271buildMatrix rc cc f =
272 fromLists $ map (\x -> map f x) 272 fromLists $ map (map f)
273 $ map (\ ri -> map (\ ci -> (ri, ci)) [0 .. (cc - 1)]) [0 .. (rc - 1)] 273 $ map (\ ri -> map (\ ci -> (ri, ci)) [0 .. (cc - 1)]) [0 .. (rc - 1)]
274 274
275----------------------------------------------------- 275-----------------------------------------------------
@@ -283,7 +283,7 @@ fromArray2D m = (r><c) (elems m)
283 283
284-- | rearranges the rows of a matrix according to the order given in a list of integers. 284-- | rearranges the rows of a matrix according to the order given in a list of integers.
285extractRows :: Element t => [Int] -> Matrix t -> Matrix t 285extractRows :: Element t => [Int] -> Matrix t -> Matrix t
286extractRows l m = fromRows $ extract (toRows $ m) l 286extractRows l m = fromRows $ extract (toRows m) l
287 where extract l' is = [l'!!i |i<-is] 287 where extract l' is = [l'!!i |i<-is]
288 288
289{- | creates matrix by repetition of a matrix a given number of rows and columns 289{- | creates matrix by repetition of a matrix a given number of rows and columns
diff --git a/lib/Data/Packed/Random.hs b/lib/Data/Packed/Random.hs
index 14d91ea..4b229f0 100644
--- a/lib/Data/Packed/Random.hs
+++ b/lib/Data/Packed/Random.hs
@@ -63,4 +63,4 @@ meanCov x = (med,cov) where
63 med = konst k r `vXm` x 63 med = konst k r `vXm` x
64 meds = konst 1 r `outer` med 64 meds = konst 1 r `outer` med
65 xc = x `sub` meds 65 xc = x `sub` meds
66 cov = flip scale (trans xc `mXm` xc) (recip (fromIntegral (r-1))) 66 cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc)
diff --git a/lib/Graphics/Plot.hs b/lib/Graphics/Plot.hs
index 32106df..74a2695 100644
--- a/lib/Graphics/Plot.hs
+++ b/lib/Graphics/Plot.hs
@@ -45,7 +45,7 @@ In certain versions you can interactively rotate the graphic using the mouse.
45mesh :: Matrix Double -> IO () 45mesh :: Matrix Double -> IO ()
46mesh m = gnuplotX (command++dat) where 46mesh m = gnuplotX (command++dat) where
47 command = "splot "++datafollows++" matrix with lines\n" 47 command = "splot "++datafollows++" matrix with lines\n"
48 dat = prep $ toLists $ m 48 dat = prep $ toLists m
49 49
50{- | Draws the surface represented by the function f in the desired ranges and number of points, internally using 'mesh'. 50{- | Draws the surface represented by the function f in the desired ranges and number of points, internally using 'mesh'.
51 51
@@ -104,7 +104,7 @@ matrixToPGM m = header ++ unlines (map unwords ll) where
104 maxgray = 255.0 104 maxgray = 255.0
105 maxval = maxElement m 105 maxval = maxElement m
106 minval = minElement m 106 minval = minElement m
107 scale' = if (maxval == minval) 107 scale' = if maxval == minval
108 then 0.0 108 then 0.0
109 else maxgray / (maxval - minval) 109 else maxgray / (maxval - minval)
110 f x = show ( round ( scale' *(x - minval) ) :: Int ) 110 f x = show ( round ( scale' *(x - minval) ) :: Int )
@@ -124,7 +124,7 @@ gnuplotX command = do { _ <- system cmdstr; return()} where
124 124
125datafollows = "\\\"-\\\"" 125datafollows = "\\\"-\\\""
126 126
127prep = (++"e\n\n") . unlines . map (unwords . (map show)) 127prep = (++"e\n\n") . unlines . map (unwords . map show)
128 128
129 129
130gnuplotpdf :: String -> String -> [([[Double]], String)] -> IO () 130gnuplotpdf :: String -> String -> [([[Double]], String)] -> IO ()
@@ -158,7 +158,7 @@ gnuplotpdf title command ds = gnuplot (prelude ++ command ++" "++ draw) >> postp
158 158
159 "\\end{document}" 159 "\\end{document}"
160 160
161 pr = (++"e\n") . unlines . map (unwords . (map show)) 161 pr = (++"e\n") . unlines . map (unwords . map show)
162 162
163 gnuplot cmd = do 163 gnuplot cmd = do
164 writeFile "gnuplotcommand" cmd 164 writeFile "gnuplotcommand" cmd
@@ -172,7 +172,7 @@ gnuplotWin title command ds = gnuplot (prelude ++ command ++" "++ draw) where
172 draw = concat (intersperse ", " (map ("\"-\" "++) defs)) ++ "\n" ++ 172 draw = concat (intersperse ", " (map ("\"-\" "++) defs)) ++ "\n" ++
173 concatMap pr dats 173 concatMap pr dats
174 174
175 pr = (++"e\n") . unlines . map (unwords . (map show)) 175 pr = (++"e\n") . unlines . map (unwords . map show)
176 176
177 prelude = "set title \""++title++"\";" 177 prelude = "set title \""++title++"\";"
178 178
diff --git a/lib/Numeric/Chain.hs b/lib/Numeric/Chain.hs
index 03ca88d..e1ab7da 100644
--- a/lib/Numeric/Chain.hs
+++ b/lib/Numeric/Chain.hs
@@ -98,11 +98,11 @@ minimum_cost :: (Sizes,Cost,Indexes) -> (Int,Int) -> (Sizes,Cost,Indexes)
98minimum_cost sci fu = foldl (smaller_cost fu) sci (fulcrum_order fu) 98minimum_cost sci fu = foldl (smaller_cost fu) sci (fulcrum_order fu)
99 99
100smaller_cost :: (Int,Int) -> (Sizes,Cost,Indexes) -> ((Int,Int),(Int,Int)) -> (Sizes,Cost,Indexes) 100smaller_cost :: (Int,Int) -> (Sizes,Cost,Indexes) -> ((Int,Int),(Int,Int)) -> (Sizes,Cost,Indexes)
101smaller_cost (r,c) (mz,cost,ixes) ix@((lr,lc),(rr,rc)) = let op_cost = (fromJust ((cost A.! lr) A.! lc)) 101smaller_cost (r,c) (mz,cost,ixes) ix@((lr,lc),(rr,rc)) = let op_cost = fromJust ((cost A.! lr) A.! lc)
102 + (fromJust ((cost A.! rr) A.! rc)) 102 + fromJust ((cost A.! rr) A.! rc)
103 + ((fst $ mz A.! (lr-lc+1)) 103 + fst (mz A.! (lr-lc+1))
104 *(snd $ mz A.! lc) 104 * snd (mz A.! lc)
105 *(snd $ mz A.! rr)) 105 * snd (mz A.! rr)
106 cost' = (cost A.! r) A.! c 106 cost' = (cost A.! r) A.! c
107 in case cost' of 107 in case cost' of
108 Nothing -> let cost'' = update cost (r,c) (Just op_cost) 108 Nothing -> let cost'' = update cost (r,c) (Just op_cost)
@@ -118,10 +118,10 @@ smaller_cost (r,c) (mz,cost,ixes) ix@((lr,lc),(rr,rc)) = let op_cost = (fromJust
118fulcrum_order (r,c) = let fs' = zip (repeat r) [1..(c-1)] 118fulcrum_order (r,c) = let fs' = zip (repeat r) [1..(c-1)]
119 in map (partner (r,c)) fs' 119 in map (partner (r,c)) fs'
120 120
121partner (r,c) (a,b) = (((r-b),(c-b)),(a,b)) 121partner (r,c) (a,b) = ((r-b, c-b), (a,b))
122 122
123order 0 = [] 123order 0 = []
124order n = (order (n-1)) ++ (zip (repeat n) [1..n]) 124order n = order (n-1) ++ zip (repeat n) [1..n]
125 125
126chain_paren :: Product a => (Int,Int) -> Indexes -> Matrices a -> Matrix a 126chain_paren :: Product a => (Int,Int) -> Indexes -> Matrices a -> Matrix a
127chain_paren (r,c) ixes ma = let ((lr,lc),(rr,rc)) = fromJust $ (ixes A.! r) A.! c 127chain_paren (r,c) ixes ma = let ((lr,lc),(rr,rc)) = fromJust $ (ixes A.! r) A.! c
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
index 45b33e0..621574e 100644
--- a/lib/Numeric/Container.hs
+++ b/lib/Numeric/Container.hs
@@ -117,10 +117,10 @@ instance Mul Matrix Matrix Matrix where
117 (<>) = mXm 117 (<>) = mXm
118 118
119instance Mul Matrix Vector Vector where 119instance Mul Matrix Vector Vector where
120 (<>) m v = flatten $ m <> (asColumn v) 120 (<>) m v = flatten $ m <> asColumn v
121 121
122instance Mul Vector Matrix Vector where 122instance Mul Vector Matrix Vector where
123 (<>) v m = flatten $ (asRow v) <> m 123 (<>) v m = flatten $ asRow v <> m
124 124
125-------------------------------------------------------- 125--------------------------------------------------------
126 126
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs
index f4f8bca..dd93db2 100644
--- a/lib/Numeric/LinearAlgebra/Algorithms.hs
+++ b/lib/Numeric/LinearAlgebra/Algorithms.hs
@@ -392,7 +392,7 @@ eps = 2.22044604925031e-16
392 392
393-- | 1 + 0.5*peps == 1, 1 + 0.6*peps /= 1 393-- | 1 + 0.5*peps == 1, 1 + 0.6*peps /= 1
394peps :: RealFloat x => x 394peps :: RealFloat x => x
395peps = x where x = 2.0**(fromIntegral $ 1-floatDigits x) 395peps = x where x = 2.0 ** fromIntegral (1 - floatDigits x)
396 396
397 397
398-- | The imaginary unit: @i = 0.0 :+ 1.0@ 398-- | The imaginary unit: @i = 0.0 :+ 1.0@
@@ -553,8 +553,7 @@ epslist = [ (fromIntegral k, golubeps k k) | k <- [1..]]
553geps delta = head [ k | (k,g) <- epslist, g<delta] 553geps delta = head [ k | (k,g) <- epslist, g<delta]
554 554
555expGolub m = iterate msq f !! j 555expGolub m = iterate msq f !! j
556 where j = max 0 $ floor $ log2 $ pnorm Infinity m 556 where j = max 0 $ floor $ logBase 2 $ pnorm Infinity m
557 log2 x = log x / log 2
558 a = m */ fromIntegral ((2::Int)^j) 557 a = m */ fromIntegral ((2::Int)^j)
559 q = geps eps -- 7 steps 558 q = geps eps -- 7 steps
560 eye = ident (rows m) 559 eye = ident (rows m)
diff --git a/lib/Numeric/LinearAlgebra/Tests/Instances.hs b/lib/Numeric/LinearAlgebra/Tests/Instances.hs
index 771739a..6dd9cfe 100644
--- a/lib/Numeric/LinearAlgebra/Tests/Instances.hs
+++ b/lib/Numeric/LinearAlgebra/Tests/Instances.hs
@@ -84,7 +84,7 @@ instance (Element a, Arbitrary a) => Arbitrary (Matrix a) where
84 84
85#if MIN_VERSION_QuickCheck(2,0,0) 85#if MIN_VERSION_QuickCheck(2,0,0)
86 -- shrink any one of the components 86 -- shrink any one of the components
87 shrink a = map ((rows a) >< (cols a)) 87 shrink a = map (rows a >< cols a)
88 . shrinkListElementwise 88 . shrinkListElementwise
89 . concat . toLists 89 . concat . toLists
90 $ a 90 $ a