module System.Command.QQ.Eval
( Eval(..)
) where
import Control.Applicative
import Control.Concurrent
import Control.Exception (evaluate)
import Control.Monad
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.IO as T
import System.Exit (ExitCode)
import qualified System.Process as P
import System.IO (hFlush, hClose)
class Eval r where
eval :: String -> [String] -> r
instance Eval (IO ()) where
eval command args = () <$ P.rawSystem command args
instance Eval (IO ExitCode) where
eval command args = do
(s, _, _) <- eval command args (T.pack "")
return s
instance Eval (IO Text) where
eval command args = do
(_, o, _) <- eval command args
return o
instance Eval (IO String) where
eval command args = T.unpack <$> eval command args
instance
( s ~ ExitCode
, o ~ Text
, e ~ Text
) => Eval (IO (s, o, e)) where
eval command args = eval command args (T.pack "")
instance
( i ~ Text
, o ~ (ExitCode, Text, Text)
) => Eval (i -> IO o) where
eval = readProcessWithExitCode
readProcessWithExitCode :: String -> [String] -> Text -> IO (ExitCode, Text, Text)
readProcessWithExitCode cmd args input = do
(Just inh, Just outh, Just errh, p) <-
P.createProcess (P.proc cmd args)
{ P.std_in = P.CreatePipe
, P.std_out = P.CreatePipe
, P.std_err = P.CreatePipe
}
var <- newEmptyMVar
out <- T.hGetContents outh
err <- T.hGetContents errh
forkFinally (evaluate (T.length out)) (\_ -> putMVar var ())
forkFinally (evaluate (T.length err)) (\_ -> putMVar var ())
unless (T.null input) $
T.hPutStr inh input >> hFlush inh
hClose inh
takeMVar var
takeMVar var
hClose outh
hClose errh
s <- P.waitForProcess p
return (s, out, err)