module Foreign.Nix.Shellout.Helpers where
import Protolude hiding (async, wait)
import Foreign.Nix.Shellout.Types
import qualified System.Process as P
import qualified Data.Text.IO as TIO
import qualified Data.Text as T
import qualified System.IO as SIO
import GHC.IO.Exception (IOErrorType(..), IOException(..))
import Foreign.C.Error (Errno(Errno), ePIPE)
readProcess :: ((Text, Text) -> ExitCode -> ExceptT e IO a)
-> Text
-> [Text]
-> NixAction e a
readProcess with exec args = NixAction $ do
(exc, out, err) <- liftIO
$ readCreateProcessWithExitCodeAndEncoding
(P.proc (toS exec) (map toS args)) SIO.utf8 ""
withExceptT (err,) $ with (out, err) exc
readCreateProcessWithExitCodeAndEncoding
:: P.CreateProcess
-> SIO.TextEncoding
-> Text
-> IO (ExitCode, Text, Text)
readCreateProcessWithExitCodeAndEncoding cp encoding input = do
let cp_opts = cp
{ P.std_in = P.CreatePipe
, P.std_out = P.CreatePipe
, P.std_err = P.CreatePipe }
P.withCreateProcess cp_opts $
\(Just inh) (Just outh) (Just errh) ph -> do
SIO.hSetEncoding outh encoding
SIO.hSetEncoding errh encoding
SIO.hSetEncoding inh encoding
out <- TIO.hGetContents outh
err <- TIO.hGetContents errh
withForkWait (evaluate $ rnf out) $ \waitOut ->
withForkWait (evaluate $ rnf err) $ \waitErr -> do
unless (T.null input) $
ignoreSigPipe $ hPutStr inh input
ignoreSigPipe $ SIO.hClose inh
waitOut
waitErr
SIO.hClose outh
SIO.hClose errh
ex <- P.waitForProcess ph
return (ex, out, err)
withForkWait :: IO () -> (IO () -> IO a) -> IO a
withForkWait async body = do
waitVar <- newEmptyMVar :: IO (MVar (Either SomeException ()))
mask $ \restore -> do
tid <- forkIO $ try (restore async) >>= putMVar waitVar
let wait = takeMVar waitVar >>= either throwIO return
restore (body wait) `onException` killThread tid
ignoreSigPipe :: IO () -> IO ()
ignoreSigPipe = handle $ \e -> case e of
IOError { ioe_type = ResourceVanished
, ioe_errno = Just ioe }
| Errno ioe == ePIPE -> return ()
_ -> throwIO e