{- git-annex trust log
-
- - Copyright 2010-2022 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2025 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
trustMapLoad,
) where
-import qualified Data.Map as M
-import Data.Default
-
import Annex.Common
import Types.TrustLevel
import qualified Annex
import Logs
import Remote.List
-import qualified Types.Remote
import Logs.Trust.Basic as X
+import qualified Data.Map as M
+
{- Returns a list of UUIDs that the trustLog indicates have the
- specified trust level.
- Note that the list can be incomplete for SemiTrusted, since that's
{- Loads the map, updating the cache, -}
trustMapLoad :: Annex TrustMap
-trustMapLoad = do
- forceoverrides <- Annex.getState Annex.forcetrust
- l <- remoteList
- let untrustoverrides = M.fromList $
- map (\r -> (Types.Remote.uuid r, UnTrusted))
- (filter Types.Remote.untrustworthy l)
- logged <- trustMapRaw
- let configured = M.fromList $ mapMaybe configuredtrust l
- let m = M.unionWith min untrustoverrides $
- M.union forceoverrides $
- M.union configured logged
- Annex.changeState $ \s -> s { Annex.trustmap = Just m }
- return m
- where
- configuredtrust r = (\l -> Just (Types.Remote.uuid r, l))
- =<< readTrustLevel
- =<< remoteAnnexTrustLevel (Types.Remote.gitconfig r)
+trustMapLoad = trustMapLoad' =<< remoteList
{- git-annex trust log, basics
-
- - Copyright 2010-2012 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2025 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module X,
trustSet,
trustMapRaw,
+ trustMapLoad',
) where
import Annex.Common
import Types.TrustLevel
import qualified Annex.Branch
import qualified Annex
+import qualified Types.Remote
import Logs
import Logs.UUIDBased
import Logs.Trust.Pure as X
+import qualified Data.Map as M
+
{- Changes the trust level for a uuid in the trustLog. -}
trustSet :: UUID -> TrustLevel -> Annex ()
trustSet uuid@(UUID _) level = do
- log file. -}
trustMapRaw :: Annex TrustMap
trustMapRaw = calcTrustMap <$> Annex.Branch.get trustLog
+
+trustMapLoad' :: [Remote] -> Annex TrustMap
+trustMapLoad' l = do
+ forceoverrides <- Annex.getState Annex.forcetrust
+ let untrustoverrides = M.fromList $
+ map (\r -> (Types.Remote.uuid r, UnTrusted))
+ (filter Types.Remote.untrustworthy l)
+ logged <- trustMapRaw
+ let configured = M.fromList $ mapMaybe configuredtrust l
+ let m = M.unionWith min untrustoverrides $
+ M.union forceoverrides $
+ M.union configured logged
+ Annex.changeState $ \s -> s { Annex.trustmap = Just m }
+ return m
+ where
+ configuredtrust r = (\lvl -> Just (Types.Remote.uuid r, lvl))
+ =<< readTrustLevel
+ =<< remoteAnnexTrustLevel (Types.Remote.gitconfig r)
import Types.ProposedAccepted
import Types.MetaData
import Types.Creds
+import Types.TrustLevel
+import Types.RemoteState
import Config
import Config.Cost
import Remote.Helper.Special
import Logs.MetaData
import Logs.EquivilantKeys
import Logs.Location
+import Logs.Trust.Basic
+import Logs.Remote
import Messages.Progress
import Utility.Metered
import Utility.TimeStamp
isComputeRemote :: Remote -> Bool
isComputeRemote r = typename (remotetype r) == typename remote
+isComputeRemote' :: RemoteConfig -> Bool
+isComputeRemote' rc = case M.lookup typeField rc of
+ Nothing -> False
+ Just t -> fromProposedAccepted t == typename remote
+
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
gen r u rc gc rs = case getComputeProgram' rc of
Left _err -> return Nothing
rs' <- avoidCycles (inputkey:outputkeys) inputkey' rs
return (rs' == rs)
--- Make sure that the compute state exists.
+-- Make sure that the compute state exists, and that the input keys are
+-- still available (are not dead, and are stored in some repository).
+--
+-- When an input key is itself stored in a compute remote, check that
+-- its inputs are also still available.
checkKey :: RemoteStateHandle -> Key -> Annex Bool
checkKey rs k = do
- states <- getComputeStatesUnsorted rs k
- return (not (null states))
+ deadset <- S.fromList . M.keys . M.filter (== DeadTrusted)
+ <$> (trustMapLoad' =<< Annex.getState Annex.remotes)
+ computeset <- S.fromList . M.keys . M.filter isComputeRemote'
+ <$> remoteConfigMap
+ availablecompute [] deadset computeset k rs
+ where
+ availablecompute inputkeys deadset computeset k' rs'
+ | k' `elem` inputkeys = return False -- avoid cycles
+ | otherwise =
+ anyM (hasinputs inputkeys deadset computeset . snd)
+ =<< getComputeStatesUnsorted rs' k'
+
+ hasinputs inputkeys deadset computeset state = do
+ let ks = M.elems (computeInputs state)
+ ifM (anyM checkDead ks)
+ ( return False
+ , allM (available inputkeys deadset computeset) ks
+ )
+
+ available inputkeys deadset computeset k' = do
+ (repolocs, computelocs) <-
+ partition (flip S.notMember computeset)
+ . filter (flip S.notMember deadset)
+ <$> loggedLocations k'
+ if not (null repolocs)
+ then return True
+ else anyM (availablecompute (k':inputkeys) deadset computeset k' . RemoteStateHandle) computelocs
-- Unsetting the compute state will prevent computing the key.
dropKey :: RemoteStateHandle -> Maybe SafeDropProof -> Key -> Annex ()
Or it could build a DAG and traverse it, but building a DAG of a large
directory tree has its own problems.
-
-* Should checkPresent check that each input file is also present in some
- (non-dead) repo?
-
- Currently it only checks if compute state is recorded. The problem
- this additional checking would solve is if an input file gets lost,
- then a computation cannot be run again.
-
- Should it be an active check against existing remotes, or a
- passive check? An active check certainly makes sense if the input
- file is itself present in a compute repo, either the same one or a
- different one. Otherwise, a passive check seems enough.