1{- |
2   Module      : Text.Pandoc.Process
3   Copyright   : Copyright (C) 2013-2021 John MacFarlane
4   License     : GNU GPL, version 2 or above
5
6   Maintainer  : John MacFarlane <jgm@berkeley.edu>
7   Stability   : alpha
8   Portability : portable
9
10ByteString variant of 'readProcessWithExitCode'.
11-}
12module Text.Pandoc.Process (pipeProcess)
13where
14import Control.Concurrent (MVar, forkIO, killThread, newEmptyMVar, putMVar,
15                           takeMVar)
16import Control.Exception (SomeException (..))
17import qualified Control.Exception as E
18import Control.Monad (unless)
19import Control.DeepSeq (rnf)
20import qualified Data.ByteString.Lazy as BL
21import Foreign.C (Errno (Errno), ePIPE)
22import GHC.IO.Exception (IOErrorType(..), IOException(..))
23import System.Exit (ExitCode (..))
24import System.IO (hClose)
25import System.Process
26
27{- |
28Version of 'System.Process.readProcessWithExitCode' that uses lazy bytestrings
29instead of strings and allows setting environment variables.
30
31@readProcessWithExitCode@ creates an external process, reads its
32standard output strictly, waits until the process
33terminates, and then returns the 'ExitCode' of the process
34and the standard output.  stderr is inherited from the parent.
35
36If an asynchronous exception is thrown to the thread executing
37@readProcessWithExitCode@, the forked process will be terminated and
38@readProcessWithExitCode@ will wait (block) until the process has been
39terminated.
40
41This function was adapted from @readProcessWithExitCode@ of module
42System.Process, package process-1.6.3.0. The original code is BSD
43licensed and © University of Glasgow 2004-2008.
44-}
45pipeProcess
46    :: Maybe [(String, String)] -- ^ environment variables
47    -> FilePath                 -- ^ Filename of the executable (see 'proc' for details)
48    -> [String]                 -- ^ any arguments
49    -> BL.ByteString            -- ^ standard input
50    -> IO (ExitCode,BL.ByteString) -- ^ exitcode, stdout
51pipeProcess mbenv cmd args input = do
52    let cp_opts = (proc cmd args)
53                  { env     = mbenv
54                  , std_in  = CreatePipe
55                  , std_out = CreatePipe
56                  , std_err = Inherit
57                  }
58    withCreateProcess cp_opts $
59      \mbInh mbOuth _ pid -> do
60        let (inh, outh) =
61             case (mbInh, mbOuth) of
62                  (Just i, Just o) -> (i, o)
63                  (Nothing, _)     -> error "withCreateProcess no inh"
64                  (_, Nothing)     -> error "withCreateProcess no outh"
65
66        out <- BL.hGetContents outh
67
68        -- fork off threads to start consuming stdout & stderr
69        withForkWait (E.evaluate $ rnf out) $ \waitOut -> do
70
71          -- now write any input
72          unless (BL.null input) $
73            ignoreSigPipe $ BL.hPutStr inh input
74          -- hClose performs implicit hFlush, and thus may trigger a SIGPIPE
75          ignoreSigPipe $ hClose inh
76
77          -- wait on the output
78          waitOut
79
80          hClose outh
81
82        -- wait on the process
83        ex <- waitForProcess pid
84
85        return (ex, out)
86
87-- | Fork a thread while doing something else, but kill it if there's an
88-- exception.
89--
90-- This is important in the cases above because we want to kill the thread
91-- that is holding the Handle lock, because when we clean up the process we
92-- try to close that handle, which could otherwise deadlock.
93--
94-- This function was copied verbatim from module System.Process of package
95-- process-1.6.3.0.
96withForkWait :: IO () -> (IO () ->  IO a) -> IO a
97withForkWait async body = do
98  waitVar <- newEmptyMVar :: IO (MVar (Either SomeException ()))
99  E.mask $ \restore -> do
100    tid <- forkIO $ E.try (restore async) >>= putMVar waitVar
101    let wait = takeMVar waitVar >>= either E.throwIO return
102    restore (body wait) `E.onException` killThread tid
103
104-- This function was copied verbatim from module System.Process of package
105-- process-1.6.3.0.
106ignoreSigPipe :: IO () -> IO ()
107ignoreSigPipe = E.handle $ \e ->
108  case e of
109    IOError { ioe_type  = ResourceVanished
110            , ioe_errno = Just ioe }
111      | Errno ioe == ePIPE -> return ()
112    _ -> E.throwIO e
113