module Language.Clafer.IG.Process (Process, executableDirectory, waitFor, getContentsVerbatim, getMessage, readMessage, putMessage, pipeProcess) where
import Control.Monad
import Control.Monad.IO.Class
import System.Environment.Executable
import System.IO
import System.Process
import GHC.IO.Exception
data Process = Process{stdIn::Handle, stdOut::Handle, procHandle::ProcessHandle}
executableDirectory :: IO FilePath
executableDirectory = fst `liftM` splitExecutablePath
pipeProcess :: FilePath -> [String] -> IO Process
pipeProcess exec args =
do
let process = (proc exec args) { std_in = CreatePipe, std_out = CreatePipe }
(Just stdIn', Just stdOut', _, proceHandle) <- createProcess process
hSetNewlineMode stdIn' noNewlineTranslation
return $ Process stdIn' stdOut' proceHandle
waitFor :: Process -> IO ExitCode
waitFor proce = waitForProcess (procHandle proce)
getContentsVerbatim :: Process -> IO String
getContentsVerbatim proce =
do
contents <- hGetContents $ stdOut proce
mapM_ return contents
return contents
getMessage :: MonadIO m => Process -> m String
getMessage proce =
liftIO $ do
len <- read `liftM` hGetLine (stdOut proce)
mapM hGetChar $ replicate len (stdOut proce)
readMessage :: (Read r, MonadIO m) => Process -> m r
readMessage proce = read `liftM` getMessage proce
putMessage :: MonadIO m => Process -> String -> m ()
putMessage proce message =
liftIO $ do
hPutStrLn (stdIn proce) (show $ length message)
hPutStr (stdIn proce) message
hFlush (stdIn proce)