minor syntax changes

This commit is contained in:
Joey Hess 2011-10-11 14:43:45 -04:00
parent 025ded4a2d
commit b505ba83e8
19 changed files with 78 additions and 95 deletions

View file

@ -57,7 +57,7 @@ calcGitLink file key = do
logStatus :: Key -> LogStatus -> Annex () logStatus :: Key -> LogStatus -> Annex ()
logStatus key status = do logStatus key status = do
g <- gitRepo g <- gitRepo
u <- getUUID g u <- getUUID
logChange g key u status logChange g key u status
{- Runs an action, passing it a temporary filename to download, {- Runs an action, passing it a temporary filename to download,

View file

@ -104,11 +104,11 @@ checkKeyChecksum size key = do
present <- liftIO $ doesFileExist file present <- liftIO $ doesFileExist file
if not present || fast if not present || fast
then return True then return True
else do else check =<< shaN size file
s <- shaN size file where
if s == dropExtension (keyName key) check s
then return True | s == dropExtension (keyName key) = return True
else do | otherwise = do
dest <- moveBad key dest <- moveBad key
warning $ "Bad file content; moved to " ++ dest warning $ "Bad file content; moved to " ++ dest
return False return False

View file

@ -20,7 +20,6 @@ seek = [withNothing start]
start :: CommandStart start :: CommandStart
start = do start = do
g <- gitRepo u <- getUUID
u <- getUUID g
liftIO $ putStrLn $ "annex.uuid=" ++ u liftIO $ putStrLn $ "annex.uuid=" ++ u
stop stop

View file

@ -55,7 +55,7 @@ verifyLocationLog key file = do
preventWrite f preventWrite f
preventWrite (parentDir f) preventWrite (parentDir f)
u <- getUUID g u <- getUUID
uuids <- keyLocations key uuids <- keyLocations key
case (present, u `elem` uuids) of case (present, u `elem` uuids) of

View file

@ -29,7 +29,6 @@ start ws = do
perform :: String -> CommandPerform perform :: String -> CommandPerform
perform description = do perform description = do
initialize initialize
g <- gitRepo u <- getUUID
u <- getUUID g
describeUUID u description describeUUID u description
next $ return True next $ return True

View file

@ -72,8 +72,7 @@ remoteHasKey remote key present = do
-} -}
toStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart toStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart
toStart dest move file = isAnnexed file $ \(key, _) -> do toStart dest move file = isAnnexed file $ \(key, _) -> do
g <- gitRepo u <- getUUID
u <- getUUID g
ishere <- inAnnex key ishere <- inAnnex key
if not ishere || u == Remote.uuid dest if not ishere || u == Remote.uuid dest
then stop -- not here, so nothing to do then stop -- not here, so nothing to do
@ -122,8 +121,7 @@ toCleanup dest move key = do
-} -}
fromStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart fromStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart
fromStart src move file = isAnnexed file $ \(key, _) -> do fromStart src move file = isAnnexed file $ \(key, _) -> do
g <- gitRepo u <- getUUID
u <- getUUID g
remotes <- Remote.keyPossibilities key remotes <- Remote.keyPossibilities key
if u == Remote.uuid src || not (any (== src) remotes) if u == Remote.uuid src || not (any (== src) remotes)
then stop then stop

View file

