2017-09-01 17:02:07 +00:00
|
|
|
{- exports to remotes
|
|
|
|
-
|
|
|
|
- Copyright 2017 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2017-09-07 17:45:31 +00:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
|
2017-09-01 17:02:07 +00:00
|
|
|
module Remote.Helper.Export where
|
|
|
|
|
|
|
|
import Annex.Common
|
|
|
|
import Types.Remote
|
2017-09-04 20:39:56 +00:00
|
|
|
import Types.Backend
|
|
|
|
import Types.Key
|
|
|
|
import Backend
|
2017-09-04 16:40:33 +00:00
|
|
|
import Remote.Helper.Encryptable (isEncrypted)
|
2017-09-04 20:39:56 +00:00
|
|
|
import Database.Export
|
2017-09-01 17:02:07 +00:00
|
|
|
|
2017-09-04 16:40:33 +00:00
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
-- | Use for remotes that do not support exports.
|
2017-09-07 17:45:31 +00:00
|
|
|
class HasExportUnsupported a where
|
|
|
|
exportUnsupported :: a
|
2017-09-04 16:40:33 +00:00
|
|
|
|
2017-09-07 17:45:31 +00:00
|
|
|
instance HasExportUnsupported (RemoteConfig -> RemoteGitConfig -> Annex Bool) where
|
|
|
|
exportUnsupported = \_ _ -> return False
|
|
|
|
|
2017-09-12 20:59:04 +00:00
|
|
|
instance HasExportUnsupported (Annex (ExportActions Annex)) where
|
|
|
|
exportUnsupported = return $ ExportActions
|
2017-09-08 18:24:05 +00:00
|
|
|
{ storeExport = \_ _ _ _ -> do
|
|
|
|
warning "store export is unsupported"
|
|
|
|
return False
|
|
|
|
, retrieveExport = \_ _ _ _ -> return False
|
2017-09-07 17:45:31 +00:00
|
|
|
, checkPresentExport = \_ _ -> return False
|
2017-09-15 17:15:47 +00:00
|
|
|
, removeExport = \_ _ -> return False
|
|
|
|
, removeExportDirectory = Just $ \_ -> return False
|
2017-09-07 17:45:31 +00:00
|
|
|
, renameExport = \_ _ _ -> return False
|
|
|
|
}
|
|
|
|
|
2017-09-08 20:44:00 +00:00
|
|
|
exportTree :: RemoteConfig -> Bool
|
|
|
|
exportTree c = case M.lookup "exporttree" c of
|
|
|
|
Just "yes" -> True
|
|
|
|
_ -> False
|
|
|
|
|
2017-09-07 17:45:31 +00:00
|
|
|
exportIsSupported :: RemoteConfig -> RemoteGitConfig -> Annex Bool
|
|
|
|
exportIsSupported = \_ _ -> return True
|
|
|
|
|
|
|
|
-- | Prevent or allow exporttree=yes when setting up a new remote,
|
|
|
|
-- depending on exportSupported and other configuration.
|
|
|
|
adjustExportableRemoteType :: RemoteType -> RemoteType
|
|
|
|
adjustExportableRemoteType rt = rt { setup = setup' }
|
|
|
|
where
|
|
|
|
setup' st mu cp c gc = do
|
|
|
|
let cont = setup rt st mu cp c gc
|
|
|
|
ifM (exportSupported rt c gc)
|
|
|
|
( case st of
|
2017-09-08 20:44:00 +00:00
|
|
|
Init
|
|
|
|
| exportTree c && isEncrypted c ->
|
2017-09-07 17:45:31 +00:00
|
|
|
giveup "cannot enable both encryption and exporttree"
|
2017-09-08 20:44:00 +00:00
|
|
|
| otherwise -> cont
|
2017-09-07 17:45:31 +00:00
|
|
|
Enable oldc
|
2017-09-08 20:44:00 +00:00
|
|
|
| exportTree c /= exportTree oldc ->
|
2017-09-07 17:45:31 +00:00
|
|
|
giveup "cannot change exporttree of existing special remote"
|
|
|
|
| otherwise -> cont
|
2017-09-08 20:44:00 +00:00
|
|
|
, if exportTree c
|
|
|
|
then giveup "exporttree=yes is not supported by this special remote"
|
|
|
|
else cont
|
2017-09-07 17:45:31 +00:00
|
|
|
)
|
2017-09-04 20:39:56 +00:00
|
|
|
|
2017-09-07 17:45:31 +00:00
|
|
|
-- | If the remote is exportSupported, and exporttree=yes, adjust the
|
|
|
|
-- remote to be an export.
|
|
|
|
adjustExportable :: Remote -> Annex Remote
|
|
|
|
adjustExportable r = case M.lookup "exporttree" (config r) of
|
|
|
|
Just "yes" -> ifM (isExportSupported r)
|
|
|
|
( isexport
|
|
|
|
, notexport
|
|
|
|
)
|
2017-09-08 18:24:05 +00:00
|
|
|
Nothing -> notexport
|
|
|
|
Just "no" -> notexport
|
|
|
|
Just _ -> error "bad exporttree value"
|
2017-09-07 17:45:31 +00:00
|
|
|
where
|
2017-09-13 16:05:53 +00:00
|
|
|
notexport = return $ r
|
|
|
|
{ exportActions = exportUnsupported
|
|
|
|
, remotetype = (remotetype r)
|
|
|
|
{ exportSupported = exportUnsupported
|
|
|
|
}
|
|
|
|
}
|
2017-09-07 17:45:31 +00:00
|
|
|
isexport = do
|
|
|
|
db <- openDb (uuid r)
|
|
|
|
return $ r
|
2017-09-04 20:39:56 +00:00
|
|
|
-- Storing a key on an export would need a way to
|
|
|
|
-- look up the file(s) that the currently exported
|
|
|
|
-- tree uses for a key; there's not currently an
|
|
|
|
-- inexpensive way to do that (getExportLocation
|
|
|
|
-- only finds files that have been stored on the
|
|
|
|
-- export already).
|
|
|
|
{ storeKey = \_ _ _ -> do
|
|
|
|
warning "remote is configured with exporttree=yes; use `git-annex export` to store content on it"
|
|
|
|
return False
|
|
|
|
-- Keys can be retrieved, but since an export
|
|
|
|
-- is not a true key/value store, the content of
|
|
|
|
-- the key has to be able to be strongly verified.
|
2017-09-08 18:24:05 +00:00
|
|
|
, retrieveKeyFile = \k _af dest p -> unVerified $
|
2017-09-04 20:39:56 +00:00
|
|
|
if maybe False (isJust . verifyKeyContent) (maybeLookupBackendVariety (keyVariety k))
|
|
|
|
then do
|
|
|
|
locs <- liftIO $ getExportLocation db k
|
|
|
|
case locs of
|
|
|
|
[] -> do
|
|
|
|
warning "unknown export location"
|
2017-09-08 18:24:05 +00:00
|
|
|
return False
|
2017-09-12 20:59:04 +00:00
|
|
|
(l:_) -> do
|
|
|
|
ea <- exportActions r
|
|
|
|
retrieveExport ea k l dest p
|
2017-09-04 20:39:56 +00:00
|
|
|
else do
|
|
|
|
warning $ "exported content cannot be verified due to using the " ++ formatKeyVariety (keyVariety k) ++ " backend"
|
2017-09-08 18:24:05 +00:00
|
|
|
return False
|
2017-09-04 20:39:56 +00:00
|
|
|
, retrieveKeyFileCheap = \_ _ _ -> return False
|
|
|
|
-- Remove all files a key was exported to.
|
|
|
|
, removeKey = \k -> do
|
|
|
|
locs <- liftIO $ getExportLocation db k
|
2017-09-12 20:59:04 +00:00
|
|
|
ea <- exportActions r
|
2017-09-04 20:39:56 +00:00
|
|
|
oks <- forM locs $ \loc -> do
|
2017-09-12 20:59:04 +00:00
|
|
|
ok <- removeExport ea k loc
|
2017-09-04 20:39:56 +00:00
|
|
|
when ok $
|
|
|
|
liftIO $ removeExportLocation db k loc
|
|
|
|
return ok
|
|
|
|
liftIO $ flushDbQueue db
|
|
|
|
return (and oks)
|
|
|
|
-- Can't lock content on exports, since they're
|
|
|
|
-- not key/value stores, and someone else could
|
|
|
|
-- change what's exported to a file at any time.
|
|
|
|
, lockContent = Nothing
|
|
|
|
-- Check if any of the files a key was exported
|
|
|
|
-- to are present. This doesn't guarantee the
|
|
|
|
-- export contains the right content.
|
2017-09-12 20:59:04 +00:00
|
|
|
, checkPresent = \k -> do
|
|
|
|
ea <- exportActions r
|
|
|
|
anyM (checkPresentExport ea k)
|
2017-09-04 20:39:56 +00:00
|
|
|
=<< liftIO (getExportLocation db k)
|
2017-09-04 20:55:31 +00:00
|
|
|
, mkUnavailable = return Nothing
|
|
|
|
, getInfo = do
|
|
|
|
is <- getInfo r
|
|
|
|
return (is++[("export", "yes")])
|
2017-09-04 20:39:56 +00:00
|
|
|
}
|