module Graphics.Plot(
mplot,
plot, parametricPlot,
splot, mesh, meshdom,
matrixToPGM, imshow,
gnuplotX, gnuplotpdf, gnuplotWin
) where
import Numeric.Container
import Data.List(intersperse)
import System.Process (system)
meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double)
meshdom r1 r2 = (outer r1 (constant 1 (dim r2)), outer (constant 1 (dim r1)) r2)
mesh :: Matrix Double -> IO ()
mesh m = gnuplotX (command++dat) where
command = "splot "++datafollows++" matrix with lines\n"
dat = prep $ toLists m
splot :: (Matrix Double->Matrix Double->Matrix Double) -> (Double,Double) -> (Double,Double) -> Int -> IO ()
splot f rx ry n = mesh z where
(x,y) = meshdom (linspace n rx) (linspace n ry)
z = f x y
mplot :: [Vector Double] -> IO ()
mplot m = gnuplotX (commands++dats) where
commands = if length m == 1 then command1 else commandmore
command1 = "plot "++datafollows++" with lines\n" ++ dat
commandmore = "plot " ++ plots ++ "\n"
plots = concat $ intersperse ", " (map cmd [2 .. length m])
cmd k = datafollows++" using 1:"++show k++" with lines"
dat = prep $ toLists $ fromColumns m
dats = concat (replicate (length m1) dat)
plot :: [Vector Double->Vector Double] -> (Double,Double) -> Int -> IO ()
plot fs rx n = mplot (x: mapf fs x)
where x = linspace n rx
mapf gs y = map ($ y) gs
parametricPlot :: (Vector Double->(Vector Double,Vector Double)) -> (Double, Double) -> Int -> IO ()
parametricPlot f rt n = mplot [fx, fy]
where t = linspace n rt
(fx,fy) = f t
matrixToPGM :: Matrix Double -> String
matrixToPGM m = header ++ unlines (map unwords ll) where
c = cols m
r = rows m
header = "P2 "++show c++" "++show r++" "++show (round maxgray :: Int)++"\n"
maxgray = 255.0
maxval = maxElement m
minval = minElement m
scale' = if maxval == minval
then 0.0
else maxgray / (maxval minval)
f x = show ( round ( scale' *(x minval) ) :: Int )
ll = map (map f) (toLists m)
imshow :: Matrix Double -> IO ()
imshow m = do
_ <- system $ "echo \""++ matrixToPGM m ++"\"| display -antialias -resize 300 - &"
return ()
gnuplotX :: String -> IO ()
gnuplotX command = do { _ <- system cmdstr; return()} where
cmdstr = "echo \""++command++"\" | gnuplot -persist"
datafollows = "\\\"-\\\""
prep = (++"e\n\n") . unlines . map (unwords . map show)
gnuplotpdf :: String -> String -> [([[Double]], String)] -> IO ()
gnuplotpdf title command ds = gnuplot (prelude ++ command ++" "++ draw) >> postproc where
prelude = "set terminal epslatex color; set output '"++title++".tex';"
(dats,defs) = unzip ds
draw = concat (intersperse ", " (map ("\"-\" "++) defs)) ++ "\n" ++
concatMap pr dats
postproc = do
_ <- system $ "epstopdf "++title++".eps"
mklatex
_ <- system $ "pdflatex "++title++"aux.tex > /dev/null"
_ <- system $ "pdfcrop "++title++"aux.pdf > /dev/null"
_ <- system $ "mv "++title++"aux-crop.pdf "++title++".pdf"
_ <- system $ "rm "++title++"aux.* "++title++".eps "++title++".tex"
return ()
mklatex = writeFile (title++"aux.tex") $
"\\documentclass{article}\n"++
"\\usepackage{graphics}\n"++
"\\usepackage{nopageno}\n"++
"\\usepackage{txfonts}\n"++
"\\renewcommand{\\familydefault}{phv}\n"++
"\\usepackage[usenames]{color}\n"++
"\\begin{document}\n"++
"\\begin{center}\n"++
" \\input{./"++title++".tex}\n"++
"\\end{center}\n"++
"\\end{document}"
pr = (++"e\n") . unlines . map (unwords . map show)
gnuplot cmd = do
writeFile "gnuplotcommand" cmd
_ <- system "gnuplot gnuplotcommand"
_ <- system "rm gnuplotcommand"
return ()
gnuplotWin :: String -> String -> [([[Double]], String)] -> IO ()
gnuplotWin title command ds = gnuplot (prelude ++ command ++" "++ draw) where
(dats,defs) = unzip ds
draw = concat (intersperse ", " (map ("\"-\" "++) defs)) ++ "\n" ++
concatMap pr dats
pr = (++"e\n") . unlines . map (unwords . map show)
prelude = "set title \""++title++"\";"
gnuplot cmd = do
writeFile "gnuplotcommand" cmd
_ <- system "gnuplot -persist gnuplotcommand"
_ <- system "rm gnuplotcommand"
return ()