2011-07-05 22:31:46 +00:00
|
|
|
{- git-annex key/value backends
|
2010-10-27 20:53:54 +00:00
|
|
|
-
|
2021-02-09 21:03:27 +00:00
|
|
|
- Copyright 2010-2021 Joey Hess <id@joeyh.name>
|
2010-10-27 20:53:54 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2010-10-27 20:53:54 +00:00
|
|
|
-}
|
2010-10-10 17:47:04 +00:00
|
|
|
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2010-10-11 21:52:46 +00:00
|
|
|
module Backend (
|
2020-07-29 19:23:18 +00:00
|
|
|
builtinList,
|
2017-05-09 19:04:07 +00:00
|
|
|
defaultBackend,
|
2011-07-05 22:31:46 +00:00
|
|
|
genKey,
|
2014-04-17 22:03:39 +00:00
|
|
|
getBackend,
|
2012-02-14 03:42:44 +00:00
|
|
|
chooseBackend,
|
2017-02-24 19:16:56 +00:00
|
|
|
lookupBackendVariety,
|
2020-07-29 19:23:18 +00:00
|
|
|
lookupBuiltinBackendVariety,
|
2017-02-24 19:16:56 +00:00
|
|
|
maybeLookupBackendVariety,
|
2014-07-30 14:34:39 +00:00
|
|
|
isStableKey,
|
2020-07-20 16:08:37 +00:00
|
|
|
isCryptographicallySecure,
|
2010-10-11 21:52:46 +00:00
|
|
|
) where
|
2010-10-10 17:47:04 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2010-10-14 07:18:11 +00:00
|
|
|
import qualified Annex
|
2012-02-14 03:42:44 +00:00
|
|
|
import Annex.CheckAttr
|
2017-02-24 19:16:56 +00:00
|
|
|
import Types.Key
|
2012-06-20 20:07:14 +00:00
|
|
|
import Types.KeySource
|
2011-06-02 01:56:04 +00:00
|
|
|
import qualified Types.Backend as B
|
2019-06-25 15:37:52 +00:00
|
|
|
import Utility.Metered
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
-- When adding a new backend, import it here and add it to the builtinList.
|
2013-10-02 00:34:06 +00:00
|
|
|
import qualified Backend.Hash
|
2011-11-04 19:21:45 +00:00
|
|
|
import qualified Backend.WORM
|
2011-08-06 18:57:22 +00:00
|
|
|
import qualified Backend.URL
|
2020-07-29 19:23:18 +00:00
|
|
|
import qualified Backend.External
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2014-07-27 16:24:12 +00:00
|
|
|
import qualified Data.Map as M
|
|
|
|
|
2023-03-14 02:39:16 +00:00
|
|
|
{- Built-in backends. Does not include externals. -}
|
2020-07-29 19:23:18 +00:00
|
|
|
builtinList :: [Backend]
|
|
|
|
builtinList = Backend.Hash.backends ++ Backend.WORM.backends ++ Backend.URL.backends
|
2010-10-14 19:58:53 +00:00
|
|
|
|
2017-05-09 19:04:07 +00:00
|
|
|
{- Backend to use by default when generating a new key. -}
|
|
|
|
defaultBackend :: Annex Backend
|
|
|
|
defaultBackend = maybe cache return =<< Annex.getState Annex.backend
|
2012-10-29 02:09:09 +00:00
|
|
|
where
|
2017-05-09 19:04:07 +00:00
|
|
|
cache = do
|
|
|
|
n <- maybe (annexBackend <$> Annex.getGitConfig) (return . Just)
|
2022-06-28 19:28:14 +00:00
|
|
|
=<< Annex.getRead Annex.forcebackend
|
2020-07-29 19:23:18 +00:00
|
|
|
b <- case n of
|
2017-05-09 19:04:07 +00:00
|
|
|
Just name | valid name -> lookupname name
|
2020-07-29 19:23:18 +00:00
|
|
|
_ -> pure (Prelude.head builtinList)
|
2017-05-09 19:04:07 +00:00
|
|
|
Annex.changeState $ \s -> s { Annex.backend = Just b }
|
|
|
|
return b
|
|
|
|
valid name = not (null name)
|
2019-01-11 20:34:04 +00:00
|
|
|
lookupname = lookupBackendVariety . parseKeyVariety . encodeBS
|
2010-10-17 15:47:36 +00:00
|
|
|
|
2017-05-09 19:04:07 +00:00
|
|
|
{- Generates a key for a file. -}
|
2023-03-27 19:10:46 +00:00
|
|
|
genKey :: KeySource -> MeterUpdate -> Backend -> Annex (Key, Backend)
|
|
|
|
genKey source meterupdate b = case B.genKey b of
|
|
|
|
Just a -> do
|
|
|
|
k <- a source meterupdate
|
|
|
|
return (k, b)
|
|
|
|
Nothing -> giveup $ "Cannot generate a key for backend " ++
|
|
|
|
decodeBS (formatKeyVariety (B.backendVariety b))
|
2011-03-23 21:57:10 +00:00
|
|
|
|
2014-04-17 22:03:39 +00:00
|
|
|
getBackend :: FilePath -> Key -> Annex (Maybe Backend)
|
2020-07-29 19:23:18 +00:00
|
|
|
getBackend file k = maybeLookupBackendVariety (fromKey keyVariety k) >>= \case
|
2017-02-24 19:16:56 +00:00
|
|
|
Just backend -> return $ Just backend
|
|
|
|
Nothing -> do
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
warning $ "skipping " <> QuotedPath (toRawFilePath file) <> " (" <>
|
|
|
|
UnquotedString (unknownBackendVarietyMessage (fromKey keyVariety k)) <> ")"
|
2017-02-24 19:16:56 +00:00
|
|
|
return Nothing
|
2010-11-01 21:50:37 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
unknownBackendVarietyMessage :: KeyVariety -> String
|
|
|
|
unknownBackendVarietyMessage v =
|
|
|
|
"unknown backend " ++ decodeBS (formatKeyVariety v)
|
|
|
|
|
2012-02-14 03:42:44 +00:00
|
|
|
{- Looks up the backend that should be used for a file.
|
2017-05-09 19:04:07 +00:00
|
|
|
- That can be configured on a per-file basis in the gitattributes file,
|
|
|
|
- or forced with --backend. -}
|
2023-03-27 19:10:46 +00:00
|
|
|
chooseBackend :: RawFilePath -> Annex Backend
|
2022-06-28 19:28:14 +00:00
|
|
|
chooseBackend f = Annex.getRead Annex.forcebackend >>= go
|
2012-10-29 02:09:09 +00:00
|
|
|
where
|
2023-03-27 19:10:46 +00:00
|
|
|
go Nothing = do
|
|
|
|
mb <- maybeLookupBackendVariety . parseKeyVariety . encodeBS
|
|
|
|
=<< checkAttr "annex.backend" f
|
|
|
|
case mb of
|
|
|
|
Just b -> return b
|
|
|
|
Nothing -> defaultBackend
|
|
|
|
go (Just _) = defaultBackend
|
2011-03-23 06:10:59 +00:00
|
|
|
|
2017-02-24 19:16:56 +00:00
|
|
|
{- Looks up a backend by variety. May fail if unsupported or disabled. -}
|
2020-07-29 19:23:18 +00:00
|
|
|
lookupBackendVariety :: KeyVariety -> Annex Backend
|
|
|
|
lookupBackendVariety v = fromMaybe (giveup (unknownBackendVarietyMessage v))
|
|
|
|
<$> maybeLookupBackendVariety v
|
|
|
|
|
|
|
|
lookupBuiltinBackendVariety :: KeyVariety -> Backend
|
|
|
|
lookupBuiltinBackendVariety v = fromMaybe (giveup (unknownBackendVarietyMessage v)) $
|
|
|
|
maybeLookupBuiltinBackendVariety v
|
|
|
|
|
|
|
|
maybeLookupBackendVariety :: KeyVariety -> Annex (Maybe Backend)
|
|
|
|
maybeLookupBackendVariety (ExternalKey s hasext) =
|
|
|
|
Just <$> Backend.External.makeBackend s hasext
|
|
|
|
maybeLookupBackendVariety v =
|
|
|
|
pure $ M.lookup v varietyMap
|
2014-07-27 16:24:12 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
maybeLookupBuiltinBackendVariety :: KeyVariety -> Maybe Backend
|
|
|
|
maybeLookupBuiltinBackendVariety v = M.lookup v varietyMap
|
2014-07-27 16:24:12 +00:00
|
|
|
|
2017-02-24 19:16:56 +00:00
|
|
|
varietyMap :: M.Map KeyVariety Backend
|
2020-07-29 19:23:18 +00:00
|
|
|
varietyMap = M.fromList $ zip (map B.backendVariety builtinList) builtinList
|
2014-07-27 16:33:46 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
isStableKey :: Key -> Annex Bool
|
2014-07-30 14:34:39 +00:00
|
|
|
isStableKey k = maybe False (`B.isStableKey` k)
|
2020-07-29 19:23:18 +00:00
|
|
|
<$> maybeLookupBackendVariety (fromKey keyVariety k)
|
2020-07-20 16:08:37 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
isCryptographicallySecure :: Key -> Annex Bool
|
2023-03-27 19:10:46 +00:00
|
|
|
isCryptographicallySecure k = maybe False B.isCryptographicallySecure
|
2020-07-29 19:23:18 +00:00
|
|
|
<$> maybeLookupBackendVariety (fromKey keyVariety k)
|