{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
module System.Process.CommunicationHandle
(
CommunicationHandle
, openCommunicationHandleRead
, openCommunicationHandleWrite
, closeCommunicationHandle
, createWeReadTheyWritePipe
, createTheyReadWeWritePipe
, readCreateProcessWithExitCodeCommunicationHandle
)
where
import GHC.IO.Handle (Handle)
import System.Process.CommunicationHandle.Internal
import System.Process.Internals
( CreateProcess(..), ignoreSigPipe, withForkWait )
import System.Process
( withCreateProcess, waitForProcess )
import GHC.IO (evaluate)
import GHC.IO.Handle (hClose)
import System.Exit (ExitCode)
import Control.DeepSeq (NFData, rnf)
openCommunicationHandleRead :: CommunicationHandle -> IO Handle
openCommunicationHandleRead :: CommunicationHandle -> IO Handle
openCommunicationHandleRead = Bool -> CommunicationHandle -> IO Handle
useCommunicationHandle Bool
True
openCommunicationHandleWrite :: CommunicationHandle -> IO Handle
openCommunicationHandleWrite :: CommunicationHandle -> IO Handle
openCommunicationHandleWrite = Bool -> CommunicationHandle -> IO Handle
useCommunicationHandle Bool
False
createWeReadTheyWritePipe
:: IO (Handle, CommunicationHandle)
createWeReadTheyWritePipe :: IO (Handle, CommunicationHandle)
createWeReadTheyWritePipe =
(forall a. (a, a) -> (a, a))
-> Bool -> IO (Handle, CommunicationHandle)
createCommunicationPipe (a, a) -> (a, a)
forall a. a -> a
forall a. (a, a) -> (a, a)
id Bool
False
createTheyReadWeWritePipe
:: IO (CommunicationHandle, Handle)
createTheyReadWeWritePipe :: IO (CommunicationHandle, Handle)
createTheyReadWeWritePipe =
(Handle, CommunicationHandle) -> (CommunicationHandle, Handle)
forall {b} {a}. (b, a) -> (a, b)
sw ((Handle, CommunicationHandle) -> (CommunicationHandle, Handle))
-> IO (Handle, CommunicationHandle)
-> IO (CommunicationHandle, Handle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. (a, a) -> (a, a))
-> Bool -> IO (Handle, CommunicationHandle)
createCommunicationPipe (a, a) -> (a, a)
forall a. (a, a) -> (a, a)
forall {b} {a}. (b, a) -> (a, b)
sw Bool
False
where
sw :: (b, a) -> (a, b)
sw (b
a,a
b) = (a
b,b
a)
readCreateProcessWithExitCodeCommunicationHandle
:: NFData a
=> ((CommunicationHandle, CommunicationHandle) -> CreateProcess)
-> (Handle -> IO a)
-> (Handle -> IO ())
-> IO (ExitCode, a)
readCreateProcessWithExitCodeCommunicationHandle :: forall a.
NFData a =>
((CommunicationHandle, CommunicationHandle) -> CreateProcess)
-> (Handle -> IO a) -> (Handle -> IO ()) -> IO (ExitCode, a)
readCreateProcessWithExitCodeCommunicationHandle (CommunicationHandle, CommunicationHandle) -> CreateProcess
mkProg Handle -> IO a
readAction Handle -> IO ()
writeAction = do
(chTheyRead, hWeWrite ) <- IO (CommunicationHandle, Handle)
createTheyReadWeWritePipe
(hWeRead , chTheyWrite) <- createWeReadTheyWritePipe
let cp = (CommunicationHandle, CommunicationHandle) -> CreateProcess
mkProg (CommunicationHandle
chTheyRead, CommunicationHandle
chTheyWrite)
withCreateProcess cp $ \ Maybe Handle
_ Maybe Handle
_ Maybe Handle
_ ProcessHandle
ph -> do
CommunicationHandle -> IO ()
closeCommunicationHandle CommunicationHandle
chTheyWrite
CommunicationHandle -> IO ()
closeCommunicationHandle CommunicationHandle
chTheyRead
output <- Handle -> IO a
readAction Handle
hWeRead
withForkWait (evaluate $ rnf output) $ \ IO ()
waitOut -> do
IO () -> IO ()
ignoreSigPipe (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle -> IO ()
writeAction Handle
hWeWrite
IO () -> IO ()
ignoreSigPipe (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle -> IO ()
hClose Handle
hWeWrite
IO ()
waitOut
Handle -> IO ()
hClose Handle
hWeRead
ex <- waitForProcess ph
return (ex, output)