module Data.GraphViz.Commands.IO
(
toUTF8
, writeDotFile
, readDotFile
, hPutDot
, hPutCompactDot
, hGetDot
, hGetStrict
, putDot
, readDot
, runCommand
) where
import Data.GraphViz.State(initialState)
import Data.GraphViz.Types(PrintDotRepr, ParseDotRepr, printDotGraph, parseDotGraph)
import Data.GraphViz.Printing(toDot)
import Data.GraphViz.Exception
import Text.PrettyPrint.Leijen.Text(displayT, renderOneLine)
import qualified Data.Text.Lazy.Encoding as T
import Data.Text.Encoding.Error(UnicodeException)
import Data.Text.Lazy(Text)
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as B
import Data.ByteString.Lazy(ByteString)
import Control.Monad(liftM)
import Control.Monad.Trans.State
import System.IO(Handle, IOMode(ReadMode,WriteMode)
, withFile, stdout, stdin, hPutChar
, hClose, hGetContents)
import System.IO.Temp(withSystemTempFile)
import System.Exit(ExitCode(ExitSuccess))
import System.Process(runInteractiveProcess, waitForProcess)
import System.FilePath((<.>))
import Control.Exception(IOException, evaluate, finally)
import Control.Concurrent(MVar, forkIO, newEmptyMVar, putMVar, takeMVar)
renderCompactDot :: (PrintDotRepr dg n) => dg n -> Text
renderCompactDot = displayT . renderOneLine
. (`evalState` initialState)
. toDot
toUTF8 :: ByteString -> Text
toUTF8 = mapException fE . T.decodeUtf8
where
fE :: UnicodeException -> GraphvizException
fE e = NotUTF8Dot $ show e
hPutDot :: (PrintDotRepr dg n) => Handle -> dg n -> IO ()
hPutDot = toHandle printDotGraph
hPutCompactDot :: (PrintDotRepr dg n) => Handle -> dg n -> IO ()
hPutCompactDot = toHandle renderCompactDot
toHandle :: (PrintDotRepr dg n) => (dg n -> Text) -> Handle -> dg n
-> IO ()
toHandle f h dg = do B.hPutStr h . T.encodeUtf8 $ f dg
hPutChar h '\n'
hGetStrict :: Handle -> IO Text
hGetStrict = liftM (toUTF8 . B.fromChunks . (:[]))
. SB.hGetContents
hGetDot :: (ParseDotRepr dg n) => Handle -> IO (dg n)
hGetDot = liftM parseDotGraph . hGetStrict
writeDotFile :: (PrintDotRepr dg n) => FilePath -> dg n -> IO ()
writeDotFile f = withFile f WriteMode . flip hPutDot
readDotFile :: (ParseDotRepr dg n) => FilePath -> IO (dg n)
readDotFile f = withFile f ReadMode hGetDot
putDot :: (PrintDotRepr dg n) => dg n -> IO ()
putDot = hPutDot stdout
readDot :: (ParseDotRepr dg n) => IO (dg n)
readDot = hGetDot stdin
runCommand :: (PrintDotRepr dg n)
=> String
-> [String]
-> (Handle -> IO a)
-> dg n
-> IO a
runCommand cmd args hf dg
= mapException notRunnable $
withSystemTempFile ("graphviz" <.> "dot") $ \dotFile dotHandle -> do
finally (hPutCompactDot dotHandle dg) (hClose dotHandle)
bracket
(runInteractiveProcess cmd (args ++ [dotFile]) Nothing Nothing)
(\(inh,outh,errh,_) -> hClose inh >> hClose outh >> hClose errh)
$ \(inp,outp,errp,prc) -> do
hClose inp
mvOutput <- newEmptyMVar
mvErr <- newEmptyMVar
forkIO $ signalWhenDone hGetContents' errp mvErr
forkIO $ signalWhenDone hf' outp mvOutput
err <- takeMVar mvErr
output <- takeMVar mvOutput
exitCode <- waitForProcess prc
case exitCode of
ExitSuccess -> return output
_ -> throw . GVProgramExc $ othErr ++ err
where
notRunnable :: IOException -> GraphvizException
notRunnable e = GVProgramExc $ unwords
[ "Unable to call the command "
, cmd
, " with the arguments: \""
, unwords args
, "\" because of: "
, show e
]
hf' = mapException fErr . hf
fErr :: IOException -> GraphvizException
fErr e = GVProgramExc $ "Error re-directing the output from "
++ cmd ++ ": " ++ show e
othErr = "Error messages from " ++ cmd ++ ":\n"
hGetContents' :: Handle -> IO String
hGetContents' h = do r <- hGetContents h
evaluate $ length r
return r
signalWhenDone :: (Handle -> IO a) -> Handle -> MVar a -> IO ()
signalWhenDone f h mv = f h >>= putMVar mv >> return ()