refactoring in preparation for external backends
This commit is contained in:
parent
6b26802047
commit
555fe669e1
4 changed files with 139 additions and 90 deletions
87
Annex/ExternalAddonProcess.hs
Normal file
87
Annex/ExternalAddonProcess.hs
Normal file
|
@ -0,0 +1,87 @@
|
||||||
|
{- External addon processes for special remotes and backends.
|
||||||
|
-
|
||||||
|
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Annex.ExternalAddonProcess where
|
||||||
|
|
||||||
|
import qualified Annex
|
||||||
|
import Annex.Common
|
||||||
|
import Git.Env
|
||||||
|
import Utility.Shell
|
||||||
|
import Messages.Progress
|
||||||
|
|
||||||
|
import Control.Concurrent.STM
|
||||||
|
import Control.Concurrent.Async
|
||||||
|
|
||||||
|
data ExternalAddonProcess = ExternalAddonProcess
|
||||||
|
{ externalSend :: Handle
|
||||||
|
, externalReceive :: Handle
|
||||||
|
-- Shut down the process. With True, it's forced to stop
|
||||||
|
-- immediately.
|
||||||
|
, externalShutdown :: Bool -> IO ()
|
||||||
|
, externalPid :: ExternalAddonPID
|
||||||
|
}
|
||||||
|
|
||||||
|
type ExternalAddonPID = Int
|
||||||
|
|
||||||
|
data ExternalAddonStartError
|
||||||
|
= ProgramNotInstalled String
|
||||||
|
| ProgramFailure String
|
||||||
|
|
||||||
|
startExternalAddonProcess :: String -> TVar ExternalAddonPID-> Annex (Either ExternalAddonStartError ExternalAddonProcess)
|
||||||
|
startExternalAddonProcess basecmd pidvar = do
|
||||||
|
errrelayer <- mkStderrRelayer
|
||||||
|
g <- Annex.gitRepo
|
||||||
|
cmdpath <- liftIO $ searchPath basecmd
|
||||||
|
liftIO $ start errrelayer g cmdpath
|
||||||
|
where
|
||||||
|
start errrelayer g cmdpath = do
|
||||||
|
(cmd, ps) <- maybe (pure (basecmd, [])) findShellCommand cmdpath
|
||||||
|
let basep = (proc cmd (toCommand ps))
|
||||||
|
{ std_in = CreatePipe
|
||||||
|
, std_out = CreatePipe
|
||||||
|
, std_err = CreatePipe
|
||||||
|
}
|
||||||
|
p <- propgit g basep
|
||||||
|
tryNonAsync (createProcess p) >>= \case
|
||||||
|
Right v -> (Right <$> started errrelayer v)
|
||||||
|
`catchNonAsync` const (runerr cmdpath)
|
||||||
|
Left _ -> runerr cmdpath
|
||||||
|
|
||||||
|
started errrelayer pall@(Just hin, Just hout, Just herr, ph) = do
|
||||||
|
stderrelay <- async $ errrelayer herr
|
||||||
|
pid <- atomically $ do
|
||||||
|
n <- succ <$> readTVar pidvar
|
||||||
|
writeTVar pidvar n
|
||||||
|
return n
|
||||||
|
let shutdown forcestop = do
|
||||||
|
cancel stderrelay
|
||||||
|
if forcestop
|
||||||
|
then cleanupProcess pall
|
||||||
|
else flip onException (cleanupProcess pall) $ do
|
||||||
|
hClose herr
|
||||||
|
hClose hin
|
||||||
|
hClose hout
|
||||||
|
void $ waitForProcess ph
|
||||||
|
return $ ExternalAddonProcess
|
||||||
|
{ externalSend = hin
|
||||||
|
, externalReceive = hout
|
||||||
|
, externalPid = pid
|
||||||
|
, externalShutdown = shutdown
|
||||||
|
}
|
||||||
|
started _ _ = giveup "internal"
|
||||||
|
|
||||||
|
propgit g p = do
|
||||||
|
environ <- propGitEnv g
|
||||||
|
return $ p { env = Just environ }
|
||||||
|
|
||||||
|
runerr (Just cmd) =
|
||||||
|
return $ Left $ ProgramFailure $
|
||||||
|
"Cannot run " ++ cmd ++ " -- Make sure it's executable and that its dependencies are installed."
|
||||||
|
runerr Nothing = do
|
||||||
|
path <- intercalate ":" <$> getSearchPath
|
||||||
|
return $ Left $ ProgramNotInstalled $
|
||||||
|
"Cannot run " ++ basecmd ++ " -- It is not installed in PATH (" ++ path ++ ")"
|
|
@ -12,6 +12,7 @@ module Remote.External (remote) where
|
||||||
import Remote.External.Types
|
import Remote.External.Types
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
|
import Annex.ExternalAddonProcess
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
import Types.Export
|
import Types.Export
|
||||||
import Types.CleanupActions
|
import Types.CleanupActions
|
||||||
|
@ -20,15 +21,12 @@ import Types.ProposedAccepted
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Config
|
import Config
|
||||||
import Git.Config (boolConfig)
|
import Git.Config (boolConfig)
|
||||||
import Git.Env
|
|
||||||
import Annex.SpecialRemote.Config
|
import Annex.SpecialRemote.Config
|
||||||
import Remote.Helper.Special
|
import Remote.Helper.Special
|
||||||
import Remote.Helper.ExportImport
|
import Remote.Helper.ExportImport
|
||||||
import Remote.Helper.ReadOnly
|
import Remote.Helper.ReadOnly
|
||||||
import Remote.Helper.Messages
|
import Remote.Helper.Messages
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import Utility.Shell
|
|
||||||
import Messages.Progress
|
|
||||||
import Types.Transfer
|
import Types.Transfer
|
||||||
import Logs.PreferredContent.Raw
|
import Logs.PreferredContent.Raw
|
||||||
import Logs.RemoteState
|
import Logs.RemoteState
|
||||||
|
@ -40,7 +38,6 @@ import Annex.UUID
|
||||||
import Creds
|
import Creds
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Control.Concurrent.Async
|
|
||||||
import System.Log.Logger (debugM)
|
import System.Log.Logger (debugM)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
@ -513,7 +510,7 @@ sendMessage st external m = liftIO $ do
|
||||||
hFlush h
|
hFlush h
|
||||||
where
|
where
|
||||||
line = unwords $ formatMessage m
|
line = unwords $ formatMessage m
|
||||||
h = externalSend st
|
h = externalSend (externalAddonProcess st)
|
||||||
|
|
||||||
{- A response handler can yeild a result, or it can request that another
|
{- A response handler can yeild a result, or it can request that another
|
||||||
- message be consumed from the external result. -}
|
- message be consumed from the external result. -}
|
||||||
|
@ -538,7 +535,7 @@ receiveMessage
|
||||||
-> (AsyncMessage -> Maybe (Annex a))
|
-> (AsyncMessage -> Maybe (Annex a))
|
||||||
-> Annex a
|
-> Annex a
|
||||||
receiveMessage st external handleresponse handlerequest handleasync =
|
receiveMessage st external handleresponse handlerequest handleasync =
|
||||||
go =<< liftIO (catchMaybeIO $ hGetLine $ externalReceive st)
|
go =<< liftIO (catchMaybeIO $ hGetLine $ externalReceive $ externalAddonProcess st)
|
||||||
where
|
where
|
||||||
go Nothing = protocolError False ""
|
go Nothing = protocolError False ""
|
||||||
go (Just s) = do
|
go (Just s) = do
|
||||||
|
@ -563,7 +560,7 @@ receiveMessage st external handleresponse handlerequest handleasync =
|
||||||
protocolDebug :: External -> ExternalState -> Bool -> String -> IO ()
|
protocolDebug :: External -> ExternalState -> Bool -> String -> IO ()
|
||||||
protocolDebug external st sendto line = debugM "external" $ unwords
|
protocolDebug external st sendto line = debugM "external" $ unwords
|
||||||
[ externalRemoteProgram (externalType external) ++
|
[ externalRemoteProgram (externalType external) ++
|
||||||
"[" ++ show (externalPid st) ++ "]"
|
"[" ++ show (externalPid (externalAddonProcess st)) ++ "]"
|
||||||
, if sendto then "<--" else "-->"
|
, if sendto then "<--" else "-->"
|
||||||
, line
|
, line
|
||||||
]
|
]
|
||||||
|
@ -582,7 +579,7 @@ protocolDebug external st sendto line = debugM "external" $ unwords
|
||||||
withExternalState :: External -> (ExternalState -> Annex a) -> Annex a
|
withExternalState :: External -> (ExternalState -> Annex a) -> Annex a
|
||||||
withExternalState external a = do
|
withExternalState external a = do
|
||||||
st <- get
|
st <- get
|
||||||
r <- a st `onException` liftIO (externalShutdown st True)
|
r <- a st `onException` liftIO (externalShutdown (externalAddonProcess st) True)
|
||||||
put st -- only when no exception is thrown
|
put st -- only when no exception is thrown
|
||||||
return r
|
return r
|
||||||
where
|
where
|
||||||
|
@ -603,90 +600,55 @@ withExternalState external a = do
|
||||||
{- Starts an external remote process running, and checks VERSION and
|
{- Starts an external remote process running, and checks VERSION and
|
||||||
- exchanges EXTENSIONS. -}
|
- exchanges EXTENSIONS. -}
|
||||||
startExternal :: External -> Annex ExternalState
|
startExternal :: External -> Annex ExternalState
|
||||||
startExternal external = do
|
startExternal external =
|
||||||
errrelayer <- mkStderrRelayer
|
startExternalAddonProcess basecmd (externalLastPid external) >>= \case
|
||||||
st <- start errrelayer =<< Annex.gitRepo
|
Left (ProgramFailure err) -> giveup err
|
||||||
receiveMessage st external
|
Left (ProgramNotInstalled err) ->
|
||||||
(const Nothing)
|
case (lookupName (unparsedRemoteConfig (externalDefaultConfig external)), remoteAnnexReadOnly <$> externalGitConfig external) of
|
||||||
(checkVersion st external)
|
(Just rname, Just True) -> giveup $ unlines
|
||||||
(const Nothing)
|
[ err
|
||||||
sendMessage st external (EXTENSIONS supportedExtensionList)
|
, "This remote has annex-readonly=true, and previous versions of"
|
||||||
-- It responds with a EXTENSIONS_RESPONSE; that extensions list
|
, "git-annex would tried to download from it without"
|
||||||
-- is reserved for future expansion. UNSUPPORTED_REQUEST is also
|
, "installing " ++ basecmd ++ ". If you want that, you need to set:"
|
||||||
-- accepted.
|
, "git config remote." ++ rname ++ ".annex-externaltype readonly"
|
||||||
receiveMessage st external
|
]
|
||||||
(\resp -> case resp of
|
_ -> giveup err
|
||||||
EXTENSIONS_RESPONSE _ -> result ()
|
Right p -> do
|
||||||
UNSUPPORTED_REQUEST -> result ()
|
cv <- liftIO $ newTVarIO $ externalDefaultConfig external
|
||||||
_ -> Nothing
|
ccv <- liftIO $ newTVarIO id
|
||||||
)
|
pv <- liftIO $ newTVarIO Unprepared
|
||||||
(const Nothing)
|
let st = ExternalState
|
||||||
(const Nothing)
|
{ externalAddonProcess = p
|
||||||
return st
|
, externalPrepared = pv
|
||||||
|
, externalConfig = cv
|
||||||
|
, externalConfigChanges = ccv
|
||||||
|
}
|
||||||
|
startproto st
|
||||||
|
return st
|
||||||
where
|
where
|
||||||
start errrelayer g = liftIO $ do
|
|
||||||
cmdpath <- searchPath basecmd
|
|
||||||
(cmd, ps) <- maybe (pure (basecmd, [])) findShellCommand cmdpath
|
|
||||||
let basep = (proc cmd (toCommand ps))
|
|
||||||
{ std_in = CreatePipe
|
|
||||||
, std_out = CreatePipe
|
|
||||||
, std_err = CreatePipe
|
|
||||||
}
|
|
||||||
p <- propgit g basep
|
|
||||||
pall@(Just hin, Just hout, Just herr, ph) <-
|
|
||||||
createProcess p `catchNonAsync` runerr cmdpath
|
|
||||||
stderrelay <- async $ errrelayer herr
|
|
||||||
cv <- newTVarIO $ externalDefaultConfig external
|
|
||||||
ccv <- newTVarIO id
|
|
||||||
pv <- newTVarIO Unprepared
|
|
||||||
pid <- atomically $ do
|
|
||||||
n <- succ <$> readTVar (externalLastPid external)
|
|
||||||
writeTVar (externalLastPid external) n
|
|
||||||
return n
|
|
||||||
let shutdown forcestop = do
|
|
||||||
cancel stderrelay
|
|
||||||
if forcestop
|
|
||||||
then cleanupProcess pall
|
|
||||||
else flip onException (cleanupProcess pall) $ do
|
|
||||||
hClose herr
|
|
||||||
hClose hin
|
|
||||||
hClose hout
|
|
||||||
void $ waitForProcess ph
|
|
||||||
return $ ExternalState
|
|
||||||
{ externalSend = hin
|
|
||||||
, externalReceive = hout
|
|
||||||
, externalPid = pid
|
|
||||||
, externalShutdown = shutdown
|
|
||||||
, externalPrepared = pv
|
|
||||||
, externalConfig = cv
|
|
||||||
, externalConfigChanges = ccv
|
|
||||||
}
|
|
||||||
|
|
||||||
basecmd = externalRemoteProgram $ externalType external
|
basecmd = externalRemoteProgram $ externalType external
|
||||||
|
startproto st = do
|
||||||
propgit g p = do
|
receiveMessage st external
|
||||||
environ <- propGitEnv g
|
(const Nothing)
|
||||||
return $ p { env = Just environ }
|
(checkVersion st external)
|
||||||
|
(const Nothing)
|
||||||
runerr (Just cmd) _ =
|
sendMessage st external (EXTENSIONS supportedExtensionList)
|
||||||
giveup $ "Cannot run " ++ cmd ++ " -- Make sure it's executable and that its dependencies are installed."
|
-- It responds with a EXTENSIONS_RESPONSE; that extensions
|
||||||
runerr Nothing _ = do
|
-- list is reserved for future expansion. UNSUPPORTED_REQUEST
|
||||||
path <- intercalate ":" <$> getSearchPath
|
-- is also accepted.
|
||||||
let err = "Cannot run " ++ basecmd ++ " -- It is not installed in PATH (" ++ path ++ ")"
|
receiveMessage st external
|
||||||
case (lookupName (unparsedRemoteConfig (externalDefaultConfig external)), remoteAnnexReadOnly <$> externalGitConfig external) of
|
(\resp -> case resp of
|
||||||
(Just rname, Just True) -> giveup $ unlines
|
EXTENSIONS_RESPONSE _ -> result ()
|
||||||
[ err
|
UNSUPPORTED_REQUEST -> result ()
|
||||||
, "This remote has annex-readonly=true, and previous versions of"
|
_ -> Nothing
|
||||||
, "git-annex would tried to download from it without"
|
)
|
||||||
, "installing " ++ basecmd ++ ". If you want that, you need to set:"
|
(const Nothing)
|
||||||
, "git config remote." ++ rname ++ ".annex-externaltype readonly"
|
(const Nothing)
|
||||||
]
|
|
||||||
_ -> giveup err
|
|
||||||
|
|
||||||
stopExternal :: External -> Annex ()
|
stopExternal :: External -> Annex ()
|
||||||
stopExternal external = liftIO $ do
|
stopExternal external = liftIO $ do
|
||||||
l <- atomically $ swapTVar (externalState external) []
|
l <- atomically $ swapTVar (externalState external) []
|
||||||
mapM_ (flip externalShutdown False) l
|
mapM_ (flip (externalShutdown . externalAddonProcess) False) l
|
||||||
|
|
||||||
externalRemoteProgram :: ExternalType -> String
|
externalRemoteProgram :: ExternalType -> String
|
||||||
externalRemoteProgram externaltype = "git-annex-remote-" ++ externaltype
|
externalRemoteProgram externaltype = "git-annex-remote-" ++ externaltype
|
||||||
|
|
6
Remote/External/Types.hs
vendored
6
Remote/External/Types.hs
vendored
|
@ -34,6 +34,7 @@ module Remote.External.Types (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
|
import Annex.ExternalAddonProcess
|
||||||
import Types.StandardGroups (PreferredContentExpression)
|
import Types.StandardGroups (PreferredContentExpression)
|
||||||
import Utility.Metered (BytesProcessed(..))
|
import Utility.Metered (BytesProcessed(..))
|
||||||
import Types.Transfer (Direction(..))
|
import Types.Transfer (Direction(..))
|
||||||
|
@ -75,10 +76,7 @@ newExternal externaltype u c gc rs = liftIO $ External
|
||||||
type ExternalType = String
|
type ExternalType = String
|
||||||
|
|
||||||
data ExternalState = ExternalState
|
data ExternalState = ExternalState
|
||||||
{ externalSend :: Handle
|
{ externalAddonProcess :: ExternalAddonProcess
|
||||||
, externalReceive :: Handle
|
|
||||||
, externalShutdown :: Bool -> IO ()
|
|
||||||
, externalPid :: PID
|
|
||||||
, externalPrepared :: TVar PrepareStatus
|
, externalPrepared :: TVar PrepareStatus
|
||||||
, externalConfig :: TVar ParsedRemoteConfig
|
, externalConfig :: TVar ParsedRemoteConfig
|
||||||
, externalConfigChanges :: TVar (RemoteConfig -> RemoteConfig)
|
, externalConfigChanges :: TVar (RemoteConfig -> RemoteConfig)
|
||||||
|
|
|
@ -652,6 +652,7 @@ Executable git-annex
|
||||||
Annex.Drop
|
Annex.Drop
|
||||||
Annex.Environment
|
Annex.Environment
|
||||||
Annex.Export
|
Annex.Export
|
||||||
|
Annex.ExternalAddonProcess
|
||||||
Annex.FileMatcher
|
Annex.FileMatcher
|
||||||
Annex.Fixup
|
Annex.Fixup
|
||||||
Annex.GitOverlay
|
Annex.GitOverlay
|
||||||
|
@ -697,6 +698,7 @@ Executable git-annex
|
||||||
Annex.WorkTree
|
Annex.WorkTree
|
||||||
Annex.YoutubeDl
|
Annex.YoutubeDl
|
||||||
Backend
|
Backend
|
||||||
|
-- Backend.External
|
||||||
Backend.Hash
|
Backend.Hash
|
||||||
Backend.URL
|
Backend.URL
|
||||||
Backend.Utilities
|
Backend.Utilities
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue