git-annex/Remote/Hook.hs

184 lines
5.6 KiB
Haskell
Raw Normal View History

{- A remote that provides hooks to run shell commands.
-
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE RankNTypes #-}
module Remote.Hook (remote) where
import Annex.Common
import Types.Remote
import Types.Creds
import qualified Git
import Git.Types (fromConfigKey, fromConfigValue)
import Config
import Config.Cost
import Annex.UUID
import Annex.SpecialRemote.Config
2011-08-17 00:49:54 +00:00
import Remote.Helper.Special
2019-02-20 19:55:01 +00:00
import Remote.Helper.ExportImport
import Utility.Env
import Messages.Progress
import Types.ProposedAccepted
import qualified Data.Map as M
type Action = String
type HookName = String
2011-12-31 08:11:39 +00:00
remote :: RemoteType
remote = specialRemoteType $ RemoteType
{ typename = "hook"
, enumerate = const (findSpecialRemotes "hooktype")
, generate = gen
, configParser = mkRemoteConfigParser
[ optionalStringParser hooktypeField
(FieldDesc "(required) specify collection of hooks to use")
]
, setup = hookSetup
, exportSupported = exportUnsupported
2019-02-20 19:55:01 +00:00
, importSupported = importUnsupported
add thirdPartyPopulated interface This is to support, eg a borg repo as a special remote, which is populated not by running git-annex commands, but by using borg. Then git-annex sync lists the content of the remote, learns which files are annex objects, and treats those as present in the remote. So, most of the import machinery is reused, to a new purpose. While normally importtree maintains a remote tracking branch, this does not, because the files stored in the remote are annex object files, not user-visible filenames. But, internally, a git tree is still generated, of the files on the remote that are annex objects. This tree is used by retrieveExportWithContentIdentifier, etc. As with other import/export remotes, that the tree is recorded in the export log, and gets grafted into the git-annex branch. importKey changed to be able to return Nothing, to indicate when an ImportLocation is not an annex object and so should be skipped from being included in the tree. It did not seem to make sense to have git-annex import do this, since from the user's perspective, it's not like other imports. So only git-annex sync does it. Note that, git-annex sync does not yet download objects from such remotes that are preferred content. importKeys is run with content downloading disabled, to avoid getting the content of all objects. Perhaps what's needed is for seekSyncContent to be run with these remotes, but I don't know if it will just work (in particular, it needs to avoid trying to transfer objects to them), so I skipped that for now. (Untested and unused as of yet.) This commit was sponsored by Jochen Bartl on Patreon.
2020-12-18 18:52:57 +00:00
, thirdPartyPopulated = False
}
hooktypeField :: RemoteConfigField
hooktypeField = Accepted "hooktype"
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
gen r u rc gc rs = do
c <- parsedRemoteConfig remote rc
cst <- remoteCost gc c expensiveRemoteCost
return $ Just $ specialRemote c
(store hooktype)
(retrieve hooktype)
(remove hooktype)
(checkKey hooktype)
2014-12-16 19:26:13 +00:00
Remote
{ uuid = u
, cost = cst
, name = Git.repoDescribe r
, storeKey = storeKeyDummy
, retrieveKeyFile = retrieveKeyFileDummy
, retrieveKeyFileCheap = Nothing
-- A hook could use http and be vulnerable to
-- redirect to file:// attacks, etc.
, retrievalSecurityPolicy = mkRetrievalVerifiableKeysSecure gc
2014-12-16 19:26:13 +00:00
, removeKey = removeKeyDummy
, lockContent = Nothing
2014-12-16 19:26:13 +00:00
, checkPresent = checkPresentDummy
, checkPresentCheap = False
, exportActions = exportUnsupported
2019-02-20 19:55:01 +00:00
, importActions = importUnsupported
2014-12-16 19:26:13 +00:00
, whereisKey = Nothing
, remoteFsck = Nothing
, repairRepo = Nothing
, config = c
, localpath = Nothing
, getRepo = return r
2014-12-16 19:26:13 +00:00
, gitconfig = gc
, readonly = False
, appendonly = False
, untrustworthy = False
2014-12-16 19:26:13 +00:00
, availability = GloballyAvailable
, remotetype = remote
, mkUnavailable = gen r u rc
(gc { remoteAnnexHookType = Just "!dne!" })
rs
2014-12-16 19:26:13 +00:00
, getInfo = return [("hooktype", hooktype)]
, claimUrl = Nothing
, checkUrl = Nothing
, remoteStateHandle = rs
2014-12-16 19:26:13 +00:00
}
where
hooktype = fromMaybe (giveup "missing hooktype") $ remoteAnnexHookType gc
hookSetup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
hookSetup _ mu _ c gc = do
u <- maybe (liftIO genUUID) return mu
let hooktype = maybe (giveup "Specify hooktype=") fromProposedAccepted $
M.lookup hooktypeField c
(c', _encsetup) <- encryptionSetup c gc
gitConfigSpecialRemote u c' [("hooktype", hooktype)]
return (c', u)
hookEnv :: Action -> Key -> Maybe FilePath -> IO (Maybe [(String, String)])
hookEnv action k f = Just <$> mergeenv (fileenv f ++ keyenv)
2012-11-11 04:51:07 +00:00
where
mergeenv l = addEntries l <$> getEnvironment
envvar s v = ("ANNEX_" ++ s, v)
2012-11-11 04:51:07 +00:00
keyenv = catMaybes
[ Just $ envvar "KEY" (serializeKey k)
, Just $ envvar "ACTION" action
, envvar "HASH_1" <$> headMaybe hashbits
, envvar "HASH_2" <$> headMaybe (drop 1 hashbits)
2012-11-11 04:51:07 +00:00
]
fileenv Nothing = []
fileenv (Just file) = [envvar "FILE" file]
hashbits = map takeDirectory $ splitPath $
fromRawFilePath $ hashDirMixed def k
lookupHook :: HookName -> Action -> Annex (Maybe String)
lookupHook hookname action = do
command <- fromConfigValue <$> getConfig hook mempty
if null command
then do
fallback <- fromConfigValue <$> getConfig hookfallback mempty
if null fallback
then do
2019-12-02 16:26:33 +00:00
warning $ "missing configuration for " ++ fromConfigKey hook ++ " or " ++ fromConfigKey hookfallback
return Nothing
else return $ Just fallback
else return $ Just command
2012-11-11 04:51:07 +00:00
where
hook = annexConfig $ encodeBS $ hookname ++ "-" ++ action ++ "-hook"
hookfallback = annexConfig $ encodeBS $ hookname ++ "-hook"
runHook :: HookName -> Action -> Key -> Maybe FilePath -> Annex ()
runHook hook action k f = lookupHook hook action >>= \case
Just command -> do
showOutput -- make way for hook output
environ <- liftIO (hookEnv action k f)
unlessM (progressCommandEnv "sh" [Param "-c", Param command] environ) $
giveup $ hook ++ " hook exited nonzero!"
Nothing -> giveup $ action ++ " hook misconfigured"
runHook' :: HookName -> Action -> Key -> Maybe FilePath -> Annex Bool -> Annex Bool
runHook' hook action k f a = maybe (return False) run =<< lookupHook hook action
2012-11-11 04:51:07 +00:00
where
run command = do
showOutput -- make way for hook output
ifM (progressCommandEnv "sh" [Param "-c", Param command] =<< liftIO (hookEnv action k f))
2012-11-11 04:51:07 +00:00
( a
, do
warning $ hook ++ " hook exited nonzero!"
return False
)
2014-08-02 21:25:16 +00:00
store :: HookName -> Storer
store h = fileStorer $ \k src _p -> runHook h "store" k (Just src)
2014-08-02 21:25:16 +00:00
retrieve :: HookName -> Retriever
retrieve h = fileRetriever $ \d k _p ->
unlessM (runHook' h "retrieve" k (Just (fromRawFilePath d)) $ return True) $
giveup "failed to retrieve content"
remove :: HookName -> Remover
2020-05-14 18:08:09 +00:00
remove h k =
unlessM (runHook' h "remove" k Nothing $ return True) $
giveup "failed to remove content"
checkKey :: HookName -> CheckPresent
checkKey h k = do
v <- lookupHook h action
liftIO $ check v
2012-11-11 04:51:07 +00:00
where
action = "checkpresent"
findkey s = serializeKey k `elem` lines s
check Nothing = giveup $ action ++ " hook misconfigured"
2012-11-11 04:51:07 +00:00
check (Just hook) = do
environ <- hookEnv action k Nothing
findkey <$> readProcessEnv "sh" ["-c", hook] environ