module RawFilePath.Process.Common
( Process(..)
, ProcessConf(..)
, proc
, processStdin
, processStdout
, processStderr
, StreamType
, mbFd
, willCreateHandle
, CreatePipe(..)
, Inherit(..)
, NoStream(..)
, UseHandle(..)
, setStdin
, setStdout
, setStderr
, PHANDLE
, ProcessHandle__(..)
, modifyProcessHandle
, withProcessHandle
, fdStdin
, fdStdout
, fdStderr
, mbPipe
) where
import RawFilePath.Import
import System.Posix.Internals (FD)
import qualified GHC.IO.FD as FD
data ProcessConf stdin stdout stderr = ProcessConf
{ cmdargs :: [ByteString]
, cwd :: Maybe RawFilePath
, env :: Maybe [(ByteString, ByteString)]
, cfgStdin :: stdin
, cfgStdout :: stdout
, cfgStderr :: stderr
, closeFds :: Bool
, createGroup :: Bool
, delegateCtlc :: Bool
, createNewConsole :: Bool
, newSession :: Bool
, childGroup :: Maybe GroupID
, childUser :: Maybe UserID
}
proc
:: RawFilePath
-> [ByteString]
-> ProcessConf Inherit Inherit Inherit
proc cmd args = ProcessConf
{ cmdargs = cmd : args
, cwd = Nothing
, env = Nothing
, cfgStdin = Inherit
, cfgStdout = Inherit
, cfgStderr = Inherit
, closeFds = False
, createGroup = False
, delegateCtlc = False
, createNewConsole = False
, newSession = False
, childGroup = Nothing
, childUser = Nothing
}
setStdin
:: (StreamType newStdin)
=> ProcessConf oldStdin stdout stderr
-> newStdin
-> ProcessConf newStdin stdout stderr
setStdin p newStdin = p { cfgStdin = newStdin }
infixl 4 `setStdin`
setStdout
:: (StreamType newStdout)
=> ProcessConf stdin oldStdout stderr
-> newStdout
-> ProcessConf stdin newStdout stderr
setStdout p newStdout = p { cfgStdout = newStdout }
infixl 4 `setStdout`
setStderr
:: (StreamType newStderr)
=> ProcessConf stdin stdout oldStderr
-> newStderr
-> ProcessConf stdin stdout newStderr
setStderr p newStderr = p { cfgStderr = newStderr }
infixl 4 `setStderr`
data Process stdin stdout stderr = Process
{ procStdin :: Maybe Handle
, procStdout :: Maybe Handle
, procStderr :: Maybe Handle
, phandle :: !(MVar ProcessHandle__)
, mbDelegateCtlc :: !Bool
, waitpidLock :: !(MVar ())
}
processStdin :: Process CreatePipe stdout stderr -> Handle
processStdin Process{..} = fromMaybe err procStdin
where
err = error "This can't happen: stdin is CreatePipe but missing"
processStdout :: Process stdin CreatePipe stderr -> Handle
processStdout Process{..} = fromMaybe err procStdout
where
err = error "This can't happen: stdout is CreatePipe but missing"
processStderr :: Process stdin stdout CreatePipe -> Handle
processStderr Process{..} = fromMaybe err procStderr
where
err = error "This can't happen: stderr is CreatePipe but missing"
data CreatePipe = CreatePipe deriving Show
data Inherit = Inherit deriving Show
data NoStream = NoStream deriving Show
data UseHandle = UseHandle Handle deriving Show
class StreamType c where
mbFd :: FD -> c -> IO FD
willCreateHandle :: c -> Bool
#if __GLASGOW_HASKELL__ >= 780
mbFd = undefined
willCreateHandle = undefined
#endif
instance StreamType CreatePipe where
mbFd _ _ = return (1)
willCreateHandle _ = True
instance StreamType Inherit where
mbFd std _ = return std
willCreateHandle _ = False
instance StreamType NoStream where
mbFd _ _ = return (2)
willCreateHandle _ = False
instance StreamType UseHandle where
mbFd _std (UseHandle hdl) =
withHandle "" hdl $ \Handle__{haDevice=dev,..} -> case cast dev of
Just fd -> do
fd' <- FD.setNonBlockingMode fd False
return (Handle__{haDevice=fd',..}, FD.fdFD fd')
Nothing -> ioError $ mkIOError illegalOperationErrorType
"createProcess" (Just hdl) Nothing
`ioeSetErrorString` "handle is not a file descriptor"
willCreateHandle _ = False
type PHANDLE = CPid
data ProcessHandle__ = OpenHandle PHANDLE
| OpenExtHandle PHANDLE PHANDLE PHANDLE
| ClosedHandle ExitCode
modifyProcessHandle
:: Process stdin stdout stderr
-> (ProcessHandle__ -> IO (ProcessHandle__, a))
-> IO a
modifyProcessHandle p = modifyMVar (phandle p)
withProcessHandle
:: Process stdin stdout stderr -> (ProcessHandle__ -> IO a) -> IO a
withProcessHandle p = withMVar (phandle p)
fdStdin, fdStdout, fdStderr :: FD
fdStdin = 0
fdStdout = 1
fdStderr = 2
mbPipe :: StreamType c => c -> Ptr FD -> IOMode -> IO (Maybe Handle)
mbPipe streamConf pfd mode = if willCreateHandle streamConf
then fmap Just (pfdToHandle pfd mode)
else return Nothing
pfdToHandle :: Ptr FD -> IOMode -> IO Handle
pfdToHandle pfd mode = do
fd <- peek pfd
let filepath = "fd:" ++ show fd
(fD,fd_type) <- FD.mkFD (fromIntegral fd) mode
(Just (Stream,0,0))
False
False
fD' <- FD.setNonBlockingMode fD True
#if __GLASGOW_HASKELL__ >= 704
enc <- getLocaleEncoding
#else
let enc = localeEncoding
#endif
mkHandleFromFD fD' fd_type filepath mode False (Just enc)