@ -135,13 +135,12 @@ decryptCipher _ (EncryptedCipher encipher _) =
{- Generates an encrypted form of a Key. The encryption does not need to be {- Generates an encrypted form of a Key. The encryption does not need to be
- reversable, nor does it need to be the same type of encryption used - reversable, nor does it need to be the same type of encryption used
- on content. It does need to be repeatable. -} - on content. It does need to be repeatable. -}
encryptKey :: Cipher -> Key -> IO Key encryptKey :: Cipher -> Key -> Key
encryptKey c k = encryptKey c k = Key
return Key { { keyName = hmacWithCipher c (show k)
keyName = hmacWithCipher c (show k), , keyBackendName = "GPGHMACSHA1"
keyBackendName = "GPGHMACSHA1", , keySize = Nothing -- size and mtime omitted
keySize = Nothing, -- size and mtime omitted , keyMtime = Nothing -- to avoid leaking data
keyMtime = Nothing -- to avoid leaking data
} }
{- Runs an action, passing it a handle from which it can {- Runs an action, passing it a handle from which it can
@ -223,18 +222,18 @@ gpgCipherHandle params c a b = do
return ret return ret
configKeyIds :: RemoteConfig -> IO KeyIds configKeyIds :: RemoteConfig -> IO KeyIds
configKeyIds c = do configKeyIds c = parse <$> gpgRead params
let k = configGet c "encryption"
s <- gpgRead [Params "--with-colons --list-public-keys", Param k]
return $ KeyIds $ parseWithColons s
where where
parseWithColons s = map keyIdField $ filter pubKey $ lines s params = [Params "--with-colons --list-public-keys",
Param $ configGet c "encryption"]
parse = KeyIds . map keyIdField . filter pubKey . lines
pubKey = isPrefixOf "pub:" pubKey = isPrefixOf "pub:"
keyIdField s = split ":" s !! 4 keyIdField s = split ":" s !! 4
configGet :: RemoteConfig -> String -> String configGet :: RemoteConfig -> String -> String
configGet c key = fromMaybe missing $ M.lookup key c configGet c key = fromMaybe missing $ M.lookup key c
where missing = error $ "missing " ++ key ++ " in remote config" where
missing = error $ "missing " ++ key ++ " in remote config"
hmacWithCipher :: Cipher -> String -> String hmacWithCipher :: Cipher -> String -> String
hmacWithCipher c = hmacWithCipher' (cipherHmac c) hmacWithCipher c = hmacWithCipher' (cipherHmac c)

View file

@ -65,14 +65,13 @@ addExclude glob = addLimit $ return . notExcluded
{- Adds a limit to skip files not believed to be present {- Adds a limit to skip files not believed to be present
- in a specfied repository. -} - in a specfied repository. -}
addIn :: String -> Annex () addIn :: String -> Annex ()
addIn name = do addIn name = addLimit $ check $ if name == "." then inAnnex else inremote
u <- Remote.nameToUUID name
addLimit $ if name == "." then check inAnnex else check (remote u)
where where
check a f = Backend.lookupFile f >>= handle a check a f = Backend.lookupFile f >>= handle a
handle _ Nothing = return False handle _ Nothing = return False
handle a (Just (key, _)) = a key handle a (Just (key, _)) = a key
remote u key = do inremote key = do
u <- Remote.nameToUUID name
us <- keyLocations key us <- keyLocations key
return $ u `elem` us return $ u `elem` us

View file

@ -31,31 +31,31 @@ import qualified Annex
import qualified Messages.JSON as JSON import qualified Messages.JSON as JSON
showStart :: String -> String -> Annex () showStart :: String -> String -> Annex ()
showStart command file = handle (JSON.start command file) $ do showStart command file = handle (JSON.start command file) $
putStr $ command ++ " " ++ file ++ " " flushed $ putStr $ command ++ " " ++ file ++ " "
hFlush stdout
showNote :: String -> Annex () showNote :: String -> Annex ()
showNote s = handle (JSON.note s) $ do showNote s = handle (JSON.note s) $
putStr $ "(" ++ s ++ ") " flushed $ putStr $ "(" ++ s ++ ") "
hFlush stdout
showAction :: String -> Annex () showAction :: String -> Annex ()
showAction s = showNote $ s ++ "..." showAction s = showNote $ s ++ "..."
showProgress :: Annex () showProgress :: Annex ()
showProgress = handle q $ do showProgress = handle q $
putStr "." flushed $ putStr "."
hFlush stdout
showSideAction :: String -> Annex () showSideAction :: String -> Annex ()
showSideAction s = handle q $ putStrLn $ "(" ++ s ++ "...)" showSideAction s = handle q $
putStrLn $ "(" ++ s ++ "...)"
showOutput :: Annex () showOutput :: Annex ()
showOutput = handle q $ putStr "\n" showOutput = handle q $
putStr "\n"
showLongNote :: String -> Annex () showLongNote :: String -> Annex ()
showLongNote s = handle (JSON.note s) $ putStrLn $ '\n' : indent s showLongNote s = handle (JSON.note s) $
putStrLn $ '\n' : indent s
showEndOk :: Annex () showEndOk :: Annex ()
showEndOk = showEndResult True showEndOk = showEndResult True
@ -113,3 +113,6 @@ maybeShowJSON v = handle (JSON.add v) q
q :: Monad m => m () q :: Monad m => m ()
q = return () q = return ()
flushed :: IO () -> IO ()
flushed a = a >> hFlush stdout

View file

@ -78,7 +78,7 @@ genList = do
enumerate t >>= enumerate t >>=
mapM (gen m t) mapM (gen m t)
gen m t r = do gen m t r = do
u <- getUUID r u <- getRepoUUID r
generate t r u (M.lookup u m) generate t r u (M.lookup u m)
{- Looks up a remote by name. (Or by UUID.) Only finds currently configured {- Looks up a remote by name. (Or by UUID.) Only finds currently configured
@ -104,7 +104,7 @@ byName' n = do
- and returns its UUID. Finds even remotes that are not configured in - and returns its UUID. Finds even remotes that are not configured in
- .git/config. -} - .git/config. -}
nameToUUID :: String -> Annex UUID nameToUUID :: String -> Annex UUID
nameToUUID "." = getUUID =<< gitRepo -- special case for current repo nameToUUID "." = getUUID -- special case for current repo
nameToUUID n = do nameToUUID n = do
res <- byName' n res <- byName' n
case res of case res of
@ -129,7 +129,7 @@ nameToUUID n = do
- of the UUIDs. -} - of the UUIDs. -}
prettyPrintUUIDs :: String -> [UUID] -> Annex String prettyPrintUUIDs :: String -> [UUID] -> Annex String
prettyPrintUUIDs desc uuids = do prettyPrintUUIDs desc uuids = do
here <- getUUID =<< gitRepo here <- getUUID
m <- M.unionWith addname <$> uuidMap <*> remoteMap m <- M.unionWith addname <$> uuidMap <*> remoteMap
maybeShowJSON [(desc, map (jsonify m here) uuids)] maybeShowJSON [(desc, map (jsonify m here) uuids)]
return $ unwords $ map (\u -> "\t" ++ prettify m here u ++ "\n") uuids return $ unwords $ map (\u -> "\t" ++ prettify m here u ++ "\n") uuids
@ -178,8 +178,7 @@ keyPossibilitiesTrusted = keyPossibilities' True
keyPossibilities' :: Bool -> Key -> Annex ([Remote Annex], [UUID]) keyPossibilities' :: Bool -> Key -> Annex ([Remote Annex], [UUID])
keyPossibilities' withtrusted key = do keyPossibilities' withtrusted key = do
g <- gitRepo u <- getUUID
u <- getUUID g
trusted <- if withtrusted then trustGet Trusted else return [] trusted <- if withtrusted then trustGet Trusted else return []
-- get uuids of all remotes that are recorded to have the key -- get uuids of all remotes that are recorded to have the key
@ -198,8 +197,7 @@ keyPossibilities' withtrusted key = do
{- Displays known locations of a key. -} {- Displays known locations of a key. -}
showLocations :: Key -> [UUID] -> Annex () showLocations :: Key -> [UUID] -> Annex ()
showLocations key exclude = do showLocations key exclude = do
g <- gitRepo u <- getUUID
u <- getUUID g
uuids <- keyLocations key uuids <- keyLocations key
untrusteduuids <- trustGet UnTrusted untrusteduuids <- trustGet UnTrusted
let uuidswanted = filteruuids uuids (u:exclude++untrusteduuids) let uuidswanted = filteruuids uuids (u:exclude++untrusteduuids)

