allow multiple concurrent external special remote processes
Multiple external special remote processes for the same remote will be started as needed when using -J. This should not beak any existing external special remotes, because running multiple git-annex commands at the same time could already start multiple processes for the same external special remotes.
This commit is contained in:
parent
b69dea0ac3
commit
5bf4623a1d
4 changed files with 115 additions and 118 deletions
|
@ -9,6 +9,11 @@ git-annex (6.20160924) UNRELEASED; urgency=medium
|
||||||
* Add "total-size" field to --json-progress output.
|
* Add "total-size" field to --json-progress output.
|
||||||
* Make --json-progress output be shown even when the size of a object
|
* Make --json-progress output be shown even when the size of a object
|
||||||
is not known.
|
is not known.
|
||||||
|
* Multiple external special remote processes for the same remote will be
|
||||||
|
started as needed when using -J. This should not beak any existing
|
||||||
|
external special remotes, because running multiple git-annex commands
|
||||||
|
at the same time could already start multiple processes for the same
|
||||||
|
external special remotes.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Mon, 26 Sep 2016 16:46:19 -0400
|
-- Joey Hess <id@joeyh.name> Mon, 26 Sep 2016 16:46:19 -0400
|
||||||
|
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- External special remote interface.
|
{- External special remote interface.
|
||||||
-
|
-
|
||||||
- Copyright 2013-2015 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2016 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -126,9 +126,8 @@ externalSetup mu _ c gc = do
|
||||||
INITREMOTE_SUCCESS -> Just noop
|
INITREMOTE_SUCCESS -> Just noop
|
||||||
INITREMOTE_FAILURE errmsg -> Just $ error errmsg
|
INITREMOTE_FAILURE errmsg -> Just $ error errmsg
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
withExternalLock external $ \lck ->
|
withExternalState external $
|
||||||
fromExternal lck external externalConfig $
|
liftIO . atomically . readTMVar . externalConfig
|
||||||
liftIO . atomically . readTMVar
|
|
||||||
|
|
||||||
gitConfigSpecialRemote u c'' "externaltype" externaltype
|
gitConfigSpecialRemote u c'' "externaltype" externaltype
|
||||||
return (c'', u)
|
return (c'', u)
|
||||||
|
@ -203,27 +202,28 @@ safely a = go =<< tryNonAsync a
|
||||||
- While the external remote is processing the Request, it may send
|
- While the external remote is processing the Request, it may send
|
||||||
- any number of RemoteRequests, that are handled here.
|
- any number of RemoteRequests, that are handled here.
|
||||||
-
|
-
|
||||||
- Only one request can be made at a time, so locking is used.
|
- An external remote process can only handle one request at a time.
|
||||||
|
- Concurrent requests will start up additional processes.
|
||||||
-
|
-
|
||||||
- May throw exceptions, for example on protocol errors, or
|
- May throw exceptions, for example on protocol errors, or
|
||||||
- when the repository cannot be used.
|
- when the repository cannot be used.
|
||||||
-}
|
-}
|
||||||
handleRequest :: External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
|
handleRequest :: External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
|
||||||
handleRequest external req mp responsehandler =
|
handleRequest external req mp responsehandler =
|
||||||
withExternalLock external $ \lck ->
|
withExternalState external $ \st ->
|
||||||
handleRequest' lck external req mp responsehandler
|
handleRequest' st external req mp responsehandler
|
||||||
|
|
||||||
handleRequest' :: ExternalLock -> External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
|
handleRequest' :: ExternalState -> External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
|
||||||
handleRequest' lck external req mp responsehandler
|
handleRequest' st external req mp responsehandler
|
||||||
| needsPREPARE req = do
|
| needsPREPARE req = do
|
||||||
checkPrepared lck external
|
checkPrepared st external
|
||||||
go
|
go
|
||||||
| otherwise = go
|
| otherwise = go
|
||||||
where
|
where
|
||||||
go = do
|
go = do
|
||||||
sendMessage lck external req
|
sendMessage st external req
|
||||||
loop
|
loop
|
||||||
loop = receiveMessage lck external responsehandler
|
loop = receiveMessage st external responsehandler
|
||||||
(\rreq -> Just $ handleRemoteRequest rreq >> loop)
|
(\rreq -> Just $ handleRemoteRequest rreq >> loop)
|
||||||
(\msg -> Just $ handleAsyncMessage msg >> loop)
|
(\msg -> Just $ handleAsyncMessage msg >> loop)
|
||||||
|
|
||||||
|
@ -234,26 +234,24 @@ handleRequest' lck external req mp responsehandler
|
||||||
handleRemoteRequest (DIRHASH_LOWER k) =
|
handleRemoteRequest (DIRHASH_LOWER k) =
|
||||||
send $ VALUE $ hashDirLower def k
|
send $ VALUE $ hashDirLower def k
|
||||||
handleRemoteRequest (SETCONFIG setting value) =
|
handleRemoteRequest (SETCONFIG setting value) =
|
||||||
fromExternal lck external externalConfig $ \v ->
|
liftIO $ atomically $ do
|
||||||
liftIO $ atomically $ do
|
let v = externalConfig st
|
||||||
m <- takeTMVar v
|
m <- takeTMVar v
|
||||||
putTMVar v $ M.insert setting value m
|
putTMVar v $ M.insert setting value m
|
||||||
handleRemoteRequest (GETCONFIG setting) = do
|
handleRemoteRequest (GETCONFIG setting) = do
|
||||||
value <- fromExternal lck external externalConfig $ \v ->
|
value <- fromMaybe "" . M.lookup setting
|
||||||
fromMaybe "" . M.lookup setting
|
<$> liftIO (atomically $ readTMVar $ externalConfig st)
|
||||||
<$> liftIO (atomically $ readTMVar v)
|
|
||||||
send $ VALUE value
|
send $ VALUE value
|
||||||
handleRemoteRequest (SETCREDS setting login password) = do
|
handleRemoteRequest (SETCREDS setting login password) = do
|
||||||
fromExternal lck external externalConfig $ \v -> do
|
let v = externalConfig st
|
||||||
c <- liftIO $ atomically $ readTMVar v
|
c <- liftIO $ atomically $ readTMVar v
|
||||||
let gc = externalGitConfig external
|
let gc = externalGitConfig external
|
||||||
c' <- setRemoteCredPair encryptionAlreadySetup c gc
|
c' <- setRemoteCredPair encryptionAlreadySetup c gc
|
||||||
(credstorage setting)
|
(credstorage setting)
|
||||||
(Just (login, password))
|
(Just (login, password))
|
||||||
void $ liftIO $ atomically $ swapTMVar v c'
|
void $ liftIO $ atomically $ swapTMVar v c'
|
||||||
handleRemoteRequest (GETCREDS setting) = do
|
handleRemoteRequest (GETCREDS setting) = do
|
||||||
c <- fromExternal lck external externalConfig $
|
c <- liftIO $ atomically $ readTMVar $ externalConfig st
|
||||||
liftIO . atomically . readTMVar
|
|
||||||
let gc = externalGitConfig external
|
let gc = externalGitConfig external
|
||||||
creds <- fromMaybe ("", "") <$>
|
creds <- fromMaybe ("", "") <$>
|
||||||
getRemoteCredPair c gc (credstorage setting)
|
getRemoteCredPair c gc (credstorage setting)
|
||||||
|
@ -286,11 +284,11 @@ handleRequest' lck external req mp responsehandler
|
||||||
send (VALUE "") -- end of list
|
send (VALUE "") -- end of list
|
||||||
handleRemoteRequest (DEBUG msg) = liftIO $ debugM "external" msg
|
handleRemoteRequest (DEBUG msg) = liftIO $ debugM "external" msg
|
||||||
handleRemoteRequest (VERSION _) =
|
handleRemoteRequest (VERSION _) =
|
||||||
sendMessage lck external $ ERROR "too late to send VERSION"
|
sendMessage st external (ERROR "too late to send VERSION")
|
||||||
|
|
||||||
handleAsyncMessage (ERROR err) = error $ "external special remote error: " ++ err
|
handleAsyncMessage (ERROR err) = error $ "external special remote error: " ++ err
|
||||||
|
|
||||||
send = sendMessage lck external
|
send = sendMessage st external
|
||||||
|
|
||||||
credstorage setting = CredPairStorage
|
credstorage setting = CredPairStorage
|
||||||
{ credPairFile = base
|
{ credPairFile = base
|
||||||
|
@ -303,30 +301,28 @@ handleRequest' lck external req mp responsehandler
|
||||||
withurl mk uri = handleRemoteRequest $ mk $
|
withurl mk uri = handleRemoteRequest $ mk $
|
||||||
setDownloader (show uri) OtherDownloader
|
setDownloader (show uri) OtherDownloader
|
||||||
|
|
||||||
sendMessage :: Sendable m => ExternalLock -> External -> m -> Annex ()
|
sendMessage :: Sendable m => ExternalState -> External -> m -> Annex ()
|
||||||
sendMessage lck external m =
|
sendMessage st external m = liftIO $ do
|
||||||
fromExternal lck external externalSend $ \h ->
|
protocolDebug external True line
|
||||||
liftIO $ do
|
hPutStrLn h line
|
||||||
protocolDebug external True line
|
hFlush h
|
||||||
hPutStrLn h line
|
|
||||||
hFlush h
|
|
||||||
where
|
where
|
||||||
line = unwords $ formatMessage m
|
line = unwords $ formatMessage m
|
||||||
|
h = externalSend st
|
||||||
|
|
||||||
{- Waits for a message from the external remote, and passes it to the
|
{- Waits for a message from the external remote, and passes it to the
|
||||||
- apppropriate handler.
|
- apppropriate handler.
|
||||||
-
|
-
|
||||||
- If the handler returns Nothing, this is a protocol error.-}
|
- If the handler returns Nothing, this is a protocol error.-}
|
||||||
receiveMessage
|
receiveMessage
|
||||||
:: ExternalLock
|
:: ExternalState
|
||||||
-> External
|
-> External
|
||||||
-> (Response -> Maybe (Annex a))
|
-> (Response -> Maybe (Annex a))
|
||||||
-> (RemoteRequest -> Maybe (Annex a))
|
-> (RemoteRequest -> Maybe (Annex a))
|
||||||
-> (AsyncMessage -> Maybe (Annex a))
|
-> (AsyncMessage -> Maybe (Annex a))
|
||||||
-> Annex a
|
-> Annex a
|
||||||
receiveMessage lck external handleresponse handlerequest handleasync =
|
receiveMessage st external handleresponse handlerequest handleasync =
|
||||||
go =<< fromExternal lck external externalReceive
|
go =<< liftIO (catchMaybeIO $ hGetLine $ externalReceive st)
|
||||||
(liftIO . catchMaybeIO . hGetLine)
|
|
||||||
where
|
where
|
||||||
go Nothing = protocolError False ""
|
go Nothing = protocolError False ""
|
||||||
go (Just s) = do
|
go (Just s) = do
|
||||||
|
@ -348,39 +344,43 @@ protocolDebug external sendto line = debugM "external" $ unwords
|
||||||
, line
|
, line
|
||||||
]
|
]
|
||||||
|
|
||||||
{- Starts up the external remote if it's not yet running,
|
{- While the action is running, the ExternalState provided to it will not
|
||||||
- and passes a value extracted from its state to an action.
|
- be available to any other calls.
|
||||||
-}
|
-
|
||||||
fromExternal :: ExternalLock -> External -> (ExternalState -> v) -> (v -> Annex a) -> Annex a
|
- Starts up a new process if no ExternalStates are available. -}
|
||||||
fromExternal lck external extractor a =
|
withExternalState :: External -> (ExternalState -> Annex a) -> Annex a
|
||||||
go =<< liftIO (atomically (tryReadTMVar v))
|
withExternalState external = bracket alloc dealloc
|
||||||
where
|
where
|
||||||
go (Just st) = run st
|
|
||||||
go Nothing = do
|
|
||||||
st <- startExternal external
|
|
||||||
void $ liftIO $ atomically $ do
|
|
||||||
void $ tryReadTMVar v
|
|
||||||
putTMVar v st
|
|
||||||
|
|
||||||
{- Handle initial protocol startup; check the VERSION
|
|
||||||
- the remote sends. -}
|
|
||||||
receiveMessage lck external
|
|
||||||
(const Nothing)
|
|
||||||
(checkVersion lck external)
|
|
||||||
(const Nothing)
|
|
||||||
|
|
||||||
run st
|
|
||||||
|
|
||||||
run st = a $ extractor st
|
|
||||||
v = externalState external
|
v = externalState external
|
||||||
|
|
||||||
{- Starts an external remote process running, but does not handle checking
|
alloc = do
|
||||||
- VERSION, etc. -}
|
ms <- liftIO $ atomically $ do
|
||||||
|
l <- takeTMVar v
|
||||||
|
case l of
|
||||||
|
[] -> do
|
||||||
|
putTMVar v l
|
||||||
|
return Nothing
|
||||||
|
(st:rest) -> do
|
||||||
|
putTMVar v rest
|
||||||
|
return (Just st)
|
||||||
|
maybe (startExternal external) return ms
|
||||||
|
|
||||||
|
dealloc st = liftIO $ atomically $ do
|
||||||
|
l <- takeTMVar v
|
||||||
|
putTMVar v (st:l)
|
||||||
|
|
||||||
|
{- Starts an external remote process running, and checks VERSION. -}
|
||||||
startExternal :: External -> Annex ExternalState
|
startExternal :: External -> Annex ExternalState
|
||||||
startExternal external = do
|
startExternal external = do
|
||||||
errrelayer <- mkStderrRelayer
|
errrelayer <- mkStderrRelayer
|
||||||
g <- Annex.gitRepo
|
st <- start errrelayer =<< Annex.gitRepo
|
||||||
liftIO $ do
|
receiveMessage st external
|
||||||
|
(const Nothing)
|
||||||
|
(checkVersion st external)
|
||||||
|
(const Nothing)
|
||||||
|
return st
|
||||||
|
where
|
||||||
|
start errrelayer g = liftIO $ do
|
||||||
(cmd, ps) <- findShellCommand basecmd
|
(cmd, ps) <- findShellCommand basecmd
|
||||||
let basep = (proc cmd (toCommand ps))
|
let basep = (proc cmd (toCommand ps))
|
||||||
{ std_in = CreatePipe
|
{ std_in = CreatePipe
|
||||||
|
@ -395,17 +395,18 @@ startExternal external = do
|
||||||
fileEncoding herr
|
fileEncoding herr
|
||||||
stderrelay <- async $ errrelayer herr
|
stderrelay <- async $ errrelayer herr
|
||||||
checkearlytermination =<< getProcessExitCode pid
|
checkearlytermination =<< getProcessExitCode pid
|
||||||
cv <- atomically $ newTMVar $ externalDefaultConfig external
|
cv <- newTMVarIO $ externalDefaultConfig external
|
||||||
|
pv <- newTMVarIO Unprepared
|
||||||
return $ ExternalState
|
return $ ExternalState
|
||||||
{ externalSend = hin
|
{ externalSend = hin
|
||||||
, externalReceive = hout
|
, externalReceive = hout
|
||||||
, externalShutdown = do
|
, externalShutdown = do
|
||||||
cancel stderrelay
|
cancel stderrelay
|
||||||
void $ waitForProcess pid
|
void $ waitForProcess pid
|
||||||
, externalPrepared = Unprepared
|
, externalPrepared = pv
|
||||||
, externalConfig = cv
|
, externalConfig = cv
|
||||||
}
|
}
|
||||||
where
|
|
||||||
basecmd = externalRemoteProgram $ externalType external
|
basecmd = externalRemoteProgram $ externalType external
|
||||||
|
|
||||||
propgit g p = do
|
propgit g p = do
|
||||||
|
@ -422,12 +423,17 @@ startExternal external = do
|
||||||
error $ basecmd ++ " is not installed in PATH (" ++ path ++ ")"
|
error $ basecmd ++ " is not installed in PATH (" ++ path ++ ")"
|
||||||
)
|
)
|
||||||
|
|
||||||
|
-- Note: Does not stop any externals that have a withExternalState
|
||||||
|
-- action currently running.
|
||||||
stopExternal :: External -> Annex ()
|
stopExternal :: External -> Annex ()
|
||||||
stopExternal external = liftIO $ stop =<< atomically (tryReadTMVar v)
|
stopExternal external = liftIO $ do
|
||||||
|
l <- atomically $ do
|
||||||
|
l <- takeTMVar v
|
||||||
|
putTMVar v []
|
||||||
|
return l
|
||||||
|
mapM_ stop l
|
||||||
where
|
where
|
||||||
stop Nothing = noop
|
stop st = do
|
||||||
stop (Just st) = do
|
|
||||||
void $ atomically $ tryTakeTMVar v
|
|
||||||
hClose $ externalSend st
|
hClose $ externalSend st
|
||||||
hClose $ externalReceive st
|
hClose $ externalReceive st
|
||||||
externalShutdown st
|
externalShutdown st
|
||||||
|
@ -436,37 +442,35 @@ stopExternal external = liftIO $ stop =<< atomically (tryReadTMVar v)
|
||||||
externalRemoteProgram :: ExternalType -> String
|
externalRemoteProgram :: ExternalType -> String
|
||||||
externalRemoteProgram externaltype = "git-annex-remote-" ++ externaltype
|
externalRemoteProgram externaltype = "git-annex-remote-" ++ externaltype
|
||||||
|
|
||||||
checkVersion :: ExternalLock -> External -> RemoteRequest -> Maybe (Annex ())
|
checkVersion :: ExternalState -> External -> RemoteRequest -> Maybe (Annex ())
|
||||||
checkVersion lck external (VERSION v) = Just $
|
checkVersion st external (VERSION v) = Just $
|
||||||
if v `elem` supportedProtocolVersions
|
if v `elem` supportedProtocolVersions
|
||||||
then noop
|
then noop
|
||||||
else sendMessage lck external (ERROR "unsupported VERSION")
|
else sendMessage st external (ERROR "unsupported VERSION")
|
||||||
checkVersion _ _ _ = Nothing
|
checkVersion _ _ _ = Nothing
|
||||||
|
|
||||||
{- If repo has not been prepared, sends PREPARE.
|
{- If repo has not been prepared, sends PREPARE.
|
||||||
-
|
-
|
||||||
- If the repo fails to prepare, or failed before, throws an exception with
|
- If the repo fails to prepare, or failed before, throws an exception with
|
||||||
- the error message. -}
|
- the error message. -}
|
||||||
checkPrepared :: ExternalLock -> External -> Annex ()
|
checkPrepared :: ExternalState -> External -> Annex ()
|
||||||
checkPrepared lck external =
|
checkPrepared st external = do
|
||||||
fromExternal lck external externalPrepared $ \prepared ->
|
v <- liftIO $ atomically $ readTMVar $ externalPrepared st
|
||||||
case prepared of
|
case v of
|
||||||
Prepared -> noop
|
Prepared -> noop
|
||||||
FailedPrepare errmsg -> error errmsg
|
FailedPrepare errmsg -> error errmsg
|
||||||
Unprepared ->
|
Unprepared ->
|
||||||
handleRequest' lck external PREPARE Nothing $ \resp ->
|
handleRequest' st external PREPARE Nothing $ \resp ->
|
||||||
case resp of
|
case resp of
|
||||||
PREPARE_SUCCESS -> Just $
|
PREPARE_SUCCESS -> Just $
|
||||||
setprepared Prepared
|
setprepared Prepared
|
||||||
PREPARE_FAILURE errmsg -> Just $ do
|
PREPARE_FAILURE errmsg -> Just $ do
|
||||||
setprepared $ FailedPrepare errmsg
|
setprepared $ FailedPrepare errmsg
|
||||||
error errmsg
|
error errmsg
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
where
|
where
|
||||||
setprepared status = liftIO . atomically $ do
|
setprepared status = liftIO $ atomically $ void $
|
||||||
let v = externalState external
|
swapTMVar (externalPrepared st) status
|
||||||
st <- takeTMVar v
|
|
||||||
void $ putTMVar v $ st { externalPrepared = status }
|
|
||||||
|
|
||||||
{- Caches the cost in the git config to avoid needing to start up an
|
{- Caches the cost in the git config to avoid needing to start up an
|
||||||
- external special remote every time time just to ask it what its
|
- external special remote every time time just to ask it what its
|
||||||
|
|
28
Remote/External/Types.hs
vendored
28
Remote/External/Types.hs
vendored
|
@ -12,8 +12,6 @@ module Remote.External.Types (
|
||||||
External(..),
|
External(..),
|
||||||
newExternal,
|
newExternal,
|
||||||
ExternalType,
|
ExternalType,
|
||||||
ExternalLock,
|
|
||||||
withExternalLock,
|
|
||||||
ExternalState(..),
|
ExternalState(..),
|
||||||
PrepareStatus(..),
|
PrepareStatus(..),
|
||||||
Proto.parseMessage,
|
Proto.parseMessage,
|
||||||
|
@ -44,14 +42,12 @@ import qualified Utility.SimpleProtocol as Proto
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Network.URI
|
import Network.URI
|
||||||
|
|
||||||
-- If the remote is not yet running, the ExternalState TMVar is empty.
|
|
||||||
data External = External
|
data External = External
|
||||||
{ externalType :: ExternalType
|
{ externalType :: ExternalType
|
||||||
, externalUUID :: UUID
|
, externalUUID :: UUID
|
||||||
-- Empty until the remote is running.
|
, externalState :: TMVar [ExternalState]
|
||||||
, externalState :: TMVar ExternalState
|
-- ^ TMVar is never left empty; list contains states for external
|
||||||
-- Empty when a remote is in use.
|
-- special remote processes that are not currently in use.
|
||||||
, externalLock :: TMVar ExternalLock
|
|
||||||
, externalDefaultConfig :: RemoteConfig
|
, externalDefaultConfig :: RemoteConfig
|
||||||
, externalGitConfig :: RemoteGitConfig
|
, externalGitConfig :: RemoteGitConfig
|
||||||
}
|
}
|
||||||
|
@ -60,8 +56,7 @@ newExternal :: ExternalType -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex
|
||||||
newExternal externaltype u c gc = liftIO $ External
|
newExternal externaltype u c gc = liftIO $ External
|
||||||
<$> pure externaltype
|
<$> pure externaltype
|
||||||
<*> pure u
|
<*> pure u
|
||||||
<*> atomically newEmptyTMVar
|
<*> atomically (newTMVar [])
|
||||||
<*> atomically (newTMVar ExternalLock)
|
|
||||||
<*> pure c
|
<*> pure c
|
||||||
<*> pure gc
|
<*> pure gc
|
||||||
|
|
||||||
|
@ -71,23 +66,14 @@ data ExternalState = ExternalState
|
||||||
{ externalSend :: Handle
|
{ externalSend :: Handle
|
||||||
, externalReceive :: Handle
|
, externalReceive :: Handle
|
||||||
, externalShutdown :: IO ()
|
, externalShutdown :: IO ()
|
||||||
, externalPrepared :: PrepareStatus
|
, externalPrepared :: TMVar PrepareStatus
|
||||||
-- Never left empty.
|
-- ^ Never left empty.
|
||||||
, externalConfig :: TMVar RemoteConfig
|
, externalConfig :: TMVar RemoteConfig
|
||||||
|
-- ^ Never left empty.
|
||||||
}
|
}
|
||||||
|
|
||||||
data PrepareStatus = Unprepared | Prepared | FailedPrepare ErrorMsg
|
data PrepareStatus = Unprepared | Prepared | FailedPrepare ErrorMsg
|
||||||
|
|
||||||
-- Constructor is not exported, and only created by newExternal.
|
|
||||||
data ExternalLock = ExternalLock
|
|
||||||
|
|
||||||
withExternalLock :: External -> (ExternalLock -> Annex a) -> Annex a
|
|
||||||
withExternalLock external = bracketIO setup cleanup
|
|
||||||
where
|
|
||||||
setup = atomically $ takeTMVar v
|
|
||||||
cleanup = atomically . putTMVar v
|
|
||||||
v = externalLock external
|
|
||||||
|
|
||||||
-- Messages that can be sent to the external remote to request it do something.
|
-- Messages that can be sent to the external remote to request it do something.
|
||||||
data Request
|
data Request
|
||||||
= PREPARE
|
= PREPARE
|
||||||
|
|
|
@ -7,3 +7,5 @@ This should not be hard to make to use a pool of Externals, starting up a
|
||||||
new one if the pool is empty or all in use. --[[Joey]]
|
new one if the pool is empty or all in use. --[[Joey]]
|
||||||
|
|
||||||
[[users/yoh]] may want this for datalad?
|
[[users/yoh]] may want this for datalad?
|
||||||
|
|
||||||
|
> [[done]] --[[Joey]]
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue