module System.Process.Posix
( mkProcessHandle
, translateInternal
, createProcess_Internal
, withCEnvironment
, closePHANDLE
, startDelegateControlC
, endDelegateControlC
, stopDelegateControlC
, isDefaultSignal
, ignoreSignal
, defaultSignal
, c_execvpe
, pPrPr_disableITimers
, createPipeInternal
, createPipeInternalFd
, interruptProcessGroupOfInternal
, runInteractiveProcess_lock
) where
import Control.Concurrent
import Control.Exception
import Data.Bits
import Foreign.C
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable
import System.IO.Unsafe
import Control.Monad
import Data.Char
import System.IO
import System.Posix.Process.Internals ( pPrPr_disableITimers, c_execvpe )
import System.Posix.Types
import System.Posix.Internals
import GHC.IO.Exception
import System.Posix.Signals as Sig
import qualified System.Posix.IO as Posix
import System.Posix.Process (getProcessGroupIDOf)
import System.Process.Common hiding (mb_delegate_ctlc)
#include "HsProcessConfig.h"
#include "processFlags.h"
mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle
mkProcessHandle p mb_delegate_ctlc = do
m <- newMVar (OpenHandle p)
l <- newMVar ()
return (ProcessHandle m mb_delegate_ctlc l)
closePHANDLE :: PHANDLE -> IO ()
closePHANDLE _ = return ()
commandToProcess :: CmdSpec -> (FilePath, [String])
commandToProcess (ShellCommand string) = ("/bin/sh", ["-c", string])
commandToProcess (RawCommand cmd args) = (cmd, args)
translateInternal :: String -> String
translateInternal "" = "''"
translateInternal str
| all goodChar str = str
| otherwise = '\'' : foldr escape "'" str
where escape '\'' = showString "'\\''"
escape c = showChar c
goodChar c = isAlphaNum c || c `elem` "-_.,/"
withCEnvironment :: [(String,String)] -> (Ptr CString -> IO a) -> IO a
withCEnvironment envir act =
let env' = map (\(name, val) -> name ++ ('=':val)) envir
in withMany withFilePath env' (\pEnv -> withArray0 nullPtr pEnv act)
createProcess_Internal
:: String
-> CreateProcess
-> IO ProcRetHandles
createProcess_Internal fun
CreateProcess{ cmdspec = cmdsp,
cwd = mb_cwd,
env = mb_env,
std_in = mb_stdin,
std_out = mb_stdout,
std_err = mb_stderr,
close_fds = mb_close_fds,
create_group = mb_create_group,
delegate_ctlc = mb_delegate_ctlc,
detach_console = mb_detach_console,
create_new_console = mb_create_new_console,
new_session = mb_new_session,
child_group = mb_child_group,
child_user = mb_child_user }
= do
let (cmd,args) = commandToProcess cmdsp
withFilePathException cmd $
alloca $ \ pfdStdInput ->
alloca $ \ pfdStdOutput ->
alloca $ \ pfdStdError ->
alloca $ \ pFailedDoing ->
maybeWith withCEnvironment mb_env $ \pEnv ->
maybeWith withFilePath mb_cwd $ \pWorkDir ->
maybeWith with mb_child_group $ \pChildGroup ->
maybeWith with mb_child_user $ \pChildUser ->
withMany withFilePath (cmd:args) $ \cstrs ->
withArray0 nullPtr cstrs $ \pargs -> do
fdin <- mbFd fun fd_stdin mb_stdin
fdout <- mbFd fun fd_stdout mb_stdout
fderr <- mbFd fun fd_stderr mb_stderr
when mb_delegate_ctlc
startDelegateControlC
let flags = (if mb_close_fds then RUN_PROCESS_IN_CLOSE_FDS else 0)
.|.(if mb_create_group then RUN_PROCESS_IN_NEW_GROUP else 0)
.|.(if mb_detach_console then RUN_PROCESS_DETACHED else 0)
.|.(if mb_create_new_console then RUN_PROCESS_NEW_CONSOLE else 0)
.|.(if mb_new_session then RUN_PROCESS_NEW_SESSION else 0)
.|.(if mb_delegate_ctlc then RESET_INT_QUIT_HANDLERS else 0)
proc_handle <- withMVar runInteractiveProcess_lock $ \_ ->
c_runInteractiveProcess pargs pWorkDir pEnv
fdin fdout fderr
pfdStdInput pfdStdOutput pfdStdError
pChildGroup pChildUser
flags
pFailedDoing
when (proc_handle == 1) $ do
cFailedDoing <- peek pFailedDoing
failedDoing <- peekCString cFailedDoing
when mb_delegate_ctlc
stopDelegateControlC
throwErrno (fun ++ ": " ++ failedDoing)
hndStdInput <- mbPipe mb_stdin pfdStdInput WriteMode
hndStdOutput <- mbPipe mb_stdout pfdStdOutput ReadMode
hndStdError <- mbPipe mb_stderr pfdStdError ReadMode
ph <- mkProcessHandle proc_handle mb_delegate_ctlc
return ProcRetHandles { hStdInput = hndStdInput
, hStdOutput = hndStdOutput
, hStdError = hndStdError
, procHandle = ph
}
runInteractiveProcess_lock :: MVar ()
runInteractiveProcess_lock = unsafePerformIO $ newMVar ()
runInteractiveProcess_delegate_ctlc :: MVar (Maybe (Int, Sig.Handler, Sig.Handler))
runInteractiveProcess_delegate_ctlc = unsafePerformIO $ newMVar Nothing
startDelegateControlC :: IO ()
startDelegateControlC =
modifyMVar_ runInteractiveProcess_delegate_ctlc $ \delegating -> do
case delegating of
Nothing -> do
old_int <- installHandler sigINT Ignore Nothing
old_quit <- installHandler sigQUIT Ignore Nothing
return (Just (1, old_int, old_quit))
Just (count, old_int, old_quit) -> do
let !count' = count + 1
return (Just (count', old_int, old_quit))
stopDelegateControlC :: IO ()
stopDelegateControlC =
modifyMVar_ runInteractiveProcess_delegate_ctlc $ \delegating -> do
case delegating of
Just (1, old_int, old_quit) -> do
_ <- installHandler sigINT old_int Nothing
_ <- installHandler sigQUIT old_quit Nothing
return Nothing
Just (count, old_int, old_quit) -> do
let !count' = count 1
return (Just (count', old_int, old_quit))
Nothing -> return Nothing
endDelegateControlC :: ExitCode -> IO ()
endDelegateControlC exitCode = do
stopDelegateControlC
case exitCode of
ExitFailure n | isSigIntQuit n -> throwIO UserInterrupt
_ -> return ()
where
isSigIntQuit n = sig == sigINT || sig == sigQUIT
where
sig = fromIntegral (n)
foreign import ccall unsafe "runInteractiveProcess"
c_runInteractiveProcess
:: Ptr CString
-> CString
-> Ptr CString
-> FD
-> FD
-> FD
-> Ptr FD
-> Ptr FD
-> Ptr FD
-> Ptr CGid
-> Ptr CUid
-> CInt
-> Ptr CString
-> IO PHANDLE
ignoreSignal, defaultSignal :: CLong
ignoreSignal = CONST_SIG_IGN
defaultSignal = CONST_SIG_DFL
isDefaultSignal :: CLong -> Bool
isDefaultSignal = (== defaultSignal)
createPipeInternal :: IO (Handle, Handle)
createPipeInternal = do
(readfd, writefd) <- Posix.createPipe
readh <- Posix.fdToHandle readfd
writeh <- Posix.fdToHandle writefd
return (readh, writeh)
createPipeInternalFd :: IO (FD, FD)
createPipeInternalFd = do
(Fd readfd, Fd writefd) <- Posix.createPipe
return (readfd, writefd)
interruptProcessGroupOfInternal
:: ProcessHandle
-> IO ()
interruptProcessGroupOfInternal ph = do
withProcessHandle ph $ \p_ -> do
case p_ of
OpenExtHandle{} -> return ()
ClosedHandle _ -> return ()
OpenHandle h -> do
pgid <- getProcessGroupIDOf h
signalProcessGroup sigINT pgid