summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2010-09-23 09:49:04 +0000
committerAlberto Ruiz <aruiz@um.es>2010-09-23 09:49:04 +0000
commit3cfce69bf3cb7d7f7976abb454b64f6fa3a32c97 (patch)
tree6c8d4b0ccbfc2eb289d9112c9106a53af58c6820
parent778e63dcc2b348914a4f6975f5328ff7fd25638a (diff)
minor doc fix, clean Plot
-rw-r--r--examples/parallel.hs8
-rw-r--r--lib/Data/Packed.hs4
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs26
-rw-r--r--lib/Data/Packed/Matrix.hs7
-rw-r--r--lib/Data/Packed/Vector.hs2
-rw-r--r--lib/Graphics/Plot.hs84
-rw-r--r--lib/Numeric/Container.hs8
-rw-r--r--lib/Numeric/LinearAlgebra/Algorithms.hs5
8 files changed, 61 insertions, 83 deletions
diff --git a/examples/parallel.hs b/examples/parallel.hs
index 435e367..c82114f 100644
--- a/examples/parallel.hs
+++ b/examples/parallel.hs
@@ -15,10 +15,10 @@ parMul p x y = fromBlocks [ inParallel ( map (x <>) ys ) ]
15main = do 15main = do
16 n <- (read . head) `fmap` getArgs 16 n <- (read . head) `fmap` getArgs
17 let m = ident n :: Matrix Double 17 let m = ident n :: Matrix Double
18 time $ print $ vectorMax $ takeDiag $ m <> m 18 time $ print $ maxElement $ takeDiag $ m <> m
19 time $ print $ vectorMax $ takeDiag $ parMul 2 m m 19 time $ print $ maxElement $ takeDiag $ parMul 2 m m
20 time $ print $ vectorMax $ takeDiag $ parMul 4 m m 20 time $ print $ maxElement $ takeDiag $ parMul 4 m m
21 time $ print $ vectorMax $ takeDiag $ parMul 8 m m 21 time $ print $ maxElement $ takeDiag $ parMul 8 m m
22 22
23time act = do 23time act = do
24 t0 <- getClockTime 24 t0 <- getClockTime
diff --git a/lib/Data/Packed.hs b/lib/Data/Packed.hs
index bfc2d8b..b8bec8a 100644
--- a/lib/Data/Packed.hs
+++ b/lib/Data/Packed.hs
@@ -1,14 +1,14 @@
1----------------------------------------------------------------------------- 1-----------------------------------------------------------------------------
2{- | 2{- |
3Module : Data.Packed 3Module : Data.Packed
4Copyright : (c) Alberto Ruiz 2006-7 4Copyright : (c) Alberto Ruiz 2006-2010
5License : GPL-style 5License : GPL-style
6 6
7Maintainer : Alberto Ruiz (aruiz at um dot es) 7Maintainer : Alberto Ruiz (aruiz at um dot es)
8Stability : provisional 8Stability : provisional
9Portability : uses ffi 9Portability : uses ffi
10 10
11The Vector and Matrix types and some utilities. 11Types for dense 'Vector' and 'Matrix' of 'Storable' elements.
12 12
13-} 13-}
14----------------------------------------------------------------------------- 14-----------------------------------------------------------------------------
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index 7b823de..b616442 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -75,7 +75,11 @@ import Foreign.C.String
75 75
76data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq) 76data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq)
77 77
78-- | Matrix representation suitable for GSL and LAPACK computations. 78{- | Matrix representation suitable for GSL and LAPACK computations.
79
80The elements are stored in a continuous memory array.
81
82-}
79data Matrix t = MC { irows :: {-# UNPACK #-} !Int 83data Matrix t = MC { irows :: {-# UNPACK #-} !Int
80 , icols :: {-# UNPACK #-} !Int 84 , icols :: {-# UNPACK #-} !Int
81 , cdat :: {-# UNPACK #-} !(Vector t) } 85 , cdat :: {-# UNPACK #-} !(Vector t) }
@@ -245,9 +249,14 @@ compat m1 m2 = rows m1 == rows m2 && cols m1 == cols m2
245 249
246------------------------------------------------------------------ 250------------------------------------------------------------------
247 251
248-- | Supported element types for basic matrix operations. 252{- | Supported matrix elements.
249-- provides unoptimised defaults for all (Storable a) instances 253
250-- @instance Element Foo where@ 254 This class provides optimized internal
255 operations for selected element types.
256 It provides unoptimised defaults for any 'Storable' type,
257 so you can create instances simply as:
258 @instance Element Foo@.
259-}
251class (Storable a) => Element a where 260class (Storable a) => Element a where
252 subMatrixD :: (Int,Int) -- ^ (r0,c0) starting position 261 subMatrixD :: (Int,Int) -- ^ (r0,c0) starting position
253 -> (Int,Int) -- ^ (rt,ct) dimensions of submatrix 262 -> (Int,Int) -- ^ (rt,ct) dimensions of submatrix
@@ -257,30 +266,23 @@ class (Storable a) => Element a where
257 transdata = transdataP -- transdata' 266 transdata = transdataP -- transdata'
258 constantD :: a -> Int -> Vector a 267 constantD :: a -> Int -> Vector a
259 constantD = constantP -- constant' 268 constantD = constantP -- constant'
260{- 269
261 conjugateD :: Vector a -> Vector a
262 conjugateD = id
263-}
264 270
265instance Element Float where 271instance Element Float where
266 transdata = transdataAux ctransF 272 transdata = transdataAux ctransF
267 constantD = constantAux cconstantF 273 constantD = constantAux cconstantF
268-- conjugateD = id
269 274
270instance Element Double where 275instance Element Double where
271 transdata = transdataAux ctransR 276 transdata = transdataAux ctransR
272 constantD = constantAux cconstantR 277 constantD = constantAux cconstantR
273-- conjugateD = id
274 278
275instance Element (Complex Float) where 279instance Element (Complex Float) where
276 transdata = transdataAux ctransQ 280 transdata = transdataAux ctransQ
277 constantD = constantAux cconstantQ 281 constantD = constantAux cconstantQ
278-- conjugateD = conjugateQ
279 282
280instance Element (Complex Double) where 283instance Element (Complex Double) where
281 transdata = transdataAux ctransC 284 transdata = transdataAux ctransC
282 constantD = constantAux cconstantC 285 constantD = constantAux cconstantC
283-- conjugateD = conjugateC
284 286
285------------------------------------------------------------------- 287-------------------------------------------------------------------
286 288
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index 1fa8903..50a321d 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -7,7 +7,7 @@
7----------------------------------------------------------------------------- 7-----------------------------------------------------------------------------
8-- | 8-- |
9-- Module : Data.Packed.Matrix 9-- Module : Data.Packed.Matrix
10-- Copyright : (c) Alberto Ruiz 2007 10-- Copyright : (c) Alberto Ruiz 2007-10
11-- License : GPL-style 11-- License : GPL-style
12-- 12--
13-- Maintainer : Alberto Ruiz <aruiz@um.es> 13-- Maintainer : Alberto Ruiz <aruiz@um.es>
@@ -16,11 +16,14 @@
16-- 16--
17-- A Matrix representation suitable for numerical computations using LAPACK and GSL. 17-- A Matrix representation suitable for numerical computations using LAPACK and GSL.
18-- 18--
19-- This module provides basic functions for manipulation of structure.
20
19----------------------------------------------------------------------------- 21-----------------------------------------------------------------------------
20 22
21module Data.Packed.Matrix ( 23module Data.Packed.Matrix (
24 Matrix,
22 Element, 25 Element,
23 Matrix,rows,cols, 26 rows,cols,
24 (><), 27 (><),
25 trans, 28 trans,
26 reshape, flatten, 29 reshape, flatten,
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index 2e0a9f5..eaf4b9c 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -11,6 +11,8 @@
11-- 11--
12-- 1D arrays suitable for numeric computations using external libraries. 12-- 1D arrays suitable for numeric computations using external libraries.
13-- 13--
14-- This module provides basic functions for manipulation of structure.
15--
14----------------------------------------------------------------------------- 16-----------------------------------------------------------------------------
15 17
16module Data.Packed.Vector ( 18module Data.Packed.Vector (
diff --git a/lib/Graphics/Plot.hs b/lib/Graphics/Plot.hs
index c5b5a4c..0bdd803 100644
--- a/lib/Graphics/Plot.hs
+++ b/lib/Graphics/Plot.hs
@@ -3,15 +3,13 @@
3-- Module : Graphics.Plot 3-- Module : Graphics.Plot
4-- Copyright : (c) Alberto Ruiz 2005-8 4-- Copyright : (c) Alberto Ruiz 2005-8
5-- License : GPL-style 5-- License : GPL-style
6-- 6--
7-- Maintainer : Alberto Ruiz (aruiz at um dot es) 7-- Maintainer : Alberto Ruiz (aruiz at um dot es)
8-- Stability : provisional 8-- Stability : provisional
9-- Portability : uses gnuplot and ImageMagick 9-- Portability : uses gnuplot and ImageMagick
10-- 10--
11-- Very basic (and provisional) drawing tools using gnuplot and imageMagick. 11-- This module is deprecated. It can be replaced by improved drawing tools
12-- 12-- available in the plot\\plot-gtk packages by Vivian McPhail or Gnuplot by Henning Thielemann.
13-- This module is deprecated. It will be replaced by improved drawing tools based
14-- on the Gnuplot package by Henning Thielemann.
15----------------------------------------------------------------------------- 13-----------------------------------------------------------------------------
16 14
17module Graphics.Plot( 15module Graphics.Plot(
@@ -20,7 +18,7 @@ module Graphics.Plot(
20 18
21 plot, parametricPlot, 19 plot, parametricPlot,
22 20
23 splot, mesh, mesh', meshdom, 21 splot, mesh, meshdom,
24 22
25 matrixToPGM, imshow, 23 matrixToPGM, imshow,
26 24
@@ -32,35 +30,14 @@ import Numeric.Matrix
32import Data.List(intersperse) 30import Data.List(intersperse)
33import System.Process (system) 31import System.Process (system)
34 32
35size = dim
36
37-- | Loads a real matrix from a formatted ASCII text file
38--fromFile :: FilePath -> IO Matrix
39--fromFile filename = readFile filename >>= return . readMatrix read
40
41-- | Saves a real matrix to a formatted ascii text file
42toFile' :: FilePath -> Matrix Double -> IO ()
43toFile' filename matrix = writeFile filename (unlines . map unwords. map (map show) . toLists $ matrix)
44
45------------------------------------------------------------------------
46
47
48-- | From vectors x and y, it generates a pair of matrices to be used as x and y arguments for matrix functions. 33-- | From vectors x and y, it generates a pair of matrices to be used as x and y arguments for matrix functions.
49meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double) 34meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double)
50meshdom r1 r2 = (outer r1 (constant 1 (size r2)), outer (constant 1 (size r1)) r2) 35meshdom r1 r2 = (outer r1 (constant 1 (dim r2)), outer (constant 1 (dim r1)) r2)
51
52gnuplotX :: String -> IO ()
53gnuplotX command = do { _ <- system cmdstr; return()} where
54 cmdstr = "echo \""++command++"\" | gnuplot -persist"
55
56datafollows = "\\\"-\\\""
57
58prep = (++"e\n\n") . unlines . map (unwords . (map show))
59 36
60 37
61{- | Draws a 3D surface representation of a real matrix. 38{- | Draws a 3D surface representation of a real matrix.
62 39
63> > mesh (hilb 20) 40> > mesh $ build (10,10) (\\i j -> i + (j-5)^2)
64 41
65In certain versions you can interactively rotate the graphic using the mouse. 42In certain versions you can interactively rotate the graphic using the mouse.
66 43
@@ -70,15 +47,6 @@ mesh m = gnuplotX (command++dat) where
70 command = "splot "++datafollows++" matrix with lines\n" 47 command = "splot "++datafollows++" matrix with lines\n"
71 dat = prep $ toLists $ m 48 dat = prep $ toLists $ m
72 49
73mesh' :: Matrix Double -> IO ()
74mesh' m = do
75 writeFile "splot-gnu-command" "splot \"splot-tmp.txt\" matrix with lines; pause -1";
76 toFile' "splot-tmp.txt" m
77 putStr "Press [Return] to close the graphic and continue... "
78 _ <- system "gnuplot -persist splot-gnu-command"
79 _ <- system "rm splot-tmp.txt splot-gnu-command"
80 return ()
81
82{- | 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'.
83 51
84> > let f x y = cos (x + y) 52> > let f x y = cos (x + y)
@@ -86,11 +54,15 @@ mesh' m = do
86 54
87-} 55-}
88splot :: (Matrix Double->Matrix Double->Matrix Double) -> (Double,Double) -> (Double,Double) -> Int -> IO () 56splot :: (Matrix Double->Matrix Double->Matrix Double) -> (Double,Double) -> (Double,Double) -> Int -> IO ()
89splot f rx ry n = mesh' z where 57splot f rx ry n = mesh z where
90 (x,y) = meshdom (linspace n rx) (linspace n ry) 58 (x,y) = meshdom (linspace n rx) (linspace n ry)
91 z = f x y 59 z = f x y
92 60
93{- | plots several vectors against the first one -} 61{- | plots several vectors against the first one
62
63> > let t = linspace 100 (-3,3) in mplot [t, sin t, exp (-t^2)]
64
65-}
94mplot :: [Vector Double] -> IO () 66mplot :: [Vector Double] -> IO ()
95mplot m = gnuplotX (commands++dats) where 67mplot m = gnuplotX (commands++dats) where
96 commands = if length m == 1 then command1 else commandmore 68 commands = if length m == 1 then command1 else commandmore
@@ -102,26 +74,6 @@ mplot m = gnuplotX (commands++dats) where
102 dats = concat (replicate (length m-1) dat) 74 dats = concat (replicate (length m-1) dat)
103 75
104 76
105{-
106mplot' m = do
107 writeFile "plot-gnu-command" (commands++endcmd)
108 toFile "plot-tmp.txt" (fromColumns m)
109 putStr "Press [Return] to close the graphic and continue... "
110 system "gnuplot plot-gnu-command"
111 system "rm plot-tmp.txt plot-gnu-command"
112 return ()
113 where
114 commands = if length m == 1 then command1 else commandmore
115 command1 = "plot \"plot-tmp.txt\" with lines\n"
116 commandmore = "plot " ++ plots ++ "\n"
117 plots = concat $ intersperse ", " (map cmd [2 .. length m])
118 cmd k = "\"plot-tmp.txt\" using 1:"++show k++" with lines"
119 endcmd = "pause -1"
120-}
121
122-- apply several functions to one object
123mapf fs x = map ($ x) fs
124
125{- | Draws a list of functions over a desired range and with a desired number of points 77{- | Draws a list of functions over a desired range and with a desired number of points
126 78
127> > plot [sin, cos, sin.(3*)] (0,2*pi) 1000 79> > plot [sin, cos, sin.(3*)] (0,2*pi) 1000
@@ -129,7 +81,8 @@ mapf fs x = map ($ x) fs
129-} 81-}
130plot :: [Vector Double->Vector Double] -> (Double,Double) -> Int -> IO () 82plot :: [Vector Double->Vector Double] -> (Double,Double) -> Int -> IO ()
131plot fs rx n = mplot (x: mapf fs x) 83plot fs rx n = mplot (x: mapf fs x)
132 where x = linspace n rx 84 where x = linspace n rx
85 mapf gs y = map ($ y) gs
133 86
134{- | Draws a parametric curve. For instance, to draw a spiral we can do something like: 87{- | Draws a parametric curve. For instance, to draw a spiral we can do something like:
135 88
@@ -165,6 +118,15 @@ imshow m = do
165 118
166---------------------------------------------------- 119----------------------------------------------------
167 120
121gnuplotX :: String -> IO ()
122gnuplotX command = do { _ <- system cmdstr; return()} where
123 cmdstr = "echo \""++command++"\" | gnuplot -persist"
124
125datafollows = "\\\"-\\\""
126
127prep = (++"e\n\n") . unlines . map (unwords . (map show))
128
129
168gnuplotpdf :: String -> String -> [([[Double]], String)] -> IO () 130gnuplotpdf :: String -> String -> [([[Double]], String)] -> IO ()
169gnuplotpdf title command ds = gnuplot (prelude ++ command ++" "++ draw) >> postproc where 131gnuplotpdf title command ds = gnuplot (prelude ++ command ++" "++ draw) >> postproc where
170 prelude = "set terminal epslatex color; set output '"++title++".tex';" 132 prelude = "set terminal epslatex color; set output '"++title++".tex';"
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
index 1c542b8..6b73a4e 100644
--- a/lib/Numeric/Container.hs
+++ b/lib/Numeric/Container.hs
@@ -15,7 +15,13 @@
15-- Stability : provisional 15-- Stability : provisional
16-- Portability : portable 16-- Portability : portable
17-- 17--
18-- Numeric classes for containers of numbers, including conversion routines 18-- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines.
19--
20-- The 'Container' class is used to define optimized generic functions which work
21-- on 'Vector' and 'Matrix' with real or complex elements.
22--
23-- Some of these functions are also available in the instances of the standard
24-- numeric Haskell classes provided by "Numeric.Vector" and "Numeric.Matrix".
19-- 25--
20----------------------------------------------------------------------------- 26-----------------------------------------------------------------------------
21 27
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs
index 64deba2..c49bec7 100644
--- a/lib/Numeric/LinearAlgebra/Algorithms.hs
+++ b/lib/Numeric/LinearAlgebra/Algorithms.hs
@@ -82,7 +82,10 @@ import Data.Array
82import Numeric.Container hiding ((.*),(*/)) 82import Numeric.Container hiding ((.*),(*/))
83import Numeric.MatrixBoot 83import Numeric.MatrixBoot
84 84
85-- | Auxiliary typeclass used to define generic computations for both real and complex matrices. 85{- | Auxiliary typeclass used to define generic linear algebra computations for both real and complex matrices. Only double precision is supported in this version (we can
86transform single precision objects using 'single' and 'double').
87
88-}
86class (Product t, 89class (Product t,
87 Convert t, 90 Convert t,
88 Container Vector t, 91 Container Vector t,