module Controller.Menu.File.Export.Diagram.Common (MakeGnuPlotFile,showPreview,plot,getNumericColumns) where import Control.Monad (forM,when) import Control.Monad.Trans (liftIO) import Data.Either (partitionEithers) import System.Exit (ExitCode(ExitSuccess,ExitFailure)) import qualified Graphics.UI.WXCore as WXC import Controller (Controller,onGridModel,onGridView) import Controller.Dialog (previewImage,warning) import Constants (tmpFilePath,programName) import qualified Util.Gnuplot as GP import Model.CellExpression.Evaluator.Common (getNumList) import Model.Grid (getColumnValues) import View.Component.Grid (getColumnLabel) import Util ((<.>)) import I18n (__) type MakeGnuPlotFile = FilePath -> String type MakeDataFile = Controller (Either String String) getTmpImageFilePath,getTmpDataFilePath,getTmpGpFilePath :: Controller FilePath getTmpImageFilePath = liftIO $ tmpFilePath $ programName ++ ".gnuplot.png" getTmpDataFilePath = liftIO $ tmpFilePath $ programName ++ ".gnuplot.data" getTmpGpFilePath = liftIO $ tmpFilePath $ programName ++ ".gnuplot" showPreview :: MakeGnuPlotFile -> MakeDataFile -> Controller Bool showPreview makeGpFile makeDataFile = do tmpImageFilePath <- getTmpImageFilePath success <- plot makeGpFile makeDataFile tmpImageFilePath when success $ do bitmap <- liftIO $ WXC.imageCreateFromFile tmpImageFilePath >>= WXC.imageConvertToBitmap previewImage bitmap return success plot :: MakeGnuPlotFile -> MakeDataFile -> FilePath -> Controller Bool plot makeGpFile makeDataFile imageFilePath = do dataFilePath <- getTmpDataFilePath gpFilePath <- getTmpGpFilePath makeDataFileContentResult <- makeDataFile case makeDataFileContentResult of Left msg -> warning msg >> return False Right dataFileContent -> let dataFile = (dataFilePath,dataFileContent) gpFileContent = unlines [ "set terminal png" , "set output \"" ++ imageFilePath ++ "\"" , makeGpFile dataFilePath] gpFile = (gpFilePath,gpFileContent) in do result <- liftIO $ GP.run gpFile [dataFile] case result of ExitSuccess -> return True ExitFailure _ -> do warning $ concat [__ "Can not plot diagram",": ",show result] return False getNumericColumns :: [Int] -> Controller (Either [String] [(String,[Double])]) getNumericColumns cols = do result <- forM cols $ \i -> do tmp <- onGridModel $ (getNumList <.> getColumnValues i) label <- onGridView $ getColumnLabel i case tmp of Left _ -> return $ Left label Right nums -> return $ Right (label,nums) case partitionEithers result of (x:xs,_) -> return $ Left (x:xs) ([],columns) -> return $ Right columns