module Graphics.Plot(
    mplot,
    plot, parametricPlot, 
    splot, mesh, mesh', meshdom,
    matrixToPGM, imshow,
    gnuplotX
) where
import Data.Packed.Vector
import Data.Packed.Matrix
import Numeric.LinearAlgebra.Linear(outer)
import Numeric.GSL.Vector(FunCodeS(Max,Min),toScalarR)
import Data.List(intersperse)
import System
import Foreign hiding (rotate)
size = dim
toFile :: FilePath -> Matrix Double -> IO ()
toFile filename matrix = writeFile filename (unlines . map unwords. map (map show) . toLists $ matrix)
meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double)
meshdom r1 r2 = (outer r1 (constant 1 (size r2)), outer (constant 1 (size r1)) r2)
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))
mesh :: Matrix Double -> IO ()
mesh m = gnuplotX (command++dat) where
    command = "splot "++datafollows++" matrix with lines\n"
    dat = prep $ toLists $ m
mesh' :: Matrix Double -> IO ()
mesh' m = do
    writeFile "splot-gnu-command" "splot \"splot-tmp.txt\" matrix with lines; pause -1"; 
    toFile "splot-tmp.txt" m
    putStr "Press [Return] to close the graphic and continue... "
    system "gnuplot -persist splot-gnu-command"
    system "rm splot-tmp.txt splot-gnu-command"
    return ()
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)
mapf fs x = map ($ x) fs
plot :: [Vector Double->Vector Double] -> (Double,Double) -> Int -> IO ()
plot fs rx n = mplot (x: mapf fs x)
    where x = linspace n rx  
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 = toScalarR Max $ flatten $ m
    minval = toScalarR Min $ flatten $ 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 ()