reorganize log modules
no code changes
This commit is contained in:
parent
279150ccd5
commit
1a29b5b52e
44 changed files with 92 additions and 92 deletions
|
@ -22,8 +22,8 @@ module Annex.Content (
|
|||
) where
|
||||
|
||||
import Common.Annex
|
||||
import LocationLog
|
||||
import UUID
|
||||
import Logs.Location
|
||||
import Logs.UUID
|
||||
import qualified Git
|
||||
import qualified Annex
|
||||
import qualified Annex.Queue
|
||||
|
@ -52,7 +52,7 @@ calcGitLink file key = do
|
|||
where
|
||||
whoops = error $ "unable to normalize " ++ file
|
||||
|
||||
{- Updates the LocationLog when a key's presence changes in the current
|
||||
{- Updates the Logs.Location when a key's presence changes in the current
|
||||
- repository. -}
|
||||
logStatus :: Key -> LogStatus -> Annex ()
|
||||
logStatus key status = do
|
||||
|
|
|
@ -13,8 +13,8 @@ import qualified Annex
|
|||
import qualified Git
|
||||
import qualified Git.LsFiles as LsFiles
|
||||
import Types.Key
|
||||
import Trust
|
||||
import LocationLog
|
||||
import Logs.Trust
|
||||
import Logs.Location
|
||||
import Config
|
||||
import Backend
|
||||
import Limit
|
||||
|
|
|
@ -13,7 +13,7 @@ import Command
|
|||
import qualified Annex
|
||||
import qualified Annex.Queue
|
||||
import qualified Backend
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
import Utility.Touch
|
||||
import Backend
|
||||
|
|
|
@ -18,7 +18,7 @@ import qualified Command.Add
|
|||
import qualified Annex
|
||||
import qualified Backend.URL
|
||||
import Annex.Content
|
||||
import PresenceLog
|
||||
import Logs.Presence
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "addurl" (paramRepeating paramUrl) seek
|
||||
|
|
|
@ -9,7 +9,7 @@ module Command.ConfigList where
|
|||
|
||||
import Common.Annex
|
||||
import Command
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "configlist" paramNothing seek
|
||||
|
|
|
@ -10,7 +10,7 @@ module Command.Describe where
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Remote
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "describe" (paramPair paramRemote paramDesc) seek
|
||||
|
|
|
@ -11,9 +11,9 @@ import Common.Annex
|
|||
import Command
|
||||
import qualified Remote
|
||||
import qualified Annex
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Logs.Trust
|
||||
import Annex.Content
|
||||
import Trust
|
||||
import Config
|
||||
|
||||
command :: [Command]
|
||||
|
|
|
@ -10,7 +10,7 @@ module Command.DropKey where
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Annex
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
|
||||
command :: [Command]
|
||||
|
|
|
@ -12,10 +12,10 @@ import Command
|
|||
import qualified Remote
|
||||
import qualified Types.Backend
|
||||
import qualified Types.Key
|
||||
import UUID
|
||||
import Annex.Content
|
||||
import LocationLog
|
||||
import Trust
|
||||
import Logs.Location
|
||||
import Logs.Trust
|
||||
import Logs.UUID
|
||||
import Utility.DataUnits
|
||||
import Utility.FileMode
|
||||
import Config
|
||||
|
|
|
@ -9,7 +9,7 @@ module Command.Init where
|
|||
|
||||
import Common.Annex
|
||||
import Command
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Init
|
||||
|
||||
command :: [Command]
|
||||
|
|
|
@ -12,9 +12,9 @@ import qualified Data.Map as M
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Remote
|
||||
import qualified RemoteLog
|
||||
import qualified Logs.Remote
|
||||
import qualified Types.Remote as R
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "initremote"
|
||||
|
@ -38,7 +38,7 @@ start ws = do
|
|||
|
||||
where
|
||||
name = head ws
|
||||
config = RemoteLog.keyValToConfig $ tail ws
|
||||
config = Logs.Remote.keyValToConfig $ tail ws
|
||||
needname = do
|
||||
let err s = error $ "Specify a name for the remote. " ++ s
|
||||
names <- remoteNames
|
||||
|
@ -54,13 +54,13 @@ perform t u c = do
|
|||
|
||||
cleanup :: UUID -> R.RemoteConfig -> CommandCleanup
|
||||
cleanup u c = do
|
||||
RemoteLog.configSet u c
|
||||
Logs.Remote.configSet u c
|
||||
return True
|
||||
|
||||
{- Look up existing remote's UUID and config by name, or generate a new one -}
|
||||
findByName :: String -> Annex (UUID, R.RemoteConfig)
|
||||
findByName name = do
|
||||
m <- RemoteLog.readRemoteLog
|
||||
m <- Logs.Remote.readRemoteLog
|
||||
maybe generate return $ findByName' name m
|
||||
where
|
||||
generate = do
|
||||
|
@ -79,7 +79,7 @@ findByName' n m = if null matches then Nothing else Just $ head matches
|
|||
|
||||
remoteNames :: Annex [String]
|
||||
remoteNames = do
|
||||
m <- RemoteLog.readRemoteLog
|
||||
m <- Logs.Remote.readRemoteLog
|
||||
return $ mapMaybe (M.lookup nameKey . snd) $ M.toList m
|
||||
|
||||
{- find the specified remote type -}
|
||||
|
|
|
@ -13,8 +13,8 @@ import qualified Data.Map as M
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Trust
|
||||
import Logs.UUID
|
||||
import Logs.Trust
|
||||
import Utility.Ssh
|
||||
import qualified Utility.Dot as Dot
|
||||
|
||||
|
|
|
@ -11,10 +11,10 @@ import Common.Annex
|
|||
import Command
|
||||
import qualified Command.Drop
|
||||
import qualified Annex
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
import qualified Remote
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "move" paramPaths seek
|
||||
|
|
|
@ -10,8 +10,8 @@ module Command.Semitrust where
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Remote
|
||||
import UUID
|
||||
import Trust
|
||||
import Logs.UUID
|
||||
import Logs.Trust
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "semitrust" (paramRepeating paramRemote) seek
|
||||
|
|
|
@ -9,7 +9,7 @@ module Command.SetKey where
|
|||
|
||||
import Common.Annex
|
||||
import Command
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
|
||||
command :: [Command]
|
||||
|
|
|
@ -23,7 +23,7 @@ import Utility.DataUnits
|
|||
import Annex.Content
|
||||
import Types.Key
|
||||
import Backend
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Remote
|
||||
|
||||
-- a named computation that produces a statistic
|
||||
|
|
|
@ -10,8 +10,8 @@ module Command.Trust where
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Remote
|
||||
import Trust
|
||||
import UUID
|
||||
import Logs.Trust
|
||||
import Logs.UUID
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "trust" (paramRepeating paramRemote) seek
|
||||
|
|
|
@ -13,7 +13,7 @@ import qualified Command.Drop
|
|||
import qualified Annex
|
||||
import qualified Annex.Queue
|
||||
import Utility.FileMode
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
import qualified Git
|
||||
import qualified Git.LsFiles as LsFiles
|
||||
|
|
|
@ -10,8 +10,8 @@ module Command.Untrust where
|
|||
import Common.Annex
|
||||
import Command
|
||||
import qualified Remote
|
||||
import UUID
|
||||
import Trust
|
||||
import Logs.UUID
|
||||
import Logs.Trust
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "untrust" (paramRepeating paramRemote) seek
|
||||
|
|
|
@ -16,7 +16,7 @@ import Common.Annex
|
|||
import Command
|
||||
import Annex.Content
|
||||
import Utility.FileMode
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import qualified Annex
|
||||
import qualified Git
|
||||
import qualified Git.LsFiles as LsFiles
|
||||
|
|
|
@ -8,10 +8,10 @@
|
|||
module Command.Whereis where
|
||||
|
||||
import Common.Annex
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Command
|
||||
import Remote
|
||||
import Trust
|
||||
import Logs.Trust
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "whereis" paramPaths seek
|
||||
|
|
4
Git.hs
4
Git.hs
|
@ -338,9 +338,9 @@ urlHostUser r = urlAuthPart uriUserInfo r ++ urlAuthPart uriRegName' r
|
|||
|
||||
{- The full authority portion an URL repo. (ie, "user@host:port") -}
|
||||
urlAuthority :: Repo -> String
|
||||
urlAuthority = urlAuthPart combine
|
||||
urlAuthority = urlAuthPart assemble
|
||||
where
|
||||
combine a = uriUserInfo a ++ uriRegName' a ++ uriPort a
|
||||
assemble a = uriUserInfo a ++ uriRegName' a ++ uriPort a
|
||||
|
||||
{- Applies a function to extract part of the uriAuthority of an URL repo. -}
|
||||
urlAuthPart :: (URIAuth -> a) -> Repo -> a
|
||||
|
|
2
Init.hs
2
Init.hs
|
@ -15,7 +15,7 @@ import Common.Annex
|
|||
import qualified Git
|
||||
import qualified Annex.Branch
|
||||
import Annex.Version
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
initialize :: Annex ()
|
||||
initialize = do
|
||||
|
|
2
Limit.hs
2
Limit.hs
|
@ -15,7 +15,7 @@ import qualified Annex
|
|||
import qualified Utility.Matcher
|
||||
import qualified Remote
|
||||
import qualified Backend
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
|
||||
type Limit = Utility.Matcher.Token (FilePath -> Annex Bool)
|
||||
|
|
|
@ -11,7 +11,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module LocationLog (
|
||||
module Logs.Location (
|
||||
LogStatus(..),
|
||||
logChange,
|
||||
readLog,
|
||||
|
@ -24,8 +24,8 @@ module LocationLog (
|
|||
import Common.Annex
|
||||
import qualified Git
|
||||
import qualified Annex.Branch
|
||||
import UUID
|
||||
import PresenceLog
|
||||
import Logs.UUID
|
||||
import Logs.Presence
|
||||
|
||||
{- Log a change in the presence of a key's value in a repository. -}
|
||||
logChange :: Git.Repo -> Key -> UUID -> LogStatus -> Annex ()
|
|
@ -11,7 +11,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module PresenceLog (
|
||||
module Logs.Presence (
|
||||
LogStatus(..),
|
||||
addLog,
|
||||
readLog,
|
|
@ -5,7 +5,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module RemoteLog (
|
||||
module Logs.Remote (
|
||||
readRemoteLog,
|
||||
configSet,
|
||||
keyValToConfig,
|
||||
|
@ -21,8 +21,8 @@ import Data.Char
|
|||
import Common.Annex
|
||||
import qualified Annex.Branch
|
||||
import Types.Remote
|
||||
import UUID
|
||||
import UUIDLog
|
||||
import Logs.UUID
|
||||
import Logs.UUIDBased
|
||||
|
||||
{- Filename of remote.log. -}
|
||||
remoteLog :: FilePath
|
|
@ -5,7 +5,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Trust (
|
||||
module Logs.Trust (
|
||||
TrustLevel(..),
|
||||
trustGet,
|
||||
trustSet,
|
||||
|
@ -20,8 +20,8 @@ import Types.TrustLevel
|
|||
import qualified Annex.Branch
|
||||
import qualified Annex
|
||||
|
||||
import UUID
|
||||
import UUIDLog
|
||||
import Logs.UUID
|
||||
import Logs.UUIDBased
|
||||
|
||||
{- Filename of trust.log. -}
|
||||
trustLog :: FilePath
|
|
@ -13,7 +13,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module UUID (
|
||||
module Logs.UUID (
|
||||
UUID,
|
||||
getUUID,
|
||||
getRepoUUID,
|
||||
|
@ -33,7 +33,7 @@ import qualified Annex.Branch
|
|||
import Types.UUID
|
||||
import qualified Build.SysConfig as SysConfig
|
||||
import Config
|
||||
import UUIDLog
|
||||
import Logs.UUIDBased
|
||||
|
||||
configkey :: String
|
||||
configkey = "annex.uuid"
|
|
@ -12,7 +12,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module UUIDLog (
|
||||
module Logs.UUIDBased (
|
||||
Log,
|
||||
LogEntry(..),
|
||||
parseLog,
|
12
Remote.hs
12
Remote.hs
|
@ -34,12 +34,12 @@ import Text.JSON.Generic
|
|||
|
||||
import Common.Annex
|
||||
import Types.Remote
|
||||
import UUID
|
||||
import qualified Annex
|
||||
import Config
|
||||
import Trust
|
||||
import LocationLog
|
||||
import RemoteLog
|
||||
import Logs.UUID
|
||||
import Logs.Trust
|
||||
import Logs.Location
|
||||
import Logs.Remote
|
||||
|
||||
import qualified Remote.Git
|
||||
import qualified Remote.S3
|
||||
|
@ -163,12 +163,12 @@ remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs
|
|||
remotesWithoutUUID :: [Remote Annex] -> [UUID] -> [Remote Annex]
|
||||
remotesWithoutUUID rs us = filter (\r -> uuid r `notElem` us) rs
|
||||
|
||||
{- Cost ordered lists of remotes that the LocationLog indicate may have a key.
|
||||
{- Cost ordered lists of remotes that the Logs.Location indicate may have a key.
|
||||
-}
|
||||
keyPossibilities :: Key -> Annex [Remote Annex]
|
||||
keyPossibilities key = fst <$> keyPossibilities' False key
|
||||
|
||||
{- Cost ordered lists of remotes that the LocationLog indicate may have a key.
|
||||
{- Cost ordered lists of remotes that the Logs.Location indicate may have a key.
|
||||
-
|
||||
- Also returns a list of UUIDs that are trusted to have the key
|
||||
- (some may not have configured remotes).
|
||||
|
|
|
@ -15,7 +15,7 @@ import System.Process
|
|||
import Common.Annex
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Config
|
||||
import Utility.Ssh
|
||||
import Remote.Helper.Special
|
||||
|
|
|
@ -15,7 +15,7 @@ import Common.Annex
|
|||
import Utility.CopyFile
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Config
|
||||
import Utility.FileMode
|
||||
import Remote.Helper.Special
|
||||
|
|
|
@ -17,7 +17,7 @@ import Utility.Ssh
|
|||
import Types.Remote
|
||||
import qualified Git
|
||||
import qualified Annex
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import qualified Annex.Content
|
||||
import qualified Utility.Url as Url
|
||||
import Config
|
||||
|
|
|
@ -12,7 +12,7 @@ import qualified Data.Map as M
|
|||
import Common.Annex
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
{- Special remotes don't have a configured url, so Git.Repo does not
|
||||
- automatically generate remotes for them. This looks for a different
|
||||
|
|
|
@ -15,7 +15,7 @@ import System.Exit
|
|||
import Common.Annex
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Config
|
||||
import Annex.Content
|
||||
import Remote.Helper.Special
|
||||
|
|
|
@ -13,7 +13,7 @@ import qualified Data.Map as M
|
|||
import Common.Annex
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
import Config
|
||||
import Annex.Content
|
||||
import Remote.Helper.Special
|
||||
|
|
|
@ -13,10 +13,10 @@ module Remote.Web (
|
|||
import Common.Annex
|
||||
import Types.Remote
|
||||
import qualified Git
|
||||
import UUID
|
||||
import Config
|
||||
import PresenceLog
|
||||
import LocationLog
|
||||
import Logs.Presence
|
||||
import Logs.Location
|
||||
import Logs.UUID
|
||||
import qualified Utility.Url as Url
|
||||
|
||||
type URLString = String
|
||||
|
|
|
@ -14,7 +14,7 @@ import Data.Char
|
|||
import Common.Annex
|
||||
import Types.Key
|
||||
import Annex.Content
|
||||
import PresenceLog
|
||||
import Logs.Presence
|
||||
import qualified Annex.Queue
|
||||
import qualified Git
|
||||
import qualified Git.LsFiles as LsFiles
|
||||
|
|
|
@ -10,7 +10,7 @@ module Upgrade.V2 where
|
|||
import Common.Annex
|
||||
import qualified Git
|
||||
import qualified Annex.Branch
|
||||
import LocationLog
|
||||
import Logs.Location
|
||||
import Annex.Content
|
||||
|
||||
olddir :: Git.Repo -> FilePath
|
||||
|
|
|
@ -13,7 +13,7 @@ import qualified Git
|
|||
import Utility.SafeCommand
|
||||
import Types
|
||||
import Config
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
{- Generates parameters to ssh to a repository's host and run a command.
|
||||
- Caller is responsible for doing any neccessary shellEscaping of the
|
||||
|
|
|
@ -13,7 +13,7 @@ import qualified Git
|
|||
import CmdLine
|
||||
import Command
|
||||
import Options
|
||||
import UUID
|
||||
import Logs.UUID
|
||||
|
||||
import qualified Command.ConfigList
|
||||
import qualified Command.InAnnex
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
Name: git-annex
|
||||
Version: 3.20111011
|
||||
Version: 3.20111012
|
||||
Cabal-Version: >= 1.6
|
||||
License: GPL
|
||||
Maintainer: Joey Hess <joey@kitenet.net>
|
||||
|
|
34
test.hs
34
test.hs
|
@ -29,12 +29,12 @@ import qualified Locations
|
|||
import qualified Types.Backend
|
||||
import qualified Types
|
||||
import qualified GitAnnex
|
||||
import qualified LocationLog
|
||||
import qualified UUID
|
||||
import qualified UUIDLog
|
||||
import qualified Trust
|
||||
import qualified Logs.Location
|
||||
import qualified Logs.UUID
|
||||
import qualified Logs.UUIDBased
|
||||
import qualified Logs.Trust
|
||||
import qualified Logs.Remote
|
||||
import qualified Remote
|
||||
import qualified RemoteLog
|
||||
import qualified Command.DropUnused
|
||||
import qualified Types.Key
|
||||
import qualified Config
|
||||
|
@ -73,14 +73,14 @@ quickcheck = TestLabel "quickcheck" $ TestList
|
|||
, qctest "prop_idempotent_key_read_show" Types.Key.prop_idempotent_key_read_show
|
||||
, qctest "prop_idempotent_shellEscape" Utility.SafeCommand.prop_idempotent_shellEscape
|
||||
, qctest "prop_idempotent_shellEscape_multiword" Utility.SafeCommand.prop_idempotent_shellEscape_multiword
|
||||
, qctest "prop_idempotent_configEscape" RemoteLog.prop_idempotent_configEscape
|
||||
, qctest "prop_idempotent_configEscape" Logs.Remote.prop_idempotent_configEscape
|
||||
, qctest "prop_parentDir_basics" Utility.Path.prop_parentDir_basics
|
||||
|
||||
, qctest "prop_relPathDirToFile_basics" Utility.Path.prop_relPathDirToFile_basics
|
||||
, qctest "prop_cost_sane" Config.prop_cost_sane
|
||||
, qctest "prop_hmacWithCipher_sane" Crypto.prop_hmacWithCipher_sane
|
||||
, qctest "prop_TimeStamp_sane" UUIDLog.prop_TimeStamp_sane
|
||||
, qctest "prop_addLog_sane" UUIDLog.prop_addLog_sane
|
||||
, qctest "prop_TimeStamp_sane" Logs.UUIDBased.prop_TimeStamp_sane
|
||||
, qctest "prop_addLog_sane" Logs.UUIDBased.prop_addLog_sane
|
||||
]
|
||||
|
||||
blackbox :: Test
|
||||
|
@ -341,22 +341,22 @@ test_fix = "git-annex fix" ~: intmpclonerepo $ do
|
|||
test_trust :: Test
|
||||
test_trust = "git-annex trust/untrust/semitrust" ~: intmpclonerepo $ do
|
||||
git_annex "trust" ["-q", repo] @? "trust failed"
|
||||
trustcheck Trust.Trusted "trusted 1"
|
||||
trustcheck Logs.Trust.Trusted "trusted 1"
|
||||
git_annex "trust" ["-q", repo] @? "trust of trusted failed"
|
||||
trustcheck Trust.Trusted "trusted 2"
|
||||
trustcheck Logs.Trust.Trusted "trusted 2"
|
||||
git_annex "untrust" ["-q", repo] @? "untrust failed"
|
||||
trustcheck Trust.UnTrusted "untrusted 1"
|
||||
trustcheck Logs.Trust.UnTrusted "untrusted 1"
|
||||
git_annex "untrust" ["-q", repo] @? "untrust of untrusted failed"
|
||||
trustcheck Trust.UnTrusted "untrusted 2"
|
||||
trustcheck Logs.Trust.UnTrusted "untrusted 2"
|
||||
git_annex "semitrust" ["-q", repo] @? "semitrust failed"
|
||||
trustcheck Trust.SemiTrusted "semitrusted 1"
|
||||
trustcheck Logs.Trust.SemiTrusted "semitrusted 1"
|
||||
git_annex "semitrust" ["-q", repo] @? "semitrust of semitrusted failed"
|
||||
trustcheck Trust.SemiTrusted "semitrusted 2"
|
||||
trustcheck Logs.Trust.SemiTrusted "semitrusted 2"
|
||||
where
|
||||
repo = "origin"
|
||||
trustcheck expected msg = do
|
||||
present <- annexeval $ do
|
||||
l <- Trust.trustGet expected
|
||||
l <- Logs.Trust.trustGet expected
|
||||
u <- Remote.nameToUUID repo
|
||||
return $ u `elem` l
|
||||
assertBool msg present
|
||||
|
@ -609,11 +609,11 @@ checkdangling f = do
|
|||
|
||||
checklocationlog :: FilePath -> Bool -> Assertion
|
||||
checklocationlog f expected = do
|
||||
thisuuid <- annexeval UUID.getUUID
|
||||
thisuuid <- annexeval Logs.UUID.getUUID
|
||||
r <- annexeval $ Backend.lookupFile f
|
||||
case r of
|
||||
Just (k, _) -> do
|
||||
uuids <- annexeval $ LocationLog.keyLocations k
|
||||
uuids <- annexeval $ Logs.Location.keyLocations k
|
||||
assertEqual ("bad content in location log for " ++ f ++ " key " ++ (show k) ++ " uuid " ++ thisuuid)
|
||||
expected (thisuuid `elem` uuids)
|
||||
_ -> assertFailure $ f ++ " failed to look up key"
|
||||
|
|
Loading…
Reference in a new issue