clean up read/show abuse

Avoid ever using read to parse a non-haskell formatted input string.

show :: Key is arguably still show abuse, but displaying Keys as filenames
is just too useful to give up.
This commit is contained in:
Joey Hess 2011-11-07 23:21:22 -04:00
parent fdf988be6d
commit b11a63a860
18 changed files with 75 additions and 98 deletions

View file

@ -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 $ liftM read . hGetLine genUUID = pOpen ReadFromPipe command params $ liftM toUUID . hGetLine
where where
command = SysConfig.uuid command = SysConfig.uuid
params = if command == "uuid" params = if command == "uuid"
@ -56,12 +56,12 @@ getRepoUUID r = do
return u return u
else return c else return c
where where
cached g = read $ Git.configGet g cachekey "" cached g = toUUID $ Git.configGet g cachekey ""
updatecache g u = when (g /= r) $ storeUUID 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 = read $ Git.configGet r configkey "" getUncachedUUID r = toUUID $ 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 ()
@ -69,4 +69,4 @@ prepUUID = whenM ((==) NoUUID <$> getUUID) $
storeUUID configkey =<< liftIO genUUID storeUUID configkey =<< liftIO genUUID
storeUUID :: String -> UUID -> Annex () storeUUID :: String -> UUID -> Annex ()
storeUUID configfield uuid = setConfig configfield (show uuid) storeUUID configfield = setConfig configfield . fromUUID

View file

@ -21,5 +21,5 @@ seek = [withNothing start]
start :: CommandStart start :: CommandStart
start = do start = do
u <- getUUID u <- getUUID
liftIO $ putStrLn $ "annex.uuid=" ++ show u liftIO $ putStrLn $ "annex.uuid=" ++ fromUUID u
stop stop

View file

@ -62,7 +62,8 @@ 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 (show u) $ M.findWithDefault "" u umap uuidnode u = Dot.graphNode (fromUUID u) $
M.findWithDefault "" u umap
hostname :: Git.Repo -> String hostname :: Git.Repo -> String
hostname r hostname r

View file

