hslint
This commit is contained in:
parent
e3f1568e0f
commit
d64132a43a
16 changed files with 25 additions and 29 deletions
|
@ -141,7 +141,7 @@ update = onceonly $ do
|
|||
let merge_desc = if null branches
|
||||
then "update"
|
||||
else "merging " ++
|
||||
(unwords $ map (show . Git.refDescribe) branches) ++
|
||||
unwords (map (show . Git.refDescribe) branches) ++
|
||||
" into " ++ show name
|
||||
unless (null branches) $ do
|
||||
showSideAction merge_desc
|
||||
|
|
|
@ -43,7 +43,7 @@ import Annex.Exception
|
|||
|
||||
{- Checks if a given key's content is currently present. -}
|
||||
inAnnex :: Key -> Annex Bool
|
||||
inAnnex = inAnnex' $ doesFileExist
|
||||
inAnnex = inAnnex' doesFileExist
|
||||
inAnnex' :: (FilePath -> IO a) -> Key -> Annex a
|
||||
inAnnex' a key = do
|
||||
whenM (fromRepo Git.repoIsUrl) $
|
||||
|
|
|
@ -43,7 +43,7 @@ git_annex_shell r command params
|
|||
shellcmd = "git-annex-shell"
|
||||
shellopts = Param command : File dir : params
|
||||
sshcmd uuid = unwords $
|
||||
shellcmd : (map shellEscape $ toCommand shellopts) ++
|
||||
shellcmd : map shellEscape (toCommand shellopts) ++
|
||||
uuidcheck uuid
|
||||
uuidcheck NoUUID = []
|
||||
uuidcheck (UUID u) = ["--uuid", u]
|
||||
|
|
|
@ -32,7 +32,7 @@ dispatch args cmds options header getgitrepo = do
|
|||
setupConsole
|
||||
r <- E.try getgitrepo :: IO (Either E.SomeException Git.Repo)
|
||||
case r of
|
||||
Left e -> maybe (throw e) id (cmdnorepo cmd)
|
||||
Left e -> fromMaybe (throw e) (cmdnorepo cmd)
|
||||
Right g -> do
|
||||
state <- Annex.new g
|
||||
(actions, state') <- Annex.run state $ do
|
||||
|
|
|
@ -73,7 +73,7 @@ doCommand = start
|
|||
whenAnnexed :: (FilePath -> (Key, Backend Annex) -> Annex (Maybe a)) -> FilePath -> Annex (Maybe a)
|
||||
whenAnnexed a file = ifAnnexed file (a file) (return Nothing)
|
||||
|
||||
ifAnnexed :: FilePath -> ((Key, Backend Annex) -> Annex a) -> (Annex a) -> Annex a
|
||||
ifAnnexed :: FilePath -> ((Key, Backend Annex) -> Annex a) -> Annex a -> Annex a
|
||||
ifAnnexed file yes no = maybe no yes =<< Backend.lookupFile file
|
||||
|
||||
notBareRepo :: Annex a -> Annex a
|
||||
|
|
|
@ -203,7 +203,7 @@ tryScan r
|
|||
"git config --list"
|
||||
dir = Git.workTree r
|
||||
cddir
|
||||
| take 2 dir == "/~" =
|
||||
| "/~" `isPrefixOf` dir =
|
||||
let (userhome, reldir) = span (/= '/') (drop 1 dir)
|
||||
in "cd " ++ userhome ++ " && cd " ++ shellEscape (drop 1 reldir)
|
||||
| otherwise = "cd " ++ shellEscape dir
|
||||
|
|
|
@ -191,9 +191,8 @@ staleSize label dirspec = do
|
|||
keys <- lift (Command.Unused.staleKeys dirspec)
|
||||
if null keys
|
||||
then nostat
|
||||
else do
|
||||
stat label $ json (++ aside "clean up with git-annex unused") $
|
||||
return $ keySizeSum $ S.fromList keys
|
||||
else stat label $ json (++ aside "clean up with git-annex unused") $
|
||||
return $ keySizeSum $ S.fromList keys
|
||||
|
||||
aside :: String -> String
|
||||
aside s = " (" ++ s ++ ")"
|
||||
|
|
|
@ -152,13 +152,12 @@ excludeReferenced l = do
|
|||
(S.fromList l)
|
||||
where
|
||||
-- Skip the git-annex branches, and get all other unique refs.
|
||||
refs = map Git.Ref .
|
||||
map last .
|
||||
refs = map (Git.Ref . last) .
|
||||
nubBy cmpheads .
|
||||
filter ourbranches .
|
||||
map words . lines . L.unpack
|
||||
cmpheads a b = head a == head b
|
||||
ourbranchend = '/' : show (Annex.Branch.name)
|
||||
ourbranchend = '/' : show Annex.Branch.name
|
||||
ourbranches ws = not $ ourbranchend `isSuffixOf` last ws
|
||||
removewith [] s = return $ S.toList s
|
||||
removewith (a:as) s
|
||||
|
|
|
@ -48,7 +48,7 @@ merge_index h repo bs =
|
|||
- earlier ones, so the list can be generated from any combination of
|
||||
- ls_tree, merge_trees, and merge_tree_index. -}
|
||||
update_index :: Repo -> [String] -> IO ()
|
||||
update_index repo ls = stream_update_index repo [\s -> mapM_ s ls]
|
||||
update_index repo ls = stream_update_index repo [(`mapM_` ls)]
|
||||
|
||||
{- Streams content into update-index. -}
|
||||
stream_update_index :: Repo -> [Streamer] -> IO ()
|
||||
|
|
|
@ -55,15 +55,15 @@ fixBadUUID = M.fromList . map fixup . M.toList
|
|||
| otherwise = (k, v)
|
||||
where
|
||||
kuuid = fromUUID k
|
||||
isbad = (not $ isuuid kuuid) && isuuid lastword
|
||||
isbad = not (isuuid kuuid) && isuuid lastword
|
||||
ws = words $ value v
|
||||
lastword = last ws
|
||||
fixeduuid = toUUID lastword
|
||||
fixedvalue = unwords $ kuuid:(take (length ws - 1) ws)
|
||||
fixedvalue = unwords $ kuuid: init ws
|
||||
-- For the fixed line to take precidence, it should be
|
||||
-- slightly newer, but only slightly.
|
||||
newertime (LogEntry (Date d) _) = d + minimumPOSIXTimeSlice
|
||||
newertime (LogEntry (Unknown) _) = minimumPOSIXTimeSlice
|
||||
newertime (LogEntry Unknown _) = minimumPOSIXTimeSlice
|
||||
minimumPOSIXTimeSlice = 0.000001
|
||||
isuuid s = length s == 36 && length (split "-" s) == 5
|
||||
|
||||
|
|
|
@ -165,7 +165,7 @@ onLocal :: Git.Repo -> Annex a -> IO a
|
|||
onLocal r a = do
|
||||
-- Avoid re-reading the repository's configuration if it was
|
||||
-- already read.
|
||||
state <- if (M.null $ Git.configMap r)
|
||||
state <- if M.null $ Git.configMap r
|
||||
then Annex.new r
|
||||
else return $ Annex.newState r
|
||||
Annex.eval state $ do
|
||||
|
|
|
@ -53,7 +53,7 @@ upgrade = do
|
|||
|
||||
when e $ do
|
||||
inRepo $ Git.run "rm" [Param "-r", Param "-f", Param "-q", File old]
|
||||
unless bare $ inRepo $ gitAttributesUnWrite
|
||||
unless bare $ inRepo gitAttributesUnWrite
|
||||
showProgress
|
||||
|
||||
unless bare push
|
||||
|
|
|
@ -99,7 +99,7 @@ bandwidthUnits = error "stop trying to rip people off"
|
|||
|
||||
{- Do you yearn for the days when men were men and megabytes were megabytes? -}
|
||||
oldSchoolUnits :: [Unit]
|
||||
oldSchoolUnits = map mingle $ zip storageUnits memoryUnits
|
||||
oldSchoolUnits = zipWith (curry mingle) storageUnits memoryUnits
|
||||
where
|
||||
mingle (Unit _ a n, Unit s' _ _) = Unit s' a n
|
||||
|
||||
|
|
|
@ -11,6 +11,7 @@ import System.IO.Error
|
|||
import System.Posix.Files
|
||||
import System.Directory
|
||||
import Control.Exception (throw)
|
||||
import Control.Monad
|
||||
|
||||
import Utility.SafeCommand
|
||||
import Utility.Conditional
|
||||
|
@ -37,13 +38,11 @@ moveFile src dest = try (rename src dest) >>= onrename
|
|||
mv tmp _ = do
|
||||
ok <- boolSystem "mv" [Param "-f",
|
||||
Param src, Param tmp]
|
||||
if ok
|
||||
then return ()
|
||||
else do
|
||||
-- delete any partial
|
||||
_ <- try $
|
||||
removeFile tmp
|
||||
rethrow
|
||||
unless ok $ do
|
||||
-- delete any partial
|
||||
_ <- try $
|
||||
removeFile tmp
|
||||
rethrow
|
||||
isdir f = do
|
||||
r <- try (getFileStatus f)
|
||||
case r of
|
||||
|
|
|
@ -71,7 +71,7 @@ checkGitVersion = do
|
|||
dotted = sum . mult 1 . reverse . extend 10 . map readi . split "."
|
||||
extend n l = l ++ replicate (n - length l) 0
|
||||
mult _ [] = []
|
||||
mult n (x:xs) = (n*x) : (mult (n*100) xs)
|
||||
mult n (x:xs) = (n*x) : mult (n*100) xs
|
||||
readi :: String -> Integer
|
||||
readi s = case reads s of
|
||||
((x,_):_) -> x
|
||||
|
|
3
test.hs
3
test.hs
|
@ -11,11 +11,10 @@ import Test.QuickCheck
|
|||
|
||||
import System.Posix.Directory (changeWorkingDirectory)
|
||||
import System.Posix.Files
|
||||
import Control.Exception (bracket_, bracket)
|
||||
import Control.Exception (bracket_, bracket, throw)
|
||||
import System.IO.Error
|
||||
import System.Posix.Env
|
||||
import qualified Control.Exception.Extensible as E
|
||||
import Control.Exception (throw)
|
||||
import qualified Data.Map as M
|
||||
import System.IO.HVFS (SystemFS(..))
|
||||
|
||||
|
|
Loading…
Reference in a new issue