git-annex/Utility/CoProcess.hs

95 lines
2.5 KiB
Haskell
Raw Normal View History

2012-02-20 19:20:36 +00:00
{- Interface for running a shell command as a coprocess,
- sending it queries and getting back results.
-
- Copyright 2012-2013 Joey Hess <joey@kitenet.net>
2012-02-20 19:20:36 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
2013-05-12 03:11:56 +00:00
{-# LANGUAGE CPP #-}
2012-02-20 19:20:36 +00:00
module Utility.CoProcess (
CoProcessHandle,
start,
stop,
2013-05-12 03:11:56 +00:00
query,
rawMode
2012-02-20 19:20:36 +00:00
) where
import Common
import Control.Concurrent.MVar
2012-02-20 19:20:36 +00:00
type CoProcessHandle = MVar CoProcessState
data CoProcessState = CoProcessState
{ coProcessPid :: ProcessHandle
, coProcessTo :: Handle
, coProcessFrom :: Handle
, coProcessSpec :: CoProcessSpec
}
data CoProcessSpec = CoProcessSpec
{ coProcessNumRestarts :: Int
, coProcessCmd :: FilePath
, coProcessParams :: [String]
, coProcessEnv :: Maybe [(String, String)]
}
start :: Int -> FilePath -> [String] -> Maybe [(String, String)] -> IO CoProcessHandle
start numrestarts cmd params env = do
s <- start' $ CoProcessSpec numrestarts cmd params env
newMVar s
start' :: CoProcessSpec -> IO CoProcessState
start' s = do
(pid, from, to) <- startInteractiveProcess (coProcessCmd s) (coProcessParams s) (coProcessEnv s)
return $ CoProcessState pid to from s
2012-02-20 19:20:36 +00:00
stop :: CoProcessHandle -> IO ()
stop ch = do
s <- readMVar ch
hClose $ coProcessTo s
hClose $ coProcessFrom s
let p = proc (coProcessCmd $ coProcessSpec s) (coProcessParams $ coProcessSpec s)
forceSuccessProcess p (coProcessPid s)
2012-02-20 19:20:36 +00:00
{- To handle a restartable process, any IO exception thrown by the send and
- receive actions are assumed to mean communication with the process
- failed, and the failed action is re-run with a new process. -}
2012-02-20 19:20:36 +00:00
query :: CoProcessHandle -> (Handle -> IO a) -> (Handle -> IO b) -> IO b
query ch send receive = do
s <- readMVar ch
restartable s (send $ coProcessTo s) $ const $
restartable s (hFlush $ coProcessTo s) $ const $
restartable s (receive $ coProcessFrom s) $
return
where
restartable s a cont
| coProcessNumRestarts (coProcessSpec s) > 0 =
maybe restart cont =<< catchMaybeIO a
| otherwise = cont =<< a
restart = do
s <- takeMVar ch
void $ catchMaybeIO $ do
hClose $ coProcessTo s
hClose $ coProcessFrom s
void $ waitForProcess $ coProcessPid s
s' <- start' $ (coProcessSpec s)
{ coProcessNumRestarts = coProcessNumRestarts (coProcessSpec s) - 1 }
putMVar ch s'
query ch send receive
2013-05-12 03:11:56 +00:00
rawMode :: CoProcessHandle -> IO CoProcessHandle
rawMode ch = do
s <- readMVar ch
raw $ coProcessFrom s
raw $ coProcessTo s
2013-05-12 03:11:56 +00:00
return ch
where
raw h = do
fileEncoding h
#ifdef mingw32_HOST_OS
2013-05-12 03:11:56 +00:00
hSetNewlineMode h noNewlineTranslation
#endif