module System.Process.Text where import Control.Concurrent import Control.Monad import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T import System.Process import System.Exit (ExitCode) import System.IO -- | Like 'System.Process.readProcessWithExitCode', but using 'Text' readProcessWithExitCode :: FilePath -- ^ command to run -> [String] -- ^ any arguments -> Text -- ^ standard input -> IO (ExitCode, Text, Text) -- ^ exitcode, stdout, stderr readProcessWithExitCode cmd args input = do (Just inh, Just outh, Just errh, pid) <- createProcess (proc cmd args){ std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe } outMVar <- newEmptyMVar outM <- newEmptyMVar errM <- newEmptyMVar -- fork off a thread to start consuming stdout _ <- forkIO $ do out <- T.hGetContents outh putMVar outM out putMVar outMVar () -- fork off a thread to start consuming stderr _ <- forkIO $ do err <- T.hGetContents errh putMVar errM err putMVar outMVar () -- now write and flush any input when (not (T.null input)) $ do T.hPutStr inh input; hFlush inh hClose inh -- done with stdin -- wait on the output takeMVar outMVar takeMVar outMVar hClose outh hClose errh -- wait on the process ex <- waitForProcess pid out <- readMVar outM err <- readMVar errM return (ex, out, err)