module System.Process.Common
( ProcessMaker(process)
, ListLikeProcessIO(forceOutput, readChunks)
, ProcessOutput(pidf, outf, errf, intf, codef)
, readProcessWithExitCode
, readCreateProcessWithExitCode
, readCreateProcess
, readCreateProcessLazy
) where
import Control.Concurrent
import Control.DeepSeq (NFData)
import Control.Exception as E (SomeException, onException, catch, mask, throw, try)
import Control.Monad
import Data.ListLike as ListLike (null)
import Data.ListLike.IO (ListLikeIO, hGetContents, hPutStr)
import Data.Monoid ((<>))
import Generics.Deriving.Instances ()
import GHC.IO.Exception (IOErrorType(ResourceVanished), IOException(ioe_type))
import Prelude hiding (null)
import System.Exit (ExitCode(..))
import System.IO (Handle, hClose, hFlush, BufferMode, hSetBuffering)
import System.IO.Unsafe (unsafeInterleaveIO)
import System.Process (CreateProcess(std_err, std_in, std_out), StdStream(CreatePipe), ProcessHandle, createProcess, proc, waitForProcess, terminateProcess)
import Utils (forkWait)
#if __GLASGOW_HASKELL__ <= 709
import Control.Applicative ((<$>), (<*>))
import Data.Monoid (Monoid(mempty, mappend))
#endif
#if !MIN_VERSION_deepseq(1,4,2)
instance NFData ExitCode
#endif
class ProcessMaker a where
process :: a -> IO (Handle, Handle, Handle, ProcessHandle)
instance ProcessMaker CreateProcess where
process p = do
(Just inh, Just outh, Just errh, pid) <- createProcess p { std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe }
return (inh, outh, errh, pid)
instance ProcessMaker (CreateProcess, BufferMode, BufferMode) where
process (p, outmode, errmode) = do
(Just inh, Just outh, Just errh, pid) <- createProcess p { std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe }
hSetBuffering outh outmode
hSetBuffering errh errmode
return (inh, outh, errh, pid)
class Monoid b => ProcessOutput a b | b -> a where
pidf :: ProcessHandle -> b
outf :: a -> b
errf :: a -> b
intf :: SomeException -> b
codef :: ExitCode -> b
instance ListLikeProcessIO a c => ProcessOutput a (ExitCode, a, a) where
pidf _ = mempty
codef c = (c, mempty, mempty)
outf x = (mempty, x, mempty)
errf x = (mempty, mempty, x)
intf e = throw e
instance Monoid ExitCode where
mempty = ExitFailure 0
mappend x (ExitFailure 0) = x
mappend _ x = x
class ListLikeIO a c => ListLikeProcessIO a c where
forceOutput :: a -> IO a
readChunks :: Handle -> IO [a]
readProcessWithExitCode
:: ListLikeProcessIO a c =>
FilePath
-> [String]
-> a
-> IO (ExitCode, a, a)
readProcessWithExitCode cmd args input = readCreateProcessWithExitCode (proc cmd args) input
readCreateProcessWithExitCode
:: (ProcessMaker maker, ListLikeProcessIO a c) =>
maker
-> a
-> IO (ExitCode, a, a)
readCreateProcessWithExitCode = readCreateProcess
readCreateProcess :: (ProcessMaker maker, ProcessOutput a b, ListLikeProcessIO a c) => maker -> a -> IO b
readCreateProcess maker input = mask $ \restore -> do
(inh, outh, errh, pid) <- process maker
flip onException
(do terminateProcess pid; hClose inh; hClose outh; hClose errh;
waitForProcess pid) $ restore $ do
waitOut <- forkWait $ outf <$> (hGetContents outh >>= forceOutput)
waitErr <- forkWait $ errf <$> (hGetContents errh >>= forceOutput)
writeInput inh input
out <- waitOut
err <- waitErr
hClose outh
hClose errh
ex <- codef <$> waitForProcess pid
return $ out <> err <> ex
readCreateProcessLazy :: (ProcessMaker maker, ProcessOutput a b, ListLikeProcessIO a c) => maker -> a -> IO b
readCreateProcessLazy maker input = mask $ \restore -> do
(inh, outh, errh, pid) <- process maker
onException
(restore $
do
waitOut <- forkWait $ (<>) <$> return (pidf pid)
<*> unsafeInterleaveIO (readInterleaved [(outf, outh), (errf, errh)] (codef <$> waitForProcess pid))
writeInput inh input
waitOut)
(do terminateProcess pid; hClose inh; hClose outh; hClose errh;
waitForProcess pid)
readInterleaved :: (ListLikeProcessIO a c, ProcessOutput a b) =>
[(a -> b, Handle)] -> IO b -> IO b
readInterleaved pairs finish = newEmptyMVar >>= readInterleaved' pairs finish
readInterleaved' :: forall a b c. (ListLikeProcessIO a c, ProcessOutput a b) =>
[(a -> b, Handle)] -> IO b -> MVar (Either Handle b) -> IO b
readInterleaved' pairs finish res = do
mapM_ (forkIO . uncurry readHandle) pairs
takeChunks (length pairs)
where
readHandle :: (a -> b) -> Handle -> IO ()
readHandle f h = do
cs <- readChunks h
mapM_ (\ c -> putMVar res (Right (f c))) cs
hClose h
putMVar res (Left h)
takeChunks :: Int -> IO b
takeChunks 0 = finish
takeChunks openCount = takeChunk >>= takeMore openCount
takeMore :: Int -> Either Handle b -> IO b
takeMore openCount (Left h) = hClose h >> takeChunks (openCount 1)
takeMore openCount (Right x) =
do xs <- unsafeInterleaveIO $ takeChunks openCount
return (x <> xs)
takeChunk = takeMVar res `E.catch` (\ (e :: SomeException) -> return $ Right $ intf e)
writeInput :: ListLikeProcessIO a c => Handle -> a -> IO ()
writeInput inh input =
ignoreResourceVanished $ do
unless (ListLike.null input) $ do
hPutStr inh input
hFlush inh
hClose inh
ignoreResourceVanished :: IO () -> IO ()
ignoreResourceVanished action =
action `E.catch` (\e -> if ioe_type e == ResourceVanished then return () else ioError e)