git-annex/Remote/Hook.hs

158 lines
4.8 KiB
Haskell
Raw Normal View History

{- A remote that provides hooks to run shell commands.
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Remote.Hook (remote) where
import qualified Data.ByteString.Lazy as L
import qualified Data.Map as M
import System.Environment
2011-10-05 20:02:51 +00:00
import Common.Annex
import Types.Remote
import Types.Key
import qualified Git
import Config
import Config.Cost
2011-10-04 04:40:47 +00:00
import Annex.Content
import Annex.UUID
2011-08-17 00:49:54 +00:00
import Remote.Helper.Special
import Remote.Helper.Encryptable
import Crypto
import Utility.Metered
type Action = String
type HookName = String
2011-12-31 08:11:39 +00:00
remote :: RemoteType
remote = RemoteType {
typename = "hook",
enumerate = findSpecialRemotes "hooktype",
generate = gen,
setup = hookSetup
}
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
gen r u c gc = do
cst <- remoteCost gc expensiveRemoteCost
return $ Just $ encryptableRemote c
(storeEncrypted hooktype $ getGpgEncParams (c,gc))
(retrieveEncrypted hooktype)
Remote {
uuid = u,
cost = cst,
name = Git.repoDescribe r,
2012-12-13 04:45:27 +00:00
storeKey = store hooktype,
retrieveKeyFile = retrieve hooktype,
retrieveKeyFileCheap = retrieveCheap hooktype,
removeKey = remove hooktype,
hasKey = checkPresent r hooktype,
hasKeyCheap = False,
whereisKey = Nothing,
2012-11-30 04:55:59 +00:00
config = M.empty,
2012-08-26 18:26:43 +00:00
localpath = Nothing,
repo = r,
gitconfig = gc,
readonly = False,
2013-03-15 23:16:13 +00:00
globallyAvailable = False,
remotetype = remote
}
where
hooktype = fromMaybe (error "missing hooktype") $ remoteAnnexHookType gc
hookSetup :: Maybe UUID -> RemoteConfig -> Annex (RemoteConfig, UUID)
hookSetup mu c = do
u <- maybe (liftIO genUUID) return mu
2011-07-15 16:47:14 +00:00
let hooktype = fromMaybe (error "Specify hooktype=") $
2011-05-15 06:49:43 +00:00
M.lookup "hooktype" c
c' <- encryptionSetup c
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 = M.toList . M.union (M.fromList l)
<$> M.fromList <$> getEnvironment
env s v = ("ANNEX_" ++ s, v)
keyenv = catMaybes
[ Just $ env "KEY" (key2file k)
, Just $ env "ACTION" action
2012-11-11 04:51:07 +00:00
, env "HASH_1" <$> headMaybe hashbits
, env "HASH_2" <$> headMaybe (drop 1 hashbits)
]
fileenv Nothing = []
fileenv (Just file) = [env "FILE" file]
hashbits = map takeDirectory $ splitPath $ hashDirMixed k
lookupHook :: HookName -> Action -> Annex (Maybe String)
lookupHook hookname action = do
command <- getConfig (annexConfig hook) ""
if null command
then do
fallback <- getConfig (annexConfig $ hookfallback) ""
if null fallback
then do
warning $ "missing configuration for " ++ hook ++ " or " ++ hookfallback
return Nothing
else return $ Just fallback
else return $ Just command
2012-11-11 04:51:07 +00:00
where
hook = hookname ++ "-" ++ action ++ "-hook"
hookfallback = hookname ++ "-hook"
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 (liftIO $ boolSystemEnv "sh" [Param "-c", Param command] =<< hookEnv action k f)
2012-11-11 04:51:07 +00:00
( a
, do
warning $ hook ++ " hook exited nonzero!"
return False
)
store :: HookName -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
store h k _f _p = sendAnnex k (void $ remove h k) $ \src ->
runHook h "store" k (Just src) $ return True
storeEncrypted :: HookName -> [CommandParam] -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
storeEncrypted h gpgOpts (cipher, enck) k _p = withTmp enck $ \tmp ->
sendAnnex k (void $ remove h enck) $ \src -> do
liftIO $ encrypt gpgOpts cipher (feedFile src) $
readBytes $ L.writeFile tmp
runHook h "store" enck (Just tmp) $ return True
retrieve :: HookName -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
retrieve h k _f d _p = runHook h "retrieve" k (Just d) $ return True
retrieveCheap :: HookName -> Key -> FilePath -> Annex Bool
retrieveCheap _ _ _ = return False
retrieveEncrypted :: HookName -> (Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool
retrieveEncrypted h (cipher, enck) _ f _p = withTmp enck $ \tmp ->
runHook h "retrieve" enck (Just tmp) $ liftIO $ catchBoolIO $ do
decrypt cipher (feedFile tmp) $
readBytes $ L.writeFile f
return True
remove :: HookName -> Key -> Annex Bool
2011-07-15 16:47:14 +00:00
remove h k = runHook h "remove" k Nothing $ return True
checkPresent :: Git.Repo -> HookName -> Key -> Annex (Either String Bool)
checkPresent r h k = do
showAction $ "checking " ++ Git.repoDescribe r
v <- lookupHook h action
liftIO $ catchMsgIO $ check v
2012-11-11 04:51:07 +00:00
where
action = "checkpresent"
2012-11-11 04:51:07 +00:00
findkey s = key2file k `elem` lines s
check Nothing = error $ action ++ " hook misconfigured"
2012-11-11 04:51:07 +00:00
check (Just hook) = do
env <- hookEnv action k Nothing
2012-11-11 04:51:07 +00:00
findkey <$> readProcessEnv "sh" ["-c", hook] env