git-annex/Annex/NumCopies.hs

218 lines
7.5 KiB
Haskell
Raw Normal View History

2015-04-30 18:02:56 +00:00
{- git-annex numcopies configuration and checking
2014-01-21 22:08:56 +00:00
-
2015-04-30 18:02:56 +00:00
- Copyright 2014-2015 Joey Hess <id@joeyh.name>
2014-01-21 22:08:56 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP, ScopedTypeVariables, DeriveDataTypeable #-}
2015-04-30 18:02:56 +00:00
module Annex.NumCopies (
2014-01-21 22:08:56 +00:00
module Types.NumCopies,
module Logs.NumCopies,
getFileNumCopies,
getGlobalFileNumCopies,
getNumCopies,
deprecatedNumCopies,
defaultNumCopies,
numCopiesCheck,
numCopiesCheck',
2015-10-09 15:09:46 +00:00
verifyEnoughCopiesToDrop,
verifiableCopies,
UnVerifiedCopy(..),
2014-01-21 22:08:56 +00:00
) where
import Annex.Common
2014-01-21 22:08:56 +00:00
import qualified Annex
import Types.NumCopies
import Logs.NumCopies
import Logs.Trust
import Annex.CheckAttr
import qualified Remote
2015-10-09 16:36:04 +00:00
import qualified Types.Remote as Remote
2015-04-30 18:02:56 +00:00
import Annex.Content
import Annex.UUID
2014-01-21 22:08:56 +00:00
import Control.Exception
import qualified Control.Monad.Catch as M
import Data.Typeable
2014-01-21 22:08:56 +00:00
defaultNumCopies :: NumCopies
defaultNumCopies = NumCopies 1
fromSources :: [Annex (Maybe NumCopies)] -> Annex NumCopies
fromSources = fromMaybe defaultNumCopies <$$> getM id
{- The git config annex.numcopies is deprecated. -}
deprecatedNumCopies :: Annex (Maybe NumCopies)
deprecatedNumCopies = annexNumCopies <$> Annex.getGitConfig
{- Value forced on the command line by --numcopies. -}
getForcedNumCopies :: Annex (Maybe NumCopies)
getForcedNumCopies = Annex.getState Annex.forcenumcopies
{- Numcopies value from any of the non-.gitattributes configuration
- sources. -}
getNumCopies :: Annex NumCopies
getNumCopies = fromSources
[ getForcedNumCopies
, getGlobalNumCopies
, deprecatedNumCopies
]
{- Numcopies value for a file, from any configuration source, including the
- deprecated git config. -}
getFileNumCopies :: FilePath -> Annex NumCopies
getFileNumCopies f = fromSources
[ getForcedNumCopies
, getFileNumCopies' f
, deprecatedNumCopies
]
{- This is the globally visible numcopies value for a file. So it does
- not include local configuration in the git config or command line
- options. -}
getGlobalFileNumCopies :: FilePath -> Annex NumCopies
getGlobalFileNumCopies f = fromSources
[ getFileNumCopies' f
]
getFileNumCopies' :: FilePath -> Annex (Maybe NumCopies)
getFileNumCopies' file = maybe getGlobalNumCopies (return . Just) =<< getattr
where
getattr = (NumCopies <$$> readish)
<$> checkAttr "annex.numcopies" file
{- Checks if numcopies are satisfied for a file by running a comparison
- between the number of (not untrusted) copies that are
- belived to exist, and the configured value.
-
- This is good enough for everything except dropping the file, which
- requires active verification of the copies.
-}
2014-01-21 22:08:56 +00:00
numCopiesCheck :: FilePath -> Key -> (Int -> Int -> v) -> Annex v
numCopiesCheck file key vs = do
have <- trustExclude UnTrusted =<< Remote.keyLocations key
numCopiesCheck' file vs have
numCopiesCheck' :: FilePath -> (Int -> Int -> v) -> [UUID] -> Annex v
numCopiesCheck' file vs have = do
NumCopies needed <- getFileNumCopies file
2014-01-21 22:08:56 +00:00
return $ length have `vs` needed
2015-04-30 18:02:56 +00:00
data UnVerifiedCopy = UnVerifiedRemote Remote | UnVerifiedHere
deriving (Ord, Eq)
2015-04-30 18:02:56 +00:00
{- Verifies that enough copies of a key exist amoung the listed remotes,
- to safely drop it, running an action with a proof if so, and
- printing an informative message if not.
2015-04-30 18:02:56 +00:00
-}
2015-10-09 15:09:46 +00:00
verifyEnoughCopiesToDrop
2015-04-30 18:02:56 +00:00
:: String -- message to print when there are no known locations
-> Key
-> Maybe ContentRemovalLock
2015-04-30 18:02:56 +00:00
-> NumCopies
-> [UUID] -- repos to skip considering (generally untrusted remotes)
-> [VerifiedCopy] -- copies already verified to exist
-> [UnVerifiedCopy] -- places to check to see if they have copies
-> (SafeDropProof -> Annex a) -- action to perform the drop
2015-10-09 15:09:46 +00:00
-> Annex a -- action to perform when unable to drop
-> Annex a
verifyEnoughCopiesToDrop nolocmsg key removallock need skip preverified tocheck dropaction nodropaction =
helper [] [] preverified (nub tocheck)
2015-04-30 18:02:56 +00:00
where
2017-12-05 19:00:50 +00:00
helper bad missing have [] =
liftIO (mkSafeDropProof need have removallock) >>= \case
2015-10-09 15:09:46 +00:00
Right proof -> dropaction proof
Left stillhave -> do
notEnoughCopies key need stillhave (skip++missing) bad nolocmsg
nodropaction
helper bad missing have (c:cs)
2017-12-05 19:00:50 +00:00
| isSafeDrop need have removallock =
liftIO (mkSafeDropProof need have removallock) >>= \case
2015-10-09 15:09:46 +00:00
Right proof -> dropaction proof
Left stillhave -> helper bad missing stillhave (c:cs)
| otherwise = case c of
UnVerifiedHere -> lockContentShared key contverified
2017-12-05 19:00:50 +00:00
UnVerifiedRemote r -> checkremote r contverified $
Remote.hasKey r key >>= \case
Right True -> helper bad missing (mkVerifiedCopy RecentlyVerifiedCopy r : have) cs
Left _ -> helper (r:bad) missing have cs
Right False -> helper bad (Remote.uuid r:missing) have cs
where
contverified vc = helper bad missing (vc : have) cs
checkremote r cont fallback = case Remote.lockContent r of
Just lockcontent -> do
-- The remote's lockContent will throw an exception
-- when it is unable to lock, in which case the
-- fallback should be run.
--
-- On the other hand, the continuation could itself
-- throw an exception (ie, the eventual drop action
-- fails), and in this case we don't want to run the
-- fallback since part of the drop action may have
-- already been performed.
--
-- Differentiate between these two sorts
-- of exceptions by using DropException.
let a = lockcontent key $ \v ->
cont v `catchNonAsync` (throw . DropException)
a `M.catches`
[ M.Handler (\ (e :: AsyncException) -> throwM e)
#if MIN_VERSION_base(4,7,0)
, M.Handler (\ (e :: SomeAsyncException) -> throwM e)
#endif
, M.Handler (\ (DropException e') -> throwM e')
, M.Handler (\ (_e :: SomeException) -> fallback)
]
Nothing -> fallback
2015-04-30 18:02:56 +00:00
data DropException = DropException SomeException
deriving (Typeable, Show)
instance Exception DropException
notEnoughCopies :: Key -> NumCopies -> [VerifiedCopy] -> [UUID] -> [Remote] -> String -> Annex ()
2015-04-30 18:02:56 +00:00
notEnoughCopies key need have skip bad nolocmsg = do
showNote "unsafe"
if length have < fromNumCopies need
then showLongNote $
"Could only verify the existence of " ++
show (length have) ++ " out of " ++ show (fromNumCopies need) ++
" necessary copies"
else do
showLongNote "Unable to lock down 1 copy of file that is required to safely drop it."
showLongNote "(This could have happened because of a concurrent drop, or because a remote has too old a version of git-annex-shell installed.)"
2015-04-30 18:02:56 +00:00
Remote.showTriedRemotes bad
Remote.showLocations True key (map toUUID have++skip) nolocmsg
2015-04-30 18:02:56 +00:00
{- Finds locations of a key that can be used to get VerifiedCopies,
- in order to allow dropping the key.
-
- Provide a list of UUIDs that the key is being dropped from.
- The returned lists will exclude any of those UUIDs.
-
- The return lists also exclude any repositories that are untrusted,
- since those should not be used for verification.
2015-04-30 18:02:56 +00:00
-
- The UnVerifiedCopy list is cost ordered.
- The VerifiedCopy list contains repositories that are trusted to
- contain the key.
2015-04-30 18:02:56 +00:00
-}
verifiableCopies :: Key -> [UUID] -> Annex ([UnVerifiedCopy], [VerifiedCopy])
verifiableCopies key exclude = do
locs <- Remote.keyLocations key
(remotes, trusteduuids) <- Remote.remoteLocations locs
=<< trustGet Trusted
untrusteduuids <- trustGet UnTrusted
let exclude' = exclude ++ untrusteduuids
let remotes' = Remote.remotesWithoutUUID remotes (exclude' ++ trusteduuids)
let verified = map (mkVerifiedCopy TrustedCopy) $
filter (`notElem` exclude') trusteduuids
2015-04-30 18:02:56 +00:00
u <- getUUID
let herec = if u `elem` locs && u `notElem` exclude'
then [UnVerifiedHere]
else []
return (herec ++ map UnVerifiedRemote remotes', verified)