{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Data.Streaming.Process
(
streamingProcess
, closeStreamingProcessHandle
, Inherited (..)
, ClosedStream (..)
, UseProvidedHandle (..)
, StreamingProcessHandle
, waitForStreamingProcess
, waitForStreamingProcessSTM
, getStreamingProcessExitCode
, getStreamingProcessExitCodeSTM
, streamingProcessHandleRaw
, streamingProcessHandleTMVar
, InputSource
, OutputSink
, withCheckedProcess
, ProcessExitedUnsuccessfully (..)
, module System.Process
) where
import Control.Applicative as A ((<$>), (<*>))
import Control.Concurrent (forkIOWithUnmask)
import Control.Concurrent.STM (STM, TMVar, atomically,
newEmptyTMVar, putTMVar,
readTMVar)
import Control.Exception (Exception, throwIO, try, throw,
SomeException, finally)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Maybe (fromMaybe)
import Data.Streaming.Process.Internal
import Data.Typeable (Typeable)
import System.Exit (ExitCode (ExitSuccess))
import System.IO (hClose)
import System.Process
#if MIN_VERSION_process(1,2,0)
import qualified System.Process.Internals as PI
#endif
#if MIN_VERSION_stm(2,3,0)
import Control.Concurrent.STM (tryReadTMVar)
#else
import Control.Concurrent.STM (tryTakeTMVar, putTMVar)
tryReadTMVar :: TMVar a -> STM (Maybe a)
tryReadTMVar var = do
mx <- tryTakeTMVar var
case mx of
Nothing -> return ()
Just x -> putTMVar var x
return mx
#endif
data UseProvidedHandle = UseProvidedHandle
data Inherited = Inherited
data ClosedStream = ClosedStream
instance InputSource ClosedStream where
isStdStream :: (Maybe Handle -> IO ClosedStream, Maybe StdStream)
isStdStream = (\(Just Handle
h) -> Handle -> IO ()
hClose Handle
h IO () -> IO ClosedStream -> IO ClosedStream
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ClosedStream -> IO ClosedStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ClosedStream
ClosedStream, StdStream -> Maybe StdStream
forall a. a -> Maybe a
Just StdStream
CreatePipe)
instance InputSource Inherited where
isStdStream :: (Maybe Handle -> IO Inherited, Maybe StdStream)
isStdStream = (\Maybe Handle
Nothing -> Inherited -> IO Inherited
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Inherited
Inherited, StdStream -> Maybe StdStream
forall a. a -> Maybe a
Just StdStream
Inherit)
instance InputSource UseProvidedHandle where
isStdStream :: (Maybe Handle -> IO UseProvidedHandle, Maybe StdStream)
isStdStream = (\Maybe Handle
Nothing -> UseProvidedHandle -> IO UseProvidedHandle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UseProvidedHandle
UseProvidedHandle, Maybe StdStream
forall a. Maybe a
Nothing)
instance OutputSink ClosedStream where
osStdStream :: (Maybe Handle -> IO ClosedStream, Maybe StdStream)
osStdStream = (\(Just Handle
h) -> Handle -> IO ()
hClose Handle
h IO () -> IO ClosedStream -> IO ClosedStream
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ClosedStream -> IO ClosedStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ClosedStream
ClosedStream, StdStream -> Maybe StdStream
forall a. a -> Maybe a
Just StdStream
CreatePipe)
instance OutputSink Inherited where
osStdStream :: (Maybe Handle -> IO Inherited, Maybe StdStream)
osStdStream = (\Maybe Handle
Nothing -> Inherited -> IO Inherited
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Inherited
Inherited, StdStream -> Maybe StdStream
forall a. a -> Maybe a
Just StdStream
Inherit)
instance OutputSink UseProvidedHandle where
osStdStream :: (Maybe Handle -> IO UseProvidedHandle, Maybe StdStream)
osStdStream = (\Maybe Handle
Nothing -> UseProvidedHandle -> IO UseProvidedHandle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UseProvidedHandle
UseProvidedHandle, Maybe StdStream
forall a. Maybe a
Nothing)
waitForStreamingProcess :: MonadIO m => StreamingProcessHandle -> m ExitCode
waitForStreamingProcess :: forall (m :: * -> *).
MonadIO m =>
StreamingProcessHandle -> m ExitCode
waitForStreamingProcess = IO ExitCode -> m ExitCode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ExitCode -> m ExitCode)
-> (StreamingProcessHandle -> IO ExitCode)
-> StreamingProcessHandle
-> m ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STM ExitCode -> IO ExitCode
forall a. STM a -> IO a
atomically (STM ExitCode -> IO ExitCode)
-> (StreamingProcessHandle -> STM ExitCode)
-> StreamingProcessHandle
-> IO ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamingProcessHandle -> STM ExitCode
waitForStreamingProcessSTM
waitForStreamingProcessSTM :: StreamingProcessHandle -> STM ExitCode
waitForStreamingProcessSTM :: StreamingProcessHandle -> STM ExitCode
waitForStreamingProcessSTM = TMVar ExitCode -> STM ExitCode
forall a. TMVar a -> STM a
readTMVar (TMVar ExitCode -> STM ExitCode)
-> (StreamingProcessHandle -> TMVar ExitCode)
-> StreamingProcessHandle
-> STM ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamingProcessHandle -> TMVar ExitCode
streamingProcessHandleTMVar
getStreamingProcessExitCode :: MonadIO m => StreamingProcessHandle -> m (Maybe ExitCode)
getStreamingProcessExitCode :: forall (m :: * -> *).
MonadIO m =>
StreamingProcessHandle -> m (Maybe ExitCode)
getStreamingProcessExitCode = IO (Maybe ExitCode) -> m (Maybe ExitCode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ExitCode) -> m (Maybe ExitCode))
-> (StreamingProcessHandle -> IO (Maybe ExitCode))
-> StreamingProcessHandle
-> m (Maybe ExitCode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STM (Maybe ExitCode) -> IO (Maybe ExitCode)
forall a. STM a -> IO a
atomically (STM (Maybe ExitCode) -> IO (Maybe ExitCode))
-> (StreamingProcessHandle -> STM (Maybe ExitCode))
-> StreamingProcessHandle
-> IO (Maybe ExitCode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamingProcessHandle -> STM (Maybe ExitCode)
getStreamingProcessExitCodeSTM
getStreamingProcessExitCodeSTM :: StreamingProcessHandle -> STM (Maybe ExitCode)
getStreamingProcessExitCodeSTM :: StreamingProcessHandle -> STM (Maybe ExitCode)
getStreamingProcessExitCodeSTM = TMVar ExitCode -> STM (Maybe ExitCode)
forall a. TMVar a -> STM (Maybe a)
tryReadTMVar (TMVar ExitCode -> STM (Maybe ExitCode))
-> (StreamingProcessHandle -> TMVar ExitCode)
-> StreamingProcessHandle
-> STM (Maybe ExitCode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamingProcessHandle -> TMVar ExitCode
streamingProcessHandleTMVar
streamingProcessHandleRaw :: StreamingProcessHandle -> ProcessHandle
streamingProcessHandleRaw :: StreamingProcessHandle -> ProcessHandle
streamingProcessHandleRaw (StreamingProcessHandle ProcessHandle
ph TMVar ExitCode
_ IO ()
_) = ProcessHandle
ph
streamingProcessHandleTMVar :: StreamingProcessHandle -> TMVar ExitCode
streamingProcessHandleTMVar :: StreamingProcessHandle -> TMVar ExitCode
streamingProcessHandleTMVar (StreamingProcessHandle ProcessHandle
_ TMVar ExitCode
var IO ()
_) = TMVar ExitCode
var
streamingProcess :: (MonadIO m, InputSource stdin, OutputSink stdout, OutputSink stderr)
=> CreateProcess
-> m (stdin, stdout, stderr, StreamingProcessHandle)
streamingProcess :: forall (m :: * -> *) stdin stdout stderr.
(MonadIO m, InputSource stdin, OutputSink stdout,
OutputSink stderr) =>
CreateProcess -> m (stdin, stdout, stderr, StreamingProcessHandle)
streamingProcess CreateProcess
cp = IO (stdin, stdout, stderr, StreamingProcessHandle)
-> m (stdin, stdout, stderr, StreamingProcessHandle)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (stdin, stdout, stderr, StreamingProcessHandle)
-> m (stdin, stdout, stderr, StreamingProcessHandle))
-> IO (stdin, stdout, stderr, StreamingProcessHandle)
-> m (stdin, stdout, stderr, StreamingProcessHandle)
forall a b. (a -> b) -> a -> b
$ do
let (Maybe Handle -> IO stdin
getStdin, Maybe StdStream
stdinStream) = (Maybe Handle -> IO stdin, Maybe StdStream)
forall a. InputSource a => (Maybe Handle -> IO a, Maybe StdStream)
isStdStream
(Maybe Handle -> IO stdout
getStdout, Maybe StdStream
stdoutStream) = (Maybe Handle -> IO stdout, Maybe StdStream)
forall a. OutputSink a => (Maybe Handle -> IO a, Maybe StdStream)
osStdStream
(Maybe Handle -> IO stderr
getStderr, Maybe StdStream
stderrStream) = (Maybe Handle -> IO stderr, Maybe StdStream)
forall a. OutputSink a => (Maybe Handle -> IO a, Maybe StdStream)
osStdStream
#if MIN_VERSION_process(1,2,0)
(Maybe Handle
stdinH, Maybe Handle
stdoutH, Maybe Handle
stderrH, ProcessHandle
ph) <- String
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
PI.createProcess_ String
"streamingProcess" CreateProcess
cp
#else
(stdinH, stdoutH, stderrH, ph) <- createProcess cp
#endif
{ std_in = fromMaybe (std_in cp) stdinStream
, std_out = fromMaybe (std_out cp) stdoutStream
, std_err = fromMaybe (std_err cp) stderrStream
}
TMVar ExitCode
ec <- STM (TMVar ExitCode) -> IO (TMVar ExitCode)
forall a. STM a -> IO a
atomically STM (TMVar ExitCode)
forall a. STM (TMVar a)
newEmptyTMVar
ThreadId
_ <- ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId
forkIOWithUnmask (((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId)
-> ((forall a. IO a -> IO a) -> IO ()) -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
_unmask -> IO ExitCode -> IO (Either SomeException ExitCode)
forall e a. Exception e => IO a -> IO (Either e a)
try (ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
ph)
IO (Either SomeException ExitCode)
-> (Either SomeException ExitCode -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= STM () -> IO ()
forall a. STM a -> IO a
atomically
(STM () -> IO ())
-> (Either SomeException ExitCode -> STM ())
-> Either SomeException ExitCode
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TMVar ExitCode -> ExitCode -> STM ()
forall a. TMVar a -> a -> STM ()
putTMVar TMVar ExitCode
ec
(ExitCode -> STM ())
-> (Either SomeException ExitCode -> ExitCode)
-> Either SomeException ExitCode
-> STM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SomeException -> ExitCode)
-> (ExitCode -> ExitCode)
-> Either SomeException ExitCode
-> ExitCode
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
(SomeException -> a
forall {a}. SomeException -> a
forall a e. Exception e => e -> a
throw :: SomeException -> a)
ExitCode -> ExitCode
forall a. a -> a
id
let close :: IO ()
close =
Maybe Handle -> IO ()
mclose Maybe Handle
stdinH IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
`finally` Maybe Handle -> IO ()
mclose Maybe Handle
stdoutH IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
`finally` Maybe Handle -> IO ()
mclose Maybe Handle
stderrH
where
mclose :: Maybe Handle -> IO ()
mclose = IO () -> (Handle -> IO ()) -> Maybe Handle -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Handle -> IO ()
hClose
(,,,)
(stdin
-> stdout
-> stderr
-> StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
-> IO stdin
-> IO
(stdout
-> stderr
-> StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
A.<$> Maybe Handle -> IO stdin
getStdin Maybe Handle
stdinH
IO
(stdout
-> stderr
-> StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
-> IO stdout
-> IO
(stderr
-> StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
A.<*> Maybe Handle -> IO stdout
getStdout Maybe Handle
stdoutH
IO
(stderr
-> StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
-> IO stderr
-> IO
(StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Handle -> IO stderr
getStderr Maybe Handle
stderrH
IO
(StreamingProcessHandle
-> (stdin, stdout, stderr, StreamingProcessHandle))
-> IO StreamingProcessHandle
-> IO (stdin, stdout, stderr, StreamingProcessHandle)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StreamingProcessHandle -> IO StreamingProcessHandle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ProcessHandle -> TMVar ExitCode -> IO () -> StreamingProcessHandle
StreamingProcessHandle ProcessHandle
ph TMVar ExitCode
ec IO ()
close)
closeStreamingProcessHandle :: MonadIO m => StreamingProcessHandle -> m ()
closeStreamingProcessHandle :: forall (m :: * -> *). MonadIO m => StreamingProcessHandle -> m ()
closeStreamingProcessHandle (StreamingProcessHandle ProcessHandle
_ TMVar ExitCode
_ IO ()
f) = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ()
f
data ProcessExitedUnsuccessfully = ProcessExitedUnsuccessfully CreateProcess ExitCode
deriving Typeable
instance Show ProcessExitedUnsuccessfully where
show :: ProcessExitedUnsuccessfully -> String
show (ProcessExitedUnsuccessfully CreateProcess
cp ExitCode
ec) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"Process exited with "
, ExitCode -> String
forall a. Show a => a -> String
show ExitCode
ec
, String
": "
, CmdSpec -> String
showCmdSpec (CreateProcess -> CmdSpec
cmdspec CreateProcess
cp)
]
where
showCmdSpec :: CmdSpec -> String
showCmdSpec (ShellCommand String
str) = String
str
showCmdSpec (RawCommand String
x [String]
xs) = [String] -> String
unwords (String
xString -> [String] -> [String]
forall a. a -> [a] -> [a]
:ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
showArg [String]
xs)
showArg :: ShowS
showArg String
x
| (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') String
x = ShowS
forall a. Show a => a -> String
show String
x
| Bool
otherwise = String
x
instance Exception ProcessExitedUnsuccessfully
withCheckedProcess :: ( InputSource stdin
, OutputSink stderr
, OutputSink stdout
, MonadIO m
)
=> CreateProcess
-> (stdin -> stdout -> stderr -> m b)
-> m b
withCheckedProcess :: forall stdin stderr stdout (m :: * -> *) b.
(InputSource stdin, OutputSink stderr, OutputSink stdout,
MonadIO m) =>
CreateProcess -> (stdin -> stdout -> stderr -> m b) -> m b
withCheckedProcess CreateProcess
cp stdin -> stdout -> stderr -> m b
f = do
(stdin
x, stdout
y, stderr
z, StreamingProcessHandle
sph) <- CreateProcess -> m (stdin, stdout, stderr, StreamingProcessHandle)
forall (m :: * -> *) stdin stdout stderr.
(MonadIO m, InputSource stdin, OutputSink stdout,
OutputSink stderr) =>
CreateProcess -> m (stdin, stdout, stderr, StreamingProcessHandle)
streamingProcess CreateProcess
cp
b
res <- stdin -> stdout -> stderr -> m b
f stdin
x stdout
y stderr
z
IO b -> m b
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> m b) -> IO b -> m b
forall a b. (a -> b) -> a -> b
$ do
ExitCode
ec <- StreamingProcessHandle -> IO ExitCode
forall (m :: * -> *).
MonadIO m =>
StreamingProcessHandle -> m ExitCode
waitForStreamingProcess StreamingProcessHandle
sph IO ExitCode -> IO () -> IO ExitCode
forall a b. IO a -> IO b -> IO a
`finally` StreamingProcessHandle -> IO ()
forall (m :: * -> *). MonadIO m => StreamingProcessHandle -> m ()
closeStreamingProcessHandle StreamingProcessHandle
sph
if ExitCode
ec ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
then b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
res
else ProcessExitedUnsuccessfully -> IO b
forall e a. Exception e => e -> IO a
throwIO (ProcessExitedUnsuccessfully -> IO b)
-> ProcessExitedUnsuccessfully -> IO b
forall a b. (a -> b) -> a -> b
$ CreateProcess -> ExitCode -> ProcessExitedUnsuccessfully
ProcessExitedUnsuccessfully CreateProcess
cp ExitCode
ec