module Data.Conduit.Process.Typed
(
createSink
, createSource
, withProcess
, withProcess_
, withLoggedProcess_
, module System.Process.Typed
) where
import System.Process.Typed hiding (withProcess, withProcess_)
import qualified System.Process.Typed as P
import Data.Conduit (ConduitM, (.|), runConduit)
import qualified Data.Conduit as C
import qualified Data.Conduit.Binary as CB
import Control.Monad.IO.Unlift
import qualified Data.ByteString as S
import System.IO (hClose)
import qualified Data.Conduit.List as CL
import qualified Data.ByteString.Lazy as BL
import Data.IORef (IORef, newIORef, readIORef, modifyIORef)
import Control.Exception (throwIO, catch)
import Control.Concurrent.Async (concurrently)
createSink :: MonadIO m => StreamSpec 'STInput (ConduitM S.ByteString o m ())
createSink =
(\h -> C.addCleanup (\_ -> liftIO $ hClose h) (CB.sinkHandle h))
`fmap` createPipe
createSource :: MonadIO m => StreamSpec 'STOutput (ConduitM i S.ByteString m ())
createSource =
(\h -> C.addCleanup (\_ -> liftIO $ hClose h) (CB.sourceHandle h))
`fmap` createPipe
createSourceLogged
:: MonadIO m
=> IORef ([S.ByteString] -> [S.ByteString])
-> StreamSpec 'STOutput (ConduitM i S.ByteString m ())
createSourceLogged ref =
(\h ->
( CB.sourceHandle h
.| CL.iterM (\bs -> liftIO $ modifyIORef ref (. (bs:))))
)
`fmap` createPipe
withProcess
:: MonadUnliftIO m
=> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a)
-> m a
withProcess pc f = withRunInIO $ \run -> P.withProcess pc (run . f)
withProcess_
:: MonadUnliftIO m
=> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a)
-> m a
withProcess_ pc f = withRunInIO $ \run -> P.withProcess_ pc (run . f)
withLoggedProcess_
:: MonadUnliftIO m
=> ProcessConfig stdin stdoutIgnored stderrIgnored
-> (Process stdin (ConduitM () S.ByteString m ()) (ConduitM () S.ByteString m ()) -> m a)
-> m a
withLoggedProcess_ pc inner = withUnliftIO $ \u -> do
stdoutBuffer <- newIORef id
stderrBuffer <- newIORef id
let pc' = setStdout (createSourceLogged stdoutBuffer)
$ setStderr (createSourceLogged stderrBuffer) pc
P.withProcess pc' $ \p -> do
a <- unliftIO u $ inner p
let drain src = unliftIO u (runConduit (src .| CL.sinkNull))
((), ()) <- drain (getStdout p) `concurrently`
drain (getStderr p)
checkExitCode p `catch` \ece -> do
stdout <- readIORef stdoutBuffer
stderr <- readIORef stderrBuffer
throwIO ece
{ eceStdout = BL.fromChunks $ stdout []
, eceStderr = BL.fromChunks $ stderr []
}
return a