@ -1,6 +1,7 @@
module Common.Annex ( module Common.Annex (
module Common, module Common,
module Types, module Types,
module Types.UUID,
module Annex, module Annex,
module Locations, module Locations,
module Messages, module Messages,
@ -8,6 +9,7 @@ module Common.Annex (
import Common import Common
import Types import Types
import Types.UUID (toUUID, fromUUID)
import Annex (gitRepo) import Annex (gitRepo)
import Locations import Locations
import Messages import Messages

View file

@ -102,14 +102,18 @@ describeCipher (EncryptedCipher _ (KeyIds ks)) =
{- Stores an EncryptedCipher in a remote's configuration. -} {- Stores an EncryptedCipher in a remote's configuration. -}
storeCipher :: RemoteConfig -> EncryptedCipher -> RemoteConfig storeCipher :: RemoteConfig -> EncryptedCipher -> RemoteConfig
storeCipher c (EncryptedCipher t ks) = storeCipher c (EncryptedCipher t ks) =
M.insert "cipher" (toB64 t) $ M.insert "cipherkeys" (show ks) c M.insert "cipher" (toB64 t) $ M.insert "cipherkeys" (showkeys ks) c
where
showkeys (KeyIds l) = join "," l
{- Extracts an EncryptedCipher from a remote's configuration. -} {- Extracts an EncryptedCipher from a remote's configuration. -}
extractCipher :: RemoteConfig -> Maybe EncryptedCipher extractCipher :: RemoteConfig -> Maybe EncryptedCipher
extractCipher c = extractCipher c =
case (M.lookup "cipher" c, M.lookup "cipherkeys" c) of case (M.lookup "cipher" c, M.lookup "cipherkeys" c) of
(Just t, Just ks) -> Just $ EncryptedCipher (fromB64 t) (read ks) (Just t, Just ks) -> Just $ EncryptedCipher (fromB64 t) (readkeys ks)
_ -> Nothing _ -> Nothing
where
readkeys = KeyIds . split ","
{- Encrypts a Cipher to the specified KeyIds. -} {- Encrypts a Cipher to the specified KeyIds. -}
encryptCipher :: Cipher -> KeyIds -> IO EncryptedCipher encryptCipher :: Cipher -> KeyIds -> IO EncryptedCipher

View file

@ -37,7 +37,7 @@ logChange repo _ NoUUID _ = error $
{- 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 key = map read <$> (currentLog . logFile) key keyLocations key = map toUUID <$> (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.) -}

View file

@ -16,6 +16,7 @@ module Logs.Presence (
addLog, addLog,
readLog, readLog,
parseLog, parseLog,
showLog,
logNow, logNow,
compactLog, compactLog,
currentLog, currentLog,
@ -36,41 +37,9 @@ data LogLine = LogLine {
info :: String info :: String
} deriving (Eq) } deriving (Eq)
data LogStatus = InfoPresent | InfoMissing | Undefined data LogStatus = InfoPresent | InfoMissing
deriving (Eq) deriving (Eq)
instance Show LogStatus where
show InfoPresent = "1"
show InfoMissing = "0"
show Undefined = "undefined"
instance Read LogStatus where
readsPrec _ "1" = [(InfoPresent, "")]
readsPrec _ "0" = [(InfoMissing, "")]
readsPrec _ _ = [(Undefined, "")]
instance Show LogLine where
show (LogLine d s i) = unwords [show d, show s, i]
instance Read LogLine where
-- This parser is robust in that even unparsable log lines are
-- read without an exception being thrown.
-- Such lines have a status of Undefined.
readsPrec _ string =
if length w >= 3
then maybe bad good pdate
else bad
where
w = words string
s = read $ w !! 1
i = w !! 2
pdate :: Maybe UTCTime
pdate = parseTime defaultTimeLocale "%s%Qs" $ head w
good v = ret $ LogLine (utcTimeToPOSIXSeconds v) s i
bad = ret $ LogLine 0 Undefined ""
ret v = [(v, "")]
addLog :: FilePath -> LogLine -> Annex () addLog :: FilePath -> LogLine -> Annex ()
addLog file line = Annex.Branch.change file $ \s -> addLog file line = Annex.Branch.change file $ \s ->
showLog $ compactLog (line : parseLog s) showLog $ compactLog (line : parseLog s)
@ -80,15 +49,26 @@ addLog file line = Annex.Branch.change file $ \s ->
readLog :: FilePath -> Annex [LogLine] readLog :: FilePath -> Annex [LogLine]
readLog file = parseLog <$> Annex.Branch.get file readLog file = parseLog <$> Annex.Branch.get file
{- Parses a log file. Unparseable lines are ignored. -}
parseLog :: String -> [LogLine] parseLog :: String -> [LogLine]
parseLog = filter parsable . map read . lines parseLog = mapMaybe (parseline . words) . lines
where where
-- some lines may be unparseable, avoid them parseline (a:b:c:_) = do
parsable l = status l /= Undefined d <- parseTime defaultTimeLocale "%s%Qs" a
s <- parsestatus b
Just $ LogLine (utcTimeToPOSIXSeconds d) s c
parseline _ = Nothing
parsestatus "1" = Just InfoPresent
parsestatus "0" = Just InfoMissing
parsestatus _ = Nothing
{- Generates a log file. -} {- Generates a log file. -}
showLog :: [LogLine] -> String showLog :: [LogLine] -> String
showLog = unlines . map show showLog = unlines . map genline
where
genline (LogLine d s i) = unwords [show d, genstatus s, i]
genstatus InfoPresent = "1"
genstatus InfoMissing = "0"
{- Generates a new LogLine with the current date. -} {- Generates a new LogLine with the current date. -}
logNow :: LogStatus -> String -> Annex LogLine logNow :: LogStatus -> String -> Annex LogLine

View file

@ -45,18 +45,26 @@ trustMap = do
parseTrust :: String -> Maybe TrustLevel parseTrust :: String -> Maybe TrustLevel
parseTrust s parseTrust s
| length w > 0 = readMaybe $ head w | length w > 0 = Just $ parse $ head w
-- back-compat; the trust.log used to only list trusted repos -- back-compat; the trust.log used to only list trusted repos
| otherwise = Just Trusted | otherwise = Just $ Trusted
where where
w = words s w = words s
parse "1" = Trusted
parse "0" = UnTrusted
parse _ = SemiTrusted
showTrust :: TrustLevel -> String
showTrust SemiTrusted = "?"
showTrust UnTrusted = "0"
showTrust Trusted = "1"
{- 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@(UUID _) level = do trustSet uuid@(UUID _) level = do
ts <- liftIO $ getPOSIXTime ts <- liftIO $ getPOSIXTime
Annex.Branch.change trustLog $ Annex.Branch.change trustLog $
showLog show . changeLog ts uuid level . parseLog parseTrust showLog showTrust . 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" trustSet NoUUID _ = error "unknown UUID; cannot modify trust level"

View file

@ -50,28 +50,27 @@ 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 [show k, shower v, tskey ++ show p] unwords [fromUUID k, shower v, tskey ++ show p]
showpair (k, LogEntry Unknown v) = showpair (k, LogEntry Unknown v) =
unwords [show k, shower v] unwords [fromUUID 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 parse . lines
where where
pair line parse line
| null ws = Nothing | null ws = Nothing
| otherwise = case parser $ unwords info of | otherwise = parser (unwords info) >>= makepair
Nothing -> Nothing
Just v -> Just (read u, LogEntry c v)
where where
makepair v = Just (toUUID u, LogEntry ts v)
ws = words line ws = words line
u = head ws u = head ws
end = last ws end = last ws
c ts
| tskey `isPrefixOf` end = | tskey `isPrefixOf` end =
pdate $ tail $ dropWhile (/= '=') end pdate $ tail $ dropWhile (/= '=') end
| otherwise = Unknown | otherwise = Unknown
info info
| c == Unknown = drop 1 ws | ts == Unknown = drop 1 ws
| otherwise = drop 1 $ init ws | otherwise = drop 1 $ init ws
pdate s = case parseTime defaultTimeLocale "%s%Qs" s of pdate s = case parseTime defaultTimeLocale "%s%Qs" s of
Nothing -> Unknown Nothing -> Unknown

View file

@ -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 || read n == uuid r matching r = n == name r || toUUID 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
@ -116,7 +116,7 @@ nameToUUID n = byName' n >>= go
case M.lookup n $ transform swap m of case M.lookup n $ transform swap m of
Just u -> return $ Just u Just u -> return $ Just u
Nothing -> return $ byuuid m Nothing -> return $ byuuid m
byuuid m = M.lookup (read n) $ transform double m byuuid m = M.lookup (toUUID n) $ 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, _) = (a, a)
@ -142,8 +142,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) = show u ++ " -- " ++ d | not (null d) = fromUUID u ++ " -- " ++ d
| otherwise = show u | otherwise = fromUUID u
where where
ishere = here == u ishere = here == u
n = findlog m u n = findlog m u
@ -152,7 +152,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 $ show u) [ ("uuid", toJSON $ fromUUID u)
, ("description", toJSON $ findlog m u) , ("description", toJSON $ findlog m u)
, ("here", toJSON $ here == u) , ("here", toJSON $ here == u)
] ]

View file

@ -161,13 +161,15 @@ 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 " ++ show u] [Params $ "config annex.uuid " ++ v]
>>! 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"
Git.run r' "config" [Param "annex.uuid", Param $ show u] [Param "annex.uuid", Param v]
where
v = fromUUID 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,7 +194,7 @@ 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 (read $ Git.configGet r' "annex.uuid" "", r') Right r' -> return (toUUID $ Git.configGet r' "annex.uuid" "", r')
Left _ -> return (NoUUID, 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

View file

@ -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 $ show u] Git.run g "config" [Param (configsetting "annex-uuid"), Param $ fromUUID 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

View file

@ -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 ++ "-" ++ show u defbucket = remotename ++ "-" ++ fromUUID u
defaults = M.fromList defaults = M.fromList
[ ("datacenter", "US") [ ("datacenter", "US")
, ("storageclass", "STANDARD") , ("storageclass", "STANDARD")

View file

@ -7,17 +7,9 @@
module Types.Crypto where module Types.Crypto where
import Data.String.Utils
-- XXX ideally, this would be a locked memory region -- XXX ideally, this would be a locked memory region
newtype Cipher = Cipher String newtype Cipher = Cipher String
data EncryptedCipher = EncryptedCipher String KeyIds data EncryptedCipher = EncryptedCipher String KeyIds
newtype KeyIds = KeyIds [String] newtype KeyIds = KeyIds [String]
instance Show KeyIds where
show (KeyIds ks) = join "," ks
instance Read KeyIds where
readsPrec _ s = [(KeyIds (split "," s), "")]

View file

@ -17,14 +17,4 @@ import Types.UUID
data TrustLevel = SemiTrusted | UnTrusted | Trusted data TrustLevel = SemiTrusted | UnTrusted | Trusted
deriving Eq deriving Eq
instance Show TrustLevel where
show SemiTrusted = "?"
show UnTrusted = "0"
show Trusted = "1"
instance Read TrustLevel where
readsPrec _ "1" = [(Trusted, "")]
readsPrec _ "0" = [(UnTrusted, "")]
readsPrec _ _ = [(SemiTrusted, "")]
type TrustMap = M.Map UUID TrustLevel type TrustMap = M.Map UUID TrustLevel

View file

@ -9,13 +9,12 @@ module Types.UUID where
-- A UUID is either an arbitrary opaque string, or UUID info may be missing. -- A UUID is either an arbitrary opaque string, or UUID info may be missing.
data UUID = NoUUID | UUID String data UUID = NoUUID | UUID String
deriving (Eq, Ord) deriving (Eq, Ord, Show)
instance Show UUID where fromUUID :: UUID -> String
show (UUID u) = u fromUUID (UUID u) = u
show NoUUID = "" fromUUID NoUUID = ""
instance Read UUID where toUUID :: String -> UUID
readsPrec _ s toUUID [] = NoUUID
| null s = [(NoUUID, "")] toUUID s = UUID s
| otherwise = [(UUID s, "")]

View file

@ -178,7 +178,7 @@ fileKey1 file = readKey1 $
replace "&a" "&" $ replace "&s" "%" $ replace "%" "/" file replace "&a" "&" $ replace "&s" "%" $ replace "%" "/" file
writeLog1 :: FilePath -> [LogLine] -> IO () writeLog1 :: FilePath -> [LogLine] -> IO ()
writeLog1 file ls = viaTmp writeFile file (unlines $ map show ls) writeLog1 file ls = viaTmp writeFile file (showLog ls)
readLog1 :: FilePath -> IO [LogLine] readLog1 :: FilePath -> IO [LogLine]
readLog1 file = catch (parseLog <$> readFileStrict file) (const $ return []) readLog1 file = catch (parseLog <$> readFileStrict file) (const $ return [])

View file

@ -45,9 +45,9 @@ options = commonOptions ++
where where
check expected = do check expected = do
u <- getUUID u <- getUUID
when (u /= read expected) $ error $ when (u /= toUUID expected) $ error $
"expected repository UUID " ++ expected "expected repository UUID " ++ expected
++ " but found UUID " ++ show u ++ " but found UUID " ++ fromUUID u
header :: String header :: String
header = "Usage: git-annex-shell [-c] command [parameters ...] [option ..]" header = "Usage: git-annex-shell [-c] command [parameters ...] [option ..]"