add a UUID type
Should have done this a long time ago.
This commit is contained in:
parent
b08f7c428b
commit
63a292324d
18 changed files with 67 additions and 55 deletions
|
@ -45,9 +45,8 @@ git_annex_shell r command params
|
||||||
sshcmd uuid = unwords $
|
sshcmd uuid = unwords $
|
||||||
shellcmd : (map shellEscape $ toCommand shellopts) ++
|
shellcmd : (map shellEscape $ toCommand shellopts) ++
|
||||||
uuidcheck uuid
|
uuidcheck uuid
|
||||||
uuidcheck uuid
|
uuidcheck NoUUID = []
|
||||||
| null uuid = []
|
uuidcheck (UUID u) = ["--uuid", u]
|
||||||
| otherwise = ["--uuid", uuid]
|
|
||||||
|
|
||||||
{- Uses a supplied function (such as boolSystem) to run a git-annex-shell
|
{- Uses a supplied function (such as boolSystem) to run a git-annex-shell
|
||||||
- command on a remote.
|
- command on a remote.
|
||||||
|
|
|
@ -30,7 +30,7 @@ configkey = "annex.uuid"
|
||||||
{- Generates a UUID. There is a library for this, but it's not packaged,
|
{- Generates a UUID. There is a library for this, but it's not packaged,
|
||||||
- so use the command line tool. -}
|
- so use the command line tool. -}
|
||||||
genUUID :: IO UUID
|
genUUID :: IO UUID
|
||||||
genUUID = pOpen ReadFromPipe command params hGetLine
|
genUUID = pOpen ReadFromPipe command params $ liftM read . hGetLine
|
||||||
where
|
where
|
||||||
command = SysConfig.uuid
|
command = SysConfig.uuid
|
||||||
params = if command == "uuid"
|
params = if command == "uuid"
|
||||||
|
@ -50,20 +50,23 @@ getRepoUUID r = do
|
||||||
let c = cached g
|
let c = cached g
|
||||||
let u = getUncachedUUID r
|
let u = getUncachedUUID r
|
||||||
|
|
||||||
if c /= u && u /= ""
|
if c /= u && u /= NoUUID
|
||||||
then do
|
then do
|
||||||
updatecache g u
|
updatecache g u
|
||||||
return u
|
return u
|
||||||
else return c
|
else return c
|
||||||
where
|
where
|
||||||
cached g = Git.configGet g cachekey ""
|
cached g = read $ Git.configGet g cachekey ""
|
||||||
updatecache g u = when (g /= r) $ setConfig cachekey u
|
updatecache g u = when (g /= r) $ storeUUID cachekey u
|
||||||
cachekey = "remote." ++ fromMaybe "" (Git.repoRemoteName r) ++ ".annex-uuid"
|
cachekey = "remote." ++ fromMaybe "" (Git.repoRemoteName r) ++ ".annex-uuid"
|
||||||
|
|
||||||
getUncachedUUID :: Git.Repo -> UUID
|
getUncachedUUID :: Git.Repo -> UUID
|
||||||
getUncachedUUID r = Git.configGet r configkey ""
|
getUncachedUUID r = read $ Git.configGet r configkey ""
|
||||||
|
|
||||||
{- Make sure that the repo has an annex.uuid setting. -}
|
{- Make sure that the repo has an annex.uuid setting. -}
|
||||||
prepUUID :: Annex ()
|
prepUUID :: Annex ()
|
||||||
prepUUID = whenM (null <$> getUUID) $
|
prepUUID = whenM ((==) NoUUID <$> getUUID) $
|
||||||
setConfig configkey =<< liftIO genUUID
|
storeUUID configkey =<< liftIO genUUID
|
||||||
|
|
||||||
|
storeUUID :: String -> UUID -> Annex ()
|
||||||
|
storeUUID configfield uuid = setConfig configfield (show uuid)
|
||||||
|
|
|
@ -21,5 +21,5 @@ seek = [withNothing start]
|
||||||
start :: CommandStart
|
start :: CommandStart
|
||||||
start = do
|
start = do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
liftIO $ putStrLn $ "annex.uuid=" ++ u
|
liftIO $ putStrLn $ "annex.uuid=" ++ show u
|
||||||
stop
|
stop
|
||||||
|
|
|
@ -62,7 +62,7 @@ drawMap rs umap ts = Dot.graph $ repos ++ trusted ++ others
|
||||||
others = map (unreachable . uuidnode) $
|
others = map (unreachable . uuidnode) $
|
||||||
filter (`notElem` ruuids) (M.keys umap)
|
filter (`notElem` ruuids) (M.keys umap)
|
||||||
trusted = map (trustworthy . uuidnode) ts
|
trusted = map (trustworthy . uuidnode) ts
|
||||||
uuidnode u = Dot.graphNode u $ M.findWithDefault "" u umap
|
uuidnode u = Dot.graphNode (show u) $ M.findWithDefault "" u umap
|
||||||
|
|
||||||
hostname :: Git.Repo -> String
|
hostname :: Git.Repo -> String
|
||||||
hostname r
|
hostname r
|
||||||
|
@ -76,7 +76,7 @@ basehostname r = head $ split "." $ hostname r
|
||||||
- or the remote name if not. -}
|
- or the remote name if not. -}
|
||||||
repoName :: M.Map UUID String -> Git.Repo -> String
|
repoName :: M.Map UUID String -> Git.Repo -> String
|
||||||
repoName umap r
|
repoName umap r
|
||||||
| null repouuid = fallback
|
| repouuid == NoUUID = fallback
|
||||||
| otherwise = M.findWithDefault fallback repouuid umap
|
| otherwise = M.findWithDefault fallback repouuid umap
|
||||||
where
|
where
|
||||||
repouuid = getUncachedUUID r
|
repouuid = getUncachedUUID r
|
||||||
|
@ -86,8 +86,8 @@ repoName umap r
|
||||||
nodeId :: Git.Repo -> String
|
nodeId :: Git.Repo -> String
|
||||||
nodeId r =
|
nodeId r =
|
||||||
case getUncachedUUID r of
|
case getUncachedUUID r of
|
||||||
"" -> Git.repoLocation r
|
NoUUID -> Git.repoLocation r
|
||||||
u -> u
|
UUID u -> u
|
||||||
|
|
||||||
{- A node representing a repo. -}
|
{- A node representing a repo. -}
|
||||||
node :: M.Map UUID String -> [Git.Repo] -> Git.Repo -> String
|
node :: M.Map UUID String -> [Git.Repo] -> Git.Repo -> String
|
||||||
|
|
|
@ -29,16 +29,15 @@ import Logs.Presence
|
||||||
|
|
||||||
{- Log a change in the presence of a key's value in a repository. -}
|
{- Log a change in the presence of a key's value in a repository. -}
|
||||||
logChange :: Git.Repo -> Key -> UUID -> LogStatus -> Annex ()
|
logChange :: Git.Repo -> Key -> UUID -> LogStatus -> Annex ()
|
||||||
logChange repo key u s
|
logChange _ key (UUID u) s = addLog (logFile key) =<< logNow s u
|
||||||
| null u = error $
|
logChange repo _ NoUUID _ = error $
|
||||||
"unknown UUID for " ++ Git.repoDescribe repo ++
|
"unknown UUID for " ++ Git.repoDescribe repo ++
|
||||||
" (have you run git annex init there?)"
|
" (have you run git annex init there?)"
|
||||||
| otherwise = addLog (logFile key) =<< logNow s u
|
|
||||||
|
|
||||||
{- Returns a list of repository UUIDs that, according to the log, have
|
{- Returns a list of repository UUIDs that, according to the log, have
|
||||||
- the value of a key. -}
|
- the value of a key. -}
|
||||||
keyLocations :: Key -> Annex [UUID]
|
keyLocations :: Key -> Annex [UUID]
|
||||||
keyLocations = currentLog . logFile
|
keyLocations key = map read <$> (currentLog . logFile) key
|
||||||
|
|
||||||
{- Finds all keys that have location log information.
|
{- Finds all keys that have location log information.
|
||||||
- (There may be duplicate keys in the list.) -}
|
- (There may be duplicate keys in the list.) -}
|
||||||
|
|
|
@ -53,13 +53,12 @@ parseTrust s
|
||||||
|
|
||||||
{- Changes the trust level for a uuid in the trustLog. -}
|
{- Changes the trust level for a uuid in the trustLog. -}
|
||||||
trustSet :: UUID -> TrustLevel -> Annex ()
|
trustSet :: UUID -> TrustLevel -> Annex ()
|
||||||
trustSet uuid level = do
|
trustSet uuid@(UUID _) level = do
|
||||||
when (null uuid) $
|
|
||||||
error "unknown UUID; cannot modify trust level"
|
|
||||||
ts <- liftIO $ getPOSIXTime
|
ts <- liftIO $ getPOSIXTime
|
||||||
Annex.Branch.change trustLog $
|
Annex.Branch.change trustLog $
|
||||||
showLog show . changeLog ts uuid level . parseLog parseTrust
|
showLog show . changeLog ts uuid level . parseLog parseTrust
|
||||||
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
|
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
|
||||||
|
trustSet NoUUID _ = error "unknown UUID; cannot modify trust level"
|
||||||
|
|
||||||
{- Partitions a list of UUIDs to those matching a TrustLevel and not. -}
|
{- Partitions a list of UUIDs to those matching a TrustLevel and not. -}
|
||||||
trustPartition :: TrustLevel -> [UUID] -> Annex ([UUID], [UUID])
|
trustPartition :: TrustLevel -> [UUID] -> Annex ([UUID], [UUID])
|
||||||
|
|
|
@ -50,9 +50,9 @@ showLog :: (a -> String) -> Log a -> String
|
||||||
showLog shower = unlines . map showpair . M.toList
|
showLog shower = unlines . map showpair . M.toList
|
||||||
where
|
where
|
||||||
showpair (k, LogEntry (Date p) v) =
|
showpair (k, LogEntry (Date p) v) =
|
||||||
unwords [k, shower v, tskey ++ show p]
|
unwords [show k, shower v, tskey ++ show p]
|
||||||
showpair (k, LogEntry Unknown v) =
|
showpair (k, LogEntry Unknown v) =
|
||||||
unwords [k, shower v]
|
unwords [show k, shower v]
|
||||||
|
|
||||||
parseLog :: (String -> Maybe a) -> String -> Log a
|
parseLog :: (String -> Maybe a) -> String -> Log a
|
||||||
parseLog parser = M.fromListWith best . catMaybes . map pair . lines
|
parseLog parser = M.fromListWith best . catMaybes . map pair . lines
|
||||||
|
@ -61,7 +61,7 @@ parseLog parser = M.fromListWith best . catMaybes . map pair . lines
|
||||||
| null ws = Nothing
|
| null ws = Nothing
|
||||||
| otherwise = case parser $ unwords info of
|
| otherwise = case parser $ unwords info of
|
||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
Just v -> Just (u, LogEntry c v)
|
Just v -> Just (read u, LogEntry c v)
|
||||||
where
|
where
|
||||||
ws = words line
|
ws = words line
|
||||||
u = head ws
|
u = head ws
|
||||||
|
@ -103,8 +103,8 @@ prop_TimeStamp_sane = Unknown < Date 1
|
||||||
prop_addLog_sane :: Bool
|
prop_addLog_sane :: Bool
|
||||||
prop_addLog_sane = newWins && newestWins
|
prop_addLog_sane = newWins && newestWins
|
||||||
where
|
where
|
||||||
newWins = addLog "foo" (LogEntry (Date 1) "new") l == l2
|
newWins = addLog (UUID "foo") (LogEntry (Date 1) "new") l == l2
|
||||||
newestWins = addLog "foo" (LogEntry (Date 1) "newest") l2 /= l2
|
newestWins = addLog (UUID "foo") (LogEntry (Date 1) "newest") l2 /= l2
|
||||||
|
|
||||||
l = M.fromList [("foo", LogEntry (Date 0) "old")]
|
l = M.fromList [(UUID "foo", LogEntry (Date 0) "old")]
|
||||||
l2 = M.fromList [("foo", LogEntry (Date 1) "new")]
|
l2 = M.fromList [(UUID "foo", LogEntry (Date 1) "new")]
|
||||||
|
|
|
@ -21,7 +21,7 @@ type URLString = String
|
||||||
|
|
||||||
-- Dummy uuid for the whole web. Do not alter.
|
-- Dummy uuid for the whole web. Do not alter.
|
||||||
webUUID :: UUID
|
webUUID :: UUID
|
||||||
webUUID = "00000000-0000-0000-0000-000000000001"
|
webUUID = UUID "00000000-0000-0000-0000-000000000001"
|
||||||
|
|
||||||
{- The urls for a key are stored in remote/web/hash/key.log
|
{- The urls for a key are stored in remote/web/hash/key.log
|
||||||
- in the git-annex branch. -}
|
- in the git-annex branch. -}
|
||||||
|
|
15
Remote.hs
15
Remote.hs
|
@ -100,7 +100,7 @@ byName' n = do
|
||||||
then return $ Left $ "there is no git remote named \"" ++ n ++ "\""
|
then return $ Left $ "there is no git remote named \"" ++ n ++ "\""
|
||||||
else return $ Right $ head match
|
else return $ Right $ head match
|
||||||
where
|
where
|
||||||
matching r = n == name r || n == uuid r
|
matching r = n == name r || read n == uuid r
|
||||||
|
|
||||||
{- Looks up a remote by name (or by UUID, or even by description),
|
{- Looks up a remote by name (or by UUID, or even by description),
|
||||||
- and returns its UUID. Finds even remotes that are not configured in
|
- and returns its UUID. Finds even remotes that are not configured in
|
||||||
|
@ -115,12 +115,13 @@ nameToUUID n = do
|
||||||
where
|
where
|
||||||
byDescription = do
|
byDescription = do
|
||||||
m <- uuidMap
|
m <- uuidMap
|
||||||
case M.lookup n $ transform swap m of
|
case M.lookup wantuuid $ transform swap m of
|
||||||
Just u -> return $ Just u
|
Just u -> return $ Just u
|
||||||
Nothing -> return $ M.lookup n $ transform double m
|
Nothing -> return $ M.lookup wantuuid $ transform double m
|
||||||
transform a = M.fromList . map a . M.toList
|
transform a = M.fromList . map a . M.toList
|
||||||
swap (a, b) = (b, a)
|
swap (a, b) = (b, a)
|
||||||
double (a, _) = (a, a)
|
double (a, _) = (show a, a)
|
||||||
|
wantuuid = read n
|
||||||
|
|
||||||
{- Pretty-prints a list of UUIDs of remotes, for human display.
|
{- Pretty-prints a list of UUIDs of remotes, for human display.
|
||||||
-
|
-
|
||||||
|
@ -143,8 +144,8 @@ prettyPrintUUIDs desc uuids = do
|
||||||
remoteMap = M.fromList . map (\r -> (uuid r, name r)) <$> genList
|
remoteMap = M.fromList . map (\r -> (uuid r, name r)) <$> genList
|
||||||
findlog m u = M.findWithDefault "" u m
|
findlog m u = M.findWithDefault "" u m
|
||||||
prettify m here u
|
prettify m here u
|
||||||
| not (null d) = u ++ " -- " ++ d
|
| not (null d) = show u ++ " -- " ++ d
|
||||||
| otherwise = u
|
| otherwise = show u
|
||||||
where
|
where
|
||||||
ishere = here == u
|
ishere = here == u
|
||||||
n = findlog m u
|
n = findlog m u
|
||||||
|
@ -153,7 +154,7 @@ prettyPrintUUIDs desc uuids = do
|
||||||
| ishere = addname n "here"
|
| ishere = addname n "here"
|
||||||
| otherwise = n
|
| otherwise = n
|
||||||
jsonify m here u = toJSObject
|
jsonify m here u = toJSObject
|
||||||
[ ("uuid", toJSON u)
|
[ ("uuid", toJSON $ show u)
|
||||||
, ("description", toJSON $ findlog m u)
|
, ("description", toJSON $ findlog m u)
|
||||||
, ("here", toJSON $ here == u)
|
, ("here", toJSON $ here == u)
|
||||||
]
|
]
|
||||||
|
|
|
@ -161,13 +161,13 @@ storeBupUUID u buprepo = do
|
||||||
then do
|
then do
|
||||||
showAction "storing uuid"
|
showAction "storing uuid"
|
||||||
onBupRemote r boolSystem "git"
|
onBupRemote r boolSystem "git"
|
||||||
[Params $ "config annex.uuid " ++ u]
|
[Params $ "config annex.uuid " ++ show u]
|
||||||
>>! error "ssh failed"
|
>>! error "ssh failed"
|
||||||
else liftIO $ do
|
else liftIO $ do
|
||||||
r' <- Git.configRead r
|
r' <- Git.configRead r
|
||||||
let olduuid = Git.configGet r' "annex.uuid" ""
|
let olduuid = Git.configGet r' "annex.uuid" ""
|
||||||
when (olduuid == "") $
|
when (olduuid == "") $
|
||||||
Git.run r' "config" [Param "annex.uuid", Param u]
|
Git.run r' "config" [Param "annex.uuid", Param $ show u]
|
||||||
|
|
||||||
onBupRemote :: Git.Repo -> (FilePath -> [CommandParam] -> IO a) -> FilePath -> [CommandParam] -> Annex a
|
onBupRemote :: Git.Repo -> (FilePath -> [CommandParam] -> IO a) -> FilePath -> [CommandParam] -> Annex a
|
||||||
onBupRemote r a command params = do
|
onBupRemote r a command params = do
|
||||||
|
@ -192,8 +192,8 @@ getBupUUID r u
|
||||||
| otherwise = liftIO $ do
|
| otherwise = liftIO $ do
|
||||||
ret <- try $ Git.configRead r
|
ret <- try $ Git.configRead r
|
||||||
case ret of
|
case ret of
|
||||||
Right r' -> return (Git.configGet r' "annex.uuid" "", r')
|
Right r' -> return (read $ Git.configGet r' "annex.uuid" "", r')
|
||||||
Left _ -> return ("", r)
|
Left _ -> return (NoUUID, r)
|
||||||
|
|
||||||
{- Converts a bup remote path spec into a Git.Repo. There are some
|
{- Converts a bup remote path spec into a Git.Repo. There are some
|
||||||
- differences in path representation between git and bup. -}
|
- differences in path representation between git and bup. -}
|
||||||
|
|
|
@ -60,7 +60,7 @@ gen r u _ = do
|
||||||
r' <- case (cheap, notignored, u) of
|
r' <- case (cheap, notignored, u) of
|
||||||
(_, False, _) -> return r
|
(_, False, _) -> return r
|
||||||
(True, _, _) -> tryGitConfigRead r
|
(True, _, _) -> tryGitConfigRead r
|
||||||
(False, _, "") -> tryGitConfigRead r
|
(False, _, NoUUID) -> tryGitConfigRead r
|
||||||
_ -> return r
|
_ -> return r
|
||||||
|
|
||||||
u' <- getRepoUUID r'
|
u' <- getRepoUUID r'
|
||||||
|
|
|
@ -32,7 +32,7 @@ gitConfigSpecialRemote u c k v = do
|
||||||
g <- gitRepo
|
g <- gitRepo
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
Git.run g "config" [Param (configsetting $ "annex-"++k), Param v]
|
Git.run g "config" [Param (configsetting $ "annex-"++k), Param v]
|
||||||
Git.run g "config" [Param (configsetting "annex-uuid"), Param u]
|
Git.run g "config" [Param (configsetting "annex-uuid"), Param $ show u]
|
||||||
where
|
where
|
||||||
remotename = fromJust (M.lookup "name" c)
|
remotename = fromJust (M.lookup "name" c)
|
||||||
configsetting s = "remote." ++ remotename ++ "." ++ s
|
configsetting s = "remote." ++ remotename ++ "." ++ s
|
||||||
|
|
|
@ -64,7 +64,7 @@ s3Setup :: UUID -> RemoteConfig -> Annex RemoteConfig
|
||||||
s3Setup u c = handlehost $ M.lookup "host" c
|
s3Setup u c = handlehost $ M.lookup "host" c
|
||||||
where
|
where
|
||||||
remotename = fromJust (M.lookup "name" c)
|
remotename = fromJust (M.lookup "name" c)
|
||||||
defbucket = remotename ++ "-" ++ u
|
defbucket = remotename ++ "-" ++ show u
|
||||||
defaults = M.fromList
|
defaults = M.fromList
|
||||||
[ ("datacenter", "US")
|
[ ("datacenter", "US")
|
||||||
, ("storageclass", "STANDARD")
|
, ("storageclass", "STANDARD")
|
||||||
|
|
2
Types.hs
2
Types.hs
|
@ -9,7 +9,7 @@ module Types (
|
||||||
Annex,
|
Annex,
|
||||||
Backend,
|
Backend,
|
||||||
Key,
|
Key,
|
||||||
UUID
|
UUID(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Annex
|
import Annex
|
||||||
|
|
|
@ -15,6 +15,7 @@ import Data.Ord
|
||||||
|
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Types.Key
|
import Types.Key
|
||||||
|
import Types.UUID
|
||||||
|
|
||||||
type RemoteConfig = M.Map String String
|
type RemoteConfig = M.Map String String
|
||||||
|
|
||||||
|
@ -25,15 +26,15 @@ data RemoteType a = RemoteType {
|
||||||
-- enumerates remotes of this type
|
-- enumerates remotes of this type
|
||||||
enumerate :: a [Git.Repo],
|
enumerate :: a [Git.Repo],
|
||||||
-- generates a remote of this type
|
-- generates a remote of this type
|
||||||
generate :: Git.Repo -> String -> Maybe RemoteConfig -> a (Remote a),
|
generate :: Git.Repo -> UUID -> Maybe RemoteConfig -> a (Remote a),
|
||||||
-- initializes or changes a remote
|
-- initializes or changes a remote
|
||||||
setup :: String -> RemoteConfig -> a RemoteConfig
|
setup :: UUID -> RemoteConfig -> a RemoteConfig
|
||||||
}
|
}
|
||||||
|
|
||||||
{- An individual remote. -}
|
{- An individual remote. -}
|
||||||
data Remote a = Remote {
|
data Remote a = Remote {
|
||||||
-- each Remote has a unique uuid
|
-- each Remote has a unique uuid
|
||||||
uuid :: String,
|
uuid :: UUID,
|
||||||
-- each Remote has a human visible name
|
-- each Remote has a human visible name
|
||||||
name :: String,
|
name :: String,
|
||||||
-- Remotes have a use cost; higher is more expensive
|
-- Remotes have a use cost; higher is more expensive
|
||||||
|
|
|
@ -7,5 +7,15 @@
|
||||||
|
|
||||||
module Types.UUID where
|
module Types.UUID where
|
||||||
|
|
||||||
-- might be nice to have a newtype, but lots of stuff treats uuids as strings
|
-- A UUID is either an arbitrary opaque string, or UUID info may be missing.
|
||||||
type UUID = String
|
data UUID = NoUUID | UUID String
|
||||||
|
deriving (Eq, Ord)
|
||||||
|
|
||||||
|
instance Show UUID where
|
||||||
|
show (UUID u) = u
|
||||||
|
show NoUUID = ""
|
||||||
|
|
||||||
|
instance Read UUID where
|
||||||
|
readsPrec _ s
|
||||||
|
| null s = [(NoUUID, "")]
|
||||||
|
| otherwise = [(UUID s, "")]
|
||||||
|
|
|
@ -45,9 +45,9 @@ options = commonOptions ++
|
||||||
where
|
where
|
||||||
check expected = do
|
check expected = do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
when (u /= expected) $ error $
|
when (u /= read expected) $ error $
|
||||||
"expected repository UUID " ++ expected
|
"expected repository UUID " ++ expected
|
||||||
++ " but found UUID " ++ u
|
++ " but found UUID " ++ show u
|
||||||
|
|
||||||
header :: String
|
header :: String
|
||||||
header = "Usage: git-annex-shell [-c] command [parameters ...] [option ..]"
|
header = "Usage: git-annex-shell [-c] command [parameters ...] [option ..]"
|
||||||
|
|
2
test.hs
2
test.hs
|
@ -614,7 +614,7 @@ checklocationlog f expected = do
|
||||||
case r of
|
case r of
|
||||||
Just (k, _) -> do
|
Just (k, _) -> do
|
||||||
uuids <- annexeval $ Logs.Location.keyLocations k
|
uuids <- annexeval $ Logs.Location.keyLocations k
|
||||||
assertEqual ("bad content in location log for " ++ f ++ " key " ++ (show k) ++ " uuid " ++ thisuuid)
|
assertEqual ("bad content in location log for " ++ f ++ " key " ++ (show k) ++ " uuid " ++ show thisuuid)
|
||||||
expected (thisuuid `elem` uuids)
|
expected (thisuuid `elem` uuids)
|
||||||
_ -> assertFailure $ f ++ " failed to look up key"
|
_ -> assertFailure $ f ++ " failed to look up key"
|
||||||
|
|
||||||
|
|
Loading…
Add table
Reference in a new issue