View file

@ -48,7 +48,7 @@ gen r u _ = do
(False, "") -> tryGitConfigRead r (False, "") -> tryGitConfigRead r
_ -> return r _ -> return r
u' <- getUUID r' u' <- getRepoUUID r'
let defcst = if cheap then cheapRemoteCost else expensiveRemoteCost let defcst = if cheap then cheapRemoteCost else expensiveRemoteCost
cst <- remoteCost r' defcst cst <- remoteCost r' defcst

View file

@ -78,8 +78,6 @@ remoteCipher c = maybe expensive cached =<< Annex.getState Annex.cipher
{- Gets encryption Cipher, and encrypted version of Key. -} {- Gets encryption Cipher, and encrypted version of Key. -}
cipherKey :: Maybe RemoteConfig -> Key -> Annex (Maybe (Cipher, Key)) cipherKey :: Maybe RemoteConfig -> Key -> Annex (Maybe (Cipher, Key))
cipherKey Nothing _ = return Nothing cipherKey Nothing _ = return Nothing
cipherKey (Just c) k = remoteCipher c >>= maybe (return Nothing) encrypt cipherKey (Just c) k = maybe Nothing encrypt <$> remoteCipher c
where where
encrypt ciphertext = do encrypt ciphertext = Just (ciphertext, encryptKey ciphertext k)
k' <- liftIO $ encryptKey ciphertext k
return $ Just (ciphertext, k')

17
UUID.hs
View file

@ -16,6 +16,7 @@
module UUID ( module UUID (
UUID, UUID,
getUUID, getUUID,
getRepoUUID,
getUncachedUUID, getUncachedUUID,
prepUUID, prepUUID,
genUUID, genUUID,
@ -44,7 +45,7 @@ logfile = "uuid.log"
{- 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 = liftIO $ pOpen ReadFromPipe command params $ \h -> hGetLine h genUUID = pOpen ReadFromPipe command params hGetLine
where where
command = SysConfig.uuid command = SysConfig.uuid
params = if command == "uuid" params = if command == "uuid"
@ -53,9 +54,12 @@ genUUID = liftIO $ pOpen ReadFromPipe command params $ \h -> hGetLine h
-- uuidgen generates random uuid by default -- uuidgen generates random uuid by default
else [] else []
getUUID :: Annex UUID
getUUID = getRepoUUID =<< gitRepo
{- Looks up a repo's UUID. May return "" if none is known. -} {- Looks up a repo's UUID. May return "" if none is known. -}
getUUID :: Git.Repo -> Annex UUID getRepoUUID :: Git.Repo -> Annex UUID
getUUID r = do getRepoUUID r = do
g <- gitRepo g <- gitRepo
let c = cached g let c = cached g
@ -76,11 +80,8 @@ getUncachedUUID r = 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 = do prepUUID = whenM (null <$> getUUID) $
u <- getUUID =<< gitRepo setConfig configkey =<< liftIO genUUID
when (null u) $ do
uuid <- liftIO genUUID
setConfig configkey uuid
{- Records a description for a uuid in the log. -} {- Records a description for a uuid in the log. -}
describeUUID :: UUID -> String -> Annex () describeUUID :: UUID -> String -> Annex ()

View file

@ -19,6 +19,7 @@ module Utility (
anyM anyM
) where ) where
import Control.Applicative
import IO (bracket) import IO (bracket)
import System.IO import System.IO
import System.Posix.Process hiding (executeFile) import System.Posix.Process hiding (executeFile)
@ -69,9 +70,7 @@ withTempFile template a = bracket create remove use
{- Lists the contents of a directory. {- Lists the contents of a directory.
- Unlike getDirectoryContents, paths are not relative to the directory. -} - Unlike getDirectoryContents, paths are not relative to the directory. -}
dirContents :: FilePath -> IO [FilePath] dirContents :: FilePath -> IO [FilePath]
dirContents d = do dirContents d = map (d </>) . filter notcruft <$> getDirectoryContents d
c <- getDirectoryContents d
return $ map (d </>) $ filter notcruft c
where where
notcruft "." = False notcruft "." = False
notcruft ".." = False notcruft ".." = False
@ -79,10 +78,7 @@ dirContents d = do
{- Current user's home directory. -} {- Current user's home directory. -}
myHomeDir :: IO FilePath myHomeDir :: IO FilePath
myHomeDir = do myHomeDir = homeDirectory <$> (getUserEntryForID =<< getEffectiveUserID)
uid <- getEffectiveUserID
u <- getUserEntryForID uid
return $ homeDirectory u
{- Catches IO errors and returns a Bool -} {- Catches IO errors and returns a Bool -}
catchBool :: IO Bool -> IO Bool catchBool :: IO Bool -> IO Bool

View file

@ -17,10 +17,9 @@ import Control.Applicative
{- Returns the parent directory of a path. Parent of / is "" -} {- Returns the parent directory of a path. Parent of / is "" -}
parentDir :: FilePath -> FilePath parentDir :: FilePath -> FilePath
parentDir dir = parentDir dir
if not $ null dirs | not $ null dirs = slash ++ join s (init dirs)
then slash ++ join s (init dirs) | otherwise = ""
else ""
where where
dirs = filter (not . null) $ split s dir dirs = filter (not . null) $ split s dir
slash = if isAbsolute dir then s else "" slash = if isAbsolute dir then s else ""
@ -72,7 +71,7 @@ relPathCwdToFile f = relPathDirToFile <$> getCurrentDirectory <*> absPath f
- Both must be absolute, and normalized (eg with absNormpath). - Both must be absolute, and normalized (eg with absNormpath).
-} -}
relPathDirToFile :: FilePath -> FilePath -> FilePath relPathDirToFile :: FilePath -> FilePath -> FilePath
relPathDirToFile from to = path relPathDirToFile from to = join s $ dotdots ++ uncommon
where where
s = [pathSeparator] s = [pathSeparator]
pfrom = split s from pfrom = split s from
@ -82,7 +81,6 @@ relPathDirToFile from to = path
uncommon = drop numcommon pto uncommon = drop numcommon pto
dotdots = replicate (length pfrom - numcommon) ".." dotdots = replicate (length pfrom - numcommon) ".."
numcommon = length common numcommon = length common
path = join s $ dotdots ++ uncommon
prop_relPathDirToFile_basics :: FilePath -> FilePath -> Bool prop_relPathDirToFile_basics :: FilePath -> FilePath -> Bool
prop_relPathDirToFile_basics from to prop_relPathDirToFile_basics from to
@ -99,14 +97,11 @@ prop_relPathDirToFile_basics from to
- appear at the same position as it did in the input list. - appear at the same position as it did in the input list.
-} -}
preserveOrder :: [FilePath] -> [FilePath] -> [FilePath] preserveOrder :: [FilePath] -> [FilePath] -> [FilePath]
-- optimisation, only one item in original list, so no reordering needed preserveOrder [] new = new
preserveOrder [_] new = new preserveOrder [_] new = new -- optimisation
preserveOrder orig new = collect orig new preserveOrder (l:ls) new = found ++ preserveOrder ls rest
where where
collect [] n = n (found, rest)=partition (l `dirContains`) new
collect [_] n = n -- optimisation
collect (l:ls) n = found ++ collect ls rest
where (found, rest)=partition (l `dirContains`) n
{- Runs an action that takes a list of FilePaths, and ensures that {- Runs an action that takes a list of FilePaths, and ensures that
- its return list preserves order. - its return list preserves order.

View file

@ -34,7 +34,7 @@ git_annex_shell :: Git.Repo -> String -> [CommandParam] -> Annex (Maybe (FilePat
git_annex_shell r command params git_annex_shell r command params
| not $ Git.repoIsUrl r = return $ Just (shellcmd, shellopts) | not $ Git.repoIsUrl r = return $ Just (shellcmd, shellopts)
| Git.repoIsSsh r = do | Git.repoIsSsh r = do
uuid <- getUUID r uuid <- getRepoUUID r
sshparams <- sshToRepo r [Param $ sshcmd uuid ] sshparams <- sshToRepo r [Param $ sshcmd uuid ]
return $ Just ("ssh", sshparams) return $ Just ("ssh", sshparams)
| otherwise = return Nothing | otherwise = return Nothing

View file

@ -37,7 +37,7 @@ options = uuid : commonOptions
where where
uuid = Option [] ["uuid"] (ReqArg check paramUUID) "repository uuid" uuid = Option [] ["uuid"] (ReqArg check paramUUID) "repository uuid"
check expected = do check expected = do
u <- getUUID =<< gitRepo u <- getUUID
when (u /= expected) $ error $ when (u /= expected) $ error $
"expected repository UUID " ++ expected "expected repository UUID " ++ expected
++ " but found UUID " ++ u ++ " but found UUID " ++ u

View file

@ -609,9 +609,7 @@ checkdangling f = do
checklocationlog :: FilePath -> Bool -> Assertion checklocationlog :: FilePath -> Bool -> Assertion
checklocationlog f expected = do checklocationlog f expected = do
thisuuid <- annexeval $ do thisuuid <- annexeval UUID.getUUID
g <- Annex.gitRepo
UUID.getUUID g
r <- annexeval $ Backend.lookupFile f r <- annexeval $ Backend.lookupFile f
case r of case r of
Just (k, _) -> do Just (k, _) -> do