more partial function removal
Left a few Prelude.head's in where it was checked not null and too hard to remove, etc.
This commit is contained in:
parent
b7e0d39abb
commit
95d2391f58
24 changed files with 73 additions and 78 deletions
|
@ -107,7 +107,7 @@ chooseBackends fs = Annex.getState Annex.forcebackend >>= go
|
||||||
return $ map (\(f,b) -> (maybeLookupBackendName b, f)) pairs
|
return $ map (\(f,b) -> (maybeLookupBackendName b, f)) pairs
|
||||||
go (Just _) = do
|
go (Just _) = do
|
||||||
l <- orderedList
|
l <- orderedList
|
||||||
return $ map (\f -> (Just $ head l, f)) fs
|
return $ map (\f -> (Just $ Prelude.head l, f)) fs
|
||||||
|
|
||||||
{- Looks up a backend by name. May fail if unknown. -}
|
{- Looks up a backend by name. May fail if unknown. -}
|
||||||
lookupBackendName :: String -> Backend Annex
|
lookupBackendName :: String -> Backend Annex
|
||||||
|
@ -115,8 +115,6 @@ lookupBackendName s = fromMaybe unknown $ maybeLookupBackendName s
|
||||||
where
|
where
|
||||||
unknown = error $ "unknown backend " ++ s
|
unknown = error $ "unknown backend " ++ s
|
||||||
maybeLookupBackendName :: String -> Maybe (Backend Annex)
|
maybeLookupBackendName :: String -> Maybe (Backend Annex)
|
||||||
maybeLookupBackendName s
|
maybeLookupBackendName s = headMaybe matches
|
||||||
| length matches == 1 = Just $ head matches
|
|
||||||
| otherwise = Nothing
|
|
||||||
where
|
where
|
||||||
matches = filter (\b -> s == B.name b) list
|
matches = filter (\b -> s == B.name b) list
|
||||||
|
|
|
@ -62,11 +62,10 @@ shaN :: SHASize -> FilePath -> Annex String
|
||||||
shaN size file = do
|
shaN size file = do
|
||||||
showAction "checksum"
|
showAction "checksum"
|
||||||
liftIO $ pOpen ReadFromPipe command (toCommand [File file]) $ \h -> do
|
liftIO $ pOpen ReadFromPipe command (toCommand [File file]) $ \h -> do
|
||||||
line <- hGetLine h
|
sha <- fst . separate (== ' ') <$> hGetLine h
|
||||||
let bits = split " " line
|
if null sha
|
||||||
if null bits
|
|
||||||
then error $ command ++ " parse error"
|
then error $ command ++ " parse error"
|
||||||
else return $ head bits
|
else return sha
|
||||||
where
|
where
|
||||||
command = fromJust $ shaCommand size
|
command = fromJust $ shaCommand size
|
||||||
|
|
||||||
|
|
|
@ -51,7 +51,7 @@ parseCmd argv cmds options header = check $ getOpt Permute options argv
|
||||||
check (_, [], []) = err "missing command"
|
check (_, [], []) = err "missing command"
|
||||||
check (flags, name:rest, [])
|
check (flags, name:rest, [])
|
||||||
| null matches = err $ "unknown command " ++ name
|
| null matches = err $ "unknown command " ++ name
|
||||||
| otherwise = (flags, head matches, rest)
|
| otherwise = (flags, Prelude.head matches, rest)
|
||||||
where
|
where
|
||||||
matches = filter (\c -> name == cmdname c) cmds
|
matches = filter (\c -> name == cmdname c) cmds
|
||||||
check (_, _, errs) = err $ concat errs
|
check (_, _, errs) = err $ concat errs
|
||||||
|
|
|
@ -25,9 +25,13 @@ seek :: [CommandSeek]
|
||||||
seek = [withWords start]
|
seek = [withWords start]
|
||||||
|
|
||||||
start :: [String] -> CommandStart
|
start :: [String] -> CommandStart
|
||||||
start ws = do
|
start [] = do
|
||||||
when (null ws) needname
|
names <- remoteNames
|
||||||
|
error $ "Specify a name for the remote. " ++
|
||||||
|
if null names
|
||||||
|
then ""
|
||||||
|
else "Either a new name, or one of these existing special remotes: " ++ join " " names
|
||||||
|
start (name:ws) = do
|
||||||
(u, c) <- findByName name
|
(u, c) <- findByName name
|
||||||
let fullconfig = config `M.union` c
|
let fullconfig = config `M.union` c
|
||||||
t <- findType fullconfig
|
t <- findType fullconfig
|
||||||
|
@ -36,15 +40,7 @@ start ws = do
|
||||||
next $ perform t u $ M.union config c
|
next $ perform t u $ M.union config c
|
||||||
|
|
||||||
where
|
where
|
||||||
name = head ws
|
config = Logs.Remote.keyValToConfig ws
|
||||||
config = Logs.Remote.keyValToConfig $ tail ws
|
|
||||||
needname = do
|
|
||||||
let err s = error $ "Specify a name for the remote. " ++ s
|
|
||||||
names <- remoteNames
|
|
||||||
if null names
|
|
||||||
then err ""
|
|
||||||
else err $ "Either a new name, or one of these existing special remotes: " ++ join " " names
|
|
||||||
|
|
||||||
|
|
||||||
perform :: R.RemoteType Annex -> UUID -> R.RemoteConfig -> CommandPerform
|
perform :: R.RemoteType Annex -> UUID -> R.RemoteConfig -> CommandPerform
|
||||||
perform t u c = do
|
perform t u c = do
|
||||||
|
@ -67,11 +63,8 @@ findByName name = do
|
||||||
return (uuid, M.insert nameKey name M.empty)
|
return (uuid, M.insert nameKey name M.empty)
|
||||||
|
|
||||||
findByName' :: String -> M.Map UUID R.RemoteConfig -> Maybe (UUID, R.RemoteConfig)
|
findByName' :: String -> M.Map UUID R.RemoteConfig -> Maybe (UUID, R.RemoteConfig)
|
||||||
findByName' n m
|
findByName' n = headMaybe . filter (matching . snd) . M.toList
|
||||||
| null matches = Nothing
|
|
||||||
| otherwise = Just $ head matches
|
|
||||||
where
|
where
|
||||||
matches = filter (matching . snd) $ M.toList m
|
|
||||||
matching c = case M.lookup nameKey c of
|
matching c = case M.lookup nameKey c of
|
||||||
Nothing -> False
|
Nothing -> False
|
||||||
Just n'
|
Just n'
|
||||||
|
|
|
@ -73,7 +73,7 @@ hostname r
|
||||||
| otherwise = "localhost"
|
| otherwise = "localhost"
|
||||||
|
|
||||||
basehostname :: Git.Repo -> String
|
basehostname :: Git.Repo -> String
|
||||||
basehostname r = head $ split "." $ hostname r
|
basehostname r = Prelude.head $ split "." $ hostname r
|
||||||
|
|
||||||
{- A name to display for a repo. Uses the name from uuid.log if available,
|
{- A name to display for a repo. Uses the name from uuid.log if available,
|
||||||
- or the remote name if not. -}
|
- or the remote name if not. -}
|
||||||
|
|
|
@ -31,7 +31,7 @@ start b file (key, oldbackend) = do
|
||||||
next $ perform file key newbackend
|
next $ perform file key newbackend
|
||||||
else stop
|
else stop
|
||||||
where
|
where
|
||||||
choosebackend Nothing = head <$> Backend.orderedList
|
choosebackend Nothing = Prelude.head <$> Backend.orderedList
|
||||||
choosebackend (Just backend) = return backend
|
choosebackend (Just backend) = return backend
|
||||||
|
|
||||||
{- Checks if a key is upgradable to a newer representation. -}
|
{- Checks if a key is upgradable to a newer representation. -}
|
||||||
|
|
|
@ -116,7 +116,7 @@ remote_list level desc = stat n $ nojson $ lift $ do
|
||||||
us <- M.keys <$> (M.union <$> uuidMap <*> remoteMap)
|
us <- M.keys <$> (M.union <$> uuidMap <*> remoteMap)
|
||||||
rs <- fst <$> trustPartition level us
|
rs <- fst <$> trustPartition level us
|
||||||
s <- prettyPrintUUIDs n rs
|
s <- prettyPrintUUIDs n rs
|
||||||
return $ if null s then "0" else show (length rs) ++ "\n" ++ init s
|
return $ if null s then "0" else show (length rs) ++ "\n" ++ beginning s
|
||||||
where
|
where
|
||||||
n = desc ++ " repositories"
|
n = desc ++ " repositories"
|
||||||
|
|
||||||
|
|
|
@ -12,6 +12,8 @@ import Command
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
import qualified Git.Config
|
import qualified Git.Config
|
||||||
|
import qualified Git.Ref
|
||||||
|
import qualified Git
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy.Char8 as L
|
import qualified Data.ByteString.Lazy.Char8 as L
|
||||||
|
|
||||||
|
@ -61,7 +63,7 @@ defaultRemote = do
|
||||||
fromRepo $ Git.Config.get ("branch." ++ branch ++ ".remote") "origin"
|
fromRepo $ Git.Config.get ("branch." ++ branch ++ ".remote") "origin"
|
||||||
|
|
||||||
currentBranch :: Annex String
|
currentBranch :: Annex String
|
||||||
currentBranch = last . split "/" . L.unpack . head . L.lines <$>
|
currentBranch = Git.Ref.describe . Git.Ref . firstLine . L.unpack <$>
|
||||||
inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"])
|
inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"])
|
||||||
|
|
||||||
checkRemote :: String -> Annex ()
|
checkRemote :: String -> Annex ()
|
||||||
|
|
|
@ -29,7 +29,7 @@ check = do
|
||||||
when (b == Annex.Branch.name) $ error $
|
when (b == Annex.Branch.name) $ error $
|
||||||
"cannot uninit when the " ++ show b ++ " branch is checked out"
|
"cannot uninit when the " ++ show b ++ " branch is checked out"
|
||||||
where
|
where
|
||||||
current_branch = Git.Ref . head . lines . B.unpack <$> revhead
|
current_branch = Git.Ref . Prelude.head . lines . B.unpack <$> revhead
|
||||||
revhead = inRepo $ Git.Command.pipeRead
|
revhead = inRepo $ Git.Command.pipeRead
|
||||||
[Params "rev-parse --abbrev-ref HEAD"]
|
[Params "rev-parse --abbrev-ref HEAD"]
|
||||||
|
|
||||||
|
|
|
@ -154,13 +154,13 @@ excludeReferenced l = do
|
||||||
(S.fromList l)
|
(S.fromList l)
|
||||||
where
|
where
|
||||||
-- Skip the git-annex branches, and get all other unique refs.
|
-- Skip the git-annex branches, and get all other unique refs.
|
||||||
refs = map (Git.Ref . last) .
|
refs = map (Git.Ref . snd) .
|
||||||
nubBy cmpheads .
|
nubBy uniqref .
|
||||||
filter ourbranches .
|
filter ourbranches .
|
||||||
map words . lines . L.unpack
|
map (separate (== ' ')) . lines . L.unpack
|
||||||
cmpheads a b = head a == head b
|
uniqref (a, _) (b, _) = a == b
|
||||||
ourbranchend = '/' : show Annex.Branch.name
|
ourbranchend = '/' : show Annex.Branch.name
|
||||||
ourbranches ws = not $ ourbranchend `isSuffixOf` last ws
|
ourbranches (_, b) = not $ ourbranchend `isSuffixOf` b
|
||||||
removewith [] s = return $ S.toList s
|
removewith [] s = return $ S.toList s
|
||||||
removewith (a:as) s
|
removewith (a:as) s
|
||||||
| s == S.empty = return [] -- optimisation
|
| s == S.empty = return [] -- optimisation
|
||||||
|
|
|
@ -6,7 +6,7 @@ import Control.Monad.State as X (liftIO)
|
||||||
import Control.Exception.Extensible as X (IOException)
|
import Control.Exception.Extensible as X (IOException)
|
||||||
|
|
||||||
import Data.Maybe as X
|
import Data.Maybe as X
|
||||||
import Data.List as X
|
import Data.List as X hiding (head, tail, init, last)
|
||||||
import Data.String.Utils as X
|
import Data.String.Utils as X
|
||||||
|
|
||||||
import System.Path as X
|
import System.Path as X
|
||||||
|
@ -25,3 +25,5 @@ import Utility.SafeCommand as X
|
||||||
import Utility.Path as X
|
import Utility.Path as X
|
||||||
import Utility.Directory as X
|
import Utility.Directory as X
|
||||||
import Utility.Monad as X
|
import Utility.Monad as X
|
||||||
|
|
||||||
|
import Utility.BadPrelude as X
|
||||||
|
|
|
@ -40,15 +40,10 @@ remoteConfig r key = "remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" +
|
||||||
remoteCost :: Git.Repo -> Int -> Annex Int
|
remoteCost :: Git.Repo -> Int -> Annex Int
|
||||||
remoteCost r def = do
|
remoteCost r def = do
|
||||||
cmd <- getConfig r "cost-command" ""
|
cmd <- getConfig r "cost-command" ""
|
||||||
safeparse <$> if not $ null cmd
|
(fromMaybe def . readMaybe) <$>
|
||||||
|
if not $ null cmd
|
||||||
then liftIO $ snd <$> pipeFrom "sh" ["-c", cmd]
|
then liftIO $ snd <$> pipeFrom "sh" ["-c", cmd]
|
||||||
else getConfig r "cost" ""
|
else getConfig r "cost" ""
|
||||||
where
|
|
||||||
safeparse v
|
|
||||||
| null ws = def
|
|
||||||
| otherwise = fromMaybe def $ readMaybe $ head ws
|
|
||||||
where
|
|
||||||
ws = words v
|
|
||||||
|
|
||||||
cheapRemoteCost :: Int
|
cheapRemoteCost :: Int
|
||||||
cheapRemoteCost = 100
|
cheapRemoteCost = 100
|
||||||
|
|
|
@ -36,10 +36,9 @@ lookup attr files repo = do
|
||||||
, Param attr
|
, Param attr
|
||||||
, Params "-z --stdin"
|
, Params "-z --stdin"
|
||||||
] repo
|
] repo
|
||||||
topair l = (file, value)
|
topair l = (Git.Filename.decode file, value)
|
||||||
where
|
where
|
||||||
file = Git.Filename.decode $ join sep $ take end bits
|
file = join sep $ beginning bits
|
||||||
value = bits !! end
|
value = end bits !! 0
|
||||||
end = length bits - 1
|
|
||||||
bits = split sep l
|
bits = split sep l
|
||||||
sep = ": " ++ attr ++ ": "
|
sep = ": " ++ attr ++ ": "
|
||||||
|
|
|
@ -134,7 +134,7 @@ hashObject repo content = getSha subcmd $ do
|
||||||
calcMerge :: [(Ref, [L.ByteString])] -> Either Ref [L.ByteString]
|
calcMerge :: [(Ref, [L.ByteString])] -> Either Ref [L.ByteString]
|
||||||
calcMerge shacontents
|
calcMerge shacontents
|
||||||
| null reuseable = Right $ new
|
| null reuseable = Right $ new
|
||||||
| otherwise = Left $ fst $ head reuseable
|
| otherwise = Left $ fst $ Prelude.head reuseable
|
||||||
where
|
where
|
||||||
reuseable = filter (\c -> sorteduniq (snd c) == new) shacontents
|
reuseable = filter (\c -> sorteduniq (snd c) == new) shacontents
|
||||||
new = sorteduniq $ concat $ map snd shacontents
|
new = sorteduniq $ concat $ map snd shacontents
|
||||||
|
|
|
@ -68,7 +68,7 @@ logFile key = hashDirLower key ++ keyFile key ++ ".log"
|
||||||
{- Converts a log filename into a key. -}
|
{- Converts a log filename into a key. -}
|
||||||
logFileKey :: FilePath -> Maybe Key
|
logFileKey :: FilePath -> Maybe Key
|
||||||
logFileKey file
|
logFileKey file
|
||||||
| end == ".log" = fileKey beginning
|
| ext == ".log" = fileKey base
|
||||||
| otherwise = Nothing
|
| otherwise = Nothing
|
||||||
where
|
where
|
||||||
(beginning, end) = splitAt (length file - 4) file
|
(base, ext) = splitAt (length file - 4) file
|
||||||
|
|
|
@ -73,14 +73,13 @@ configUnEscape = unescape
|
||||||
| c == '&' = entity rest
|
| c == '&' = entity rest
|
||||||
| otherwise = c : unescape rest
|
| otherwise = c : unescape rest
|
||||||
entity s = if ok
|
entity s = if ok
|
||||||
then chr (read num) : unescape rest
|
then chr (Prelude.read num) : unescape rest
|
||||||
else '&' : unescape s
|
else '&' : unescape s
|
||||||
where
|
where
|
||||||
num = takeWhile isNumber s
|
num = takeWhile isNumber s
|
||||||
r = drop (length num) s
|
r = drop (length num) s
|
||||||
rest = drop 1 r
|
rest = drop 1 r
|
||||||
ok = not (null num) &&
|
ok = not (null num) && take 1 r == ";"
|
||||||
not (null r) && head r == ';'
|
|
||||||
|
|
||||||
{- for quickcheck -}
|
{- for quickcheck -}
|
||||||
prop_idempotent_configEscape :: String -> Bool
|
prop_idempotent_configEscape :: String -> Bool
|
||||||
|
|
|
@ -54,18 +54,16 @@ trustMap = do
|
||||||
Just m -> return m
|
Just m -> return m
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
overrides <- M.fromList <$> Annex.getState Annex.forcetrust
|
overrides <- M.fromList <$> Annex.getState Annex.forcetrust
|
||||||
m <- (M.union overrides . simpleMap . parseLog parseTrust) <$>
|
m <- (M.union overrides . simpleMap . parseLog (Just . parseTrust)) <$>
|
||||||
Annex.Branch.get trustLog
|
Annex.Branch.get trustLog
|
||||||
Annex.changeState $ \s -> s { Annex.trustmap = Just m }
|
Annex.changeState $ \s -> s { Annex.trustmap = Just m }
|
||||||
return m
|
return m
|
||||||
|
|
||||||
parseTrust :: String -> Maybe TrustLevel
|
{- The trust.log used to only list trusted repos, without a field for the
|
||||||
parseTrust s
|
- trust status, which is why this defaults to Trusted. -}
|
||||||
| length w > 0 = Just $ parse $ head w
|
parseTrust :: String -> TrustLevel
|
||||||
-- back-compat; the trust.log used to only list trusted repos
|
parseTrust s = maybe Trusted parse $ headMaybe $ words s
|
||||||
| otherwise = Just Trusted
|
|
||||||
where
|
where
|
||||||
w = words s
|
|
||||||
parse "1" = Trusted
|
parse "1" = Trusted
|
||||||
parse "0" = UnTrusted
|
parse "0" = UnTrusted
|
||||||
parse "X" = DeadTrusted
|
parse "X" = DeadTrusted
|
||||||
|
@ -82,6 +80,6 @@ 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 showTrust . changeLog ts uuid level . parseLog parseTrust
|
showLog showTrust . changeLog ts uuid level . parseLog (Just . 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"
|
||||||
|
|
|
@ -57,9 +57,9 @@ fixBadUUID = M.fromList . map fixup . M.toList
|
||||||
kuuid = fromUUID k
|
kuuid = fromUUID k
|
||||||
isbad = not (isuuid kuuid) && isuuid lastword
|
isbad = not (isuuid kuuid) && isuuid lastword
|
||||||
ws = words $ value v
|
ws = words $ value v
|
||||||
lastword = last ws
|
lastword = Prelude.last ws
|
||||||
fixeduuid = toUUID lastword
|
fixeduuid = toUUID lastword
|
||||||
fixedvalue = unwords $ kuuid: init ws
|
fixedvalue = unwords $ kuuid: Prelude.init ws
|
||||||
-- For the fixed line to take precidence, it should be
|
-- For the fixed line to take precidence, it should be
|
||||||
-- slightly newer, but only slightly.
|
-- slightly newer, but only slightly.
|
||||||
newertime (LogEntry (Date d) _) = d + minimumPOSIXTimeSlice
|
newertime (LogEntry (Date d) _) = d + minimumPOSIXTimeSlice
|
||||||
|
|
|
@ -103,7 +103,7 @@ byName' n = do
|
||||||
let match = filter matching allremotes
|
let match = filter matching allremotes
|
||||||
if null match
|
if null match
|
||||||
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 $ Prelude.head match
|
||||||
where
|
where
|
||||||
matching r = n == name r || toUUID n == uuid r
|
matching r = n == name r || toUUID n == uuid r
|
||||||
|
|
||||||
|
|
|
@ -209,20 +209,20 @@ bup2GitRemote "" = do
|
||||||
Git.Construct.fromAbsPath $ h </> ".bup"
|
Git.Construct.fromAbsPath $ h </> ".bup"
|
||||||
bup2GitRemote r
|
bup2GitRemote r
|
||||||
| bupLocal r =
|
| bupLocal r =
|
||||||
if head r == '/'
|
if "/" `isPrefixOf` r
|
||||||
then Git.Construct.fromAbsPath r
|
then Git.Construct.fromAbsPath r
|
||||||
else error "please specify an absolute path"
|
else error "please specify an absolute path"
|
||||||
| otherwise = Git.Construct.fromUrl $ "ssh://" ++ host ++ slash dir
|
| otherwise = Git.Construct.fromUrl $ "ssh://" ++ host ++ slash dir
|
||||||
where
|
where
|
||||||
bits = split ":" r
|
bits = split ":" r
|
||||||
host = head bits
|
host = Prelude.head bits
|
||||||
dir = join ":" $ drop 1 bits
|
dir = join ":" $ drop 1 bits
|
||||||
-- "host:~user/dir" is not supported specially by bup;
|
-- "host:~user/dir" is not supported specially by bup;
|
||||||
-- "host:dir" is relative to the home directory;
|
-- "host:dir" is relative to the home directory;
|
||||||
-- "host:" goes in ~/.bup
|
-- "host:" goes in ~/.bup
|
||||||
slash d
|
slash d
|
||||||
| d == "" = "/~/.bup"
|
| null d = "/~/.bup"
|
||||||
| head d == '/' = d
|
| "/" `isPrefixOf` d = d
|
||||||
| otherwise = "/~/" ++ d
|
| otherwise = "/~/" ++ d
|
||||||
|
|
||||||
bupLocal :: BupRepo -> Bool
|
bupLocal :: BupRepo -> Bool
|
||||||
|
|
|
@ -96,7 +96,7 @@ storeEncrypted d (cipher, enck) k = do
|
||||||
|
|
||||||
storeHelper :: FilePath -> Key -> (FilePath -> IO Bool) -> IO Bool
|
storeHelper :: FilePath -> Key -> (FilePath -> IO Bool) -> IO Bool
|
||||||
storeHelper d key a = do
|
storeHelper d key a = do
|
||||||
let dest = head $ locations d key
|
let dest = Prelude.head $ locations d key
|
||||||
let dir = parentDir dest
|
let dir = parentDir dest
|
||||||
createDirectoryIfMissing True dir
|
createDirectoryIfMissing True dir
|
||||||
allowWrite dir
|
allowWrite dir
|
||||||
|
|
|
@ -188,7 +188,7 @@ rsyncRemote o params = do
|
||||||
directories. -}
|
directories. -}
|
||||||
rsyncSend :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
rsyncSend :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
||||||
rsyncSend o k src = withRsyncScratchDir $ \tmp -> do
|
rsyncSend o k src = withRsyncScratchDir $ \tmp -> do
|
||||||
let dest = tmp </> head (keyPaths k)
|
let dest = tmp </> Prelude.head (keyPaths k)
|
||||||
liftIO $ createDirectoryIfMissing True $ parentDir dest
|
liftIO $ createDirectoryIfMissing True $ parentDir dest
|
||||||
liftIO $ createLink src dest
|
liftIO $ createLink src dest
|
||||||
rsyncRemote o
|
rsyncRemote o
|
||||||
|
|
|
@ -146,20 +146,20 @@ oldlog2key l =
|
||||||
readKey1 :: String -> Key
|
readKey1 :: String -> Key
|
||||||
readKey1 v =
|
readKey1 v =
|
||||||
if mixup
|
if mixup
|
||||||
then fromJust $ readKey $ join ":" $ tail bits
|
then fromJust $ readKey $ join ":" $ Prelude.tail bits
|
||||||
else Key { keyName = n , keyBackendName = b, keySize = s, keyMtime = t }
|
else Key { keyName = n , keyBackendName = b, keySize = s, keyMtime = t }
|
||||||
where
|
where
|
||||||
bits = split ":" v
|
bits = split ":" v
|
||||||
b = head bits
|
b = Prelude.head bits
|
||||||
n = join ":" $ drop (if wormy then 3 else 1) bits
|
n = join ":" $ drop (if wormy then 3 else 1) bits
|
||||||
t = if wormy
|
t = if wormy
|
||||||
then Just (read (bits !! 1) :: EpochTime)
|
then Just (Prelude.read (bits !! 1) :: EpochTime)
|
||||||
else Nothing
|
else Nothing
|
||||||
s = if wormy
|
s = if wormy
|
||||||
then Just (read (bits !! 2) :: Integer)
|
then Just (Prelude.read (bits !! 2) :: Integer)
|
||||||
else Nothing
|
else Nothing
|
||||||
wormy = head bits == "WORM"
|
wormy = Prelude.head bits == "WORM"
|
||||||
mixup = wormy && isUpper (head $ bits !! 1)
|
mixup = wormy && isUpper (Prelude.head $ bits !! 1)
|
||||||
|
|
||||||
showKey1 :: Key -> String
|
showKey1 :: Key -> String
|
||||||
showKey1 Key { keyName = n , keyBackendName = b, keySize = s, keyMtime = t } =
|
showKey1 Key { keyName = n , keyBackendName = b, keySize = s, keyMtime = t } =
|
||||||
|
|
|
@ -12,7 +12,7 @@ read :: Read a => String -> a
|
||||||
read = Prelude.read
|
read = Prelude.read
|
||||||
|
|
||||||
{- head is a partial function; head [] is an error
|
{- head is a partial function; head [] is an error
|
||||||
- Instead, use: take 1 -}
|
- Instead, use: take 1 or headMaybe -}
|
||||||
head :: [a] -> a
|
head :: [a] -> a
|
||||||
head = Prelude.head
|
head = Prelude.head
|
||||||
|
|
||||||
|
@ -27,10 +27,20 @@ init :: [a] -> [a]
|
||||||
init = Prelude.init
|
init = Prelude.init
|
||||||
|
|
||||||
{- last too
|
{- last too
|
||||||
- Instead, use: end -}
|
- Instead, use: end or lastMaybe -}
|
||||||
last :: [a] -> a
|
last :: [a] -> a
|
||||||
last = Prelude.last
|
last = Prelude.last
|
||||||
|
|
||||||
|
{- Like head but Nothing on empty list. -}
|
||||||
|
headMaybe :: [a] -> Maybe a
|
||||||
|
headMaybe [] = Nothing
|
||||||
|
headMaybe v = Just $ Prelude.head v
|
||||||
|
|
||||||
|
{- Like last but Nothing on empty list. -}
|
||||||
|
lastMaybe :: [a] -> Maybe a
|
||||||
|
lastMaybe [] = Nothing
|
||||||
|
lastMaybe v = Just $ Prelude.last v
|
||||||
|
|
||||||
{- All but the last element of a list.
|
{- All but the last element of a list.
|
||||||
- (Like init, but no error on an empty list.) -}
|
- (Like init, but no error on an empty list.) -}
|
||||||
beginning :: [a] -> [a]
|
beginning :: [a] -> [a]
|
||||||
|
|
Loading…
Reference in a new issue