hlint
This commit is contained in:
parent
85f0992c03
commit
942d8f7298
14 changed files with 20 additions and 21 deletions
|
@ -22,7 +22,7 @@ seek = [withNothing start]
|
|||
start :: CommandStart
|
||||
start = next $ next $ do
|
||||
Annex.Branch.commit "update"
|
||||
_ <- runhook =<< (inRepo $ Git.hookPath "annex-content")
|
||||
_ <- runhook =<< inRepo (Git.hookPath "annex-content")
|
||||
return True
|
||||
where
|
||||
runhook (Just hook) = liftIO $ boolSystem hook []
|
||||
|
|
|
@ -145,13 +145,13 @@ fixLink key file = do
|
|||
-}
|
||||
whenM (liftIO $ doesFileExist file) $
|
||||
unlessM (inAnnex key) $ do
|
||||
showNote $ "fixing content location"
|
||||
showNote "fixing content location"
|
||||
dir <- liftIO $ parentDir <$> absPath file
|
||||
let content = absPathFrom dir have
|
||||
liftIO $ allowWrite (parentDir content)
|
||||
moveAnnex key content
|
||||
|
||||
showNote $ "fixing link"
|
||||
showNote "fixing link"
|
||||
liftIO $ createDirectoryIfMissing True (parentDir file)
|
||||
liftIO $ removeFile file
|
||||
liftIO $ createSymbolicLink want file
|
||||
|
@ -220,7 +220,7 @@ checkKeySize' key file bad = case Types.Key.keySize key of
|
|||
Nothing -> return True
|
||||
Just size -> do
|
||||
size' <- fromIntegral . fileSize
|
||||
<$> (liftIO $ getFileStatus file)
|
||||
<$> liftIO (getFileStatus file)
|
||||
comparesizes size size'
|
||||
where
|
||||
comparesizes a b = do
|
||||
|
|
|
@ -26,7 +26,7 @@ start from file (key, _) = stopUnless (not <$> inAnnex key) $
|
|||
autoCopies file key (<) $ \_numcopies ->
|
||||
case from of
|
||||
Nothing -> go $ perform key
|
||||
Just src -> do
|
||||
Just src ->
|
||||
-- get --from = copy --from
|
||||
stopUnless (Command.Move.fromOk src key) $
|
||||
go $ Command.Move.fromPerform src False key
|
||||
|
|
|
@ -128,9 +128,9 @@ fromOk src key
|
|||
expensive = do
|
||||
u <- getUUID
|
||||
remotes <- Remote.keyPossibilities key
|
||||
return $ u /= Remote.uuid src && any (== src) remotes
|
||||
return $ u /= Remote.uuid src && elem src remotes
|
||||
fromPerform :: Remote -> Bool -> Key -> CommandPerform
|
||||
fromPerform src move key = moveLock move key $ do
|
||||
fromPerform src move key = moveLock move key $
|
||||
ifM (inAnnex key)
|
||||
( handle move True
|
||||
, do
|
||||
|
|
|
@ -28,8 +28,8 @@ check = do
|
|||
"cannot uninit when the " ++ show b ++ " branch is checked out"
|
||||
top <- fromRepo Git.repoPath
|
||||
cwd <- liftIO getCurrentDirectory
|
||||
whenM ((/=) <$> liftIO (absPath top) <*> liftIO (absPath cwd)) $ error $
|
||||
"can only run uninit from the top of the git repository"
|
||||
whenM ((/=) <$> liftIO (absPath top) <*> liftIO (absPath cwd)) $
|
||||
error "can only run uninit from the top of the git repository"
|
||||
where
|
||||
current_branch = Git.Ref . Prelude.head . lines <$> revhead
|
||||
revhead = inRepo $ Git.Command.pipeRead
|
||||
|
|
|
@ -176,7 +176,7 @@ runHandler :: MVar Annex.AnnexState -> ChangeChan -> Handler -> FilePath -> IO (
|
|||
runHandler st changechan handler file = void $ do
|
||||
r <- tryIO (runStateMVar st $ handler file)
|
||||
case r of
|
||||
Left e -> putStrLn $ show e
|
||||
Left e -> print e
|
||||
Right Nothing -> noop
|
||||
Right (Just change) -> void $
|
||||
runChangeChan $ writeTChan changechan change
|
||||
|
@ -236,7 +236,7 @@ onAddSymlink file = go =<< Backend.lookupFile file
|
|||
- So for speed, tries to reuse the existing blob for
|
||||
- the symlink target. -}
|
||||
addlink link = do
|
||||
v <- catObjectDetails $ Ref $ ":" ++ file
|
||||
v <- catObjectDetails $ Ref $ ':':file
|
||||
case v of
|
||||
Just (currlink, sha)
|
||||
| s2w8 link == L.unpack currlink ->
|
||||
|
@ -307,7 +307,7 @@ commitThread st changechan = forever $ do
|
|||
-- Now see if now's a good time to commit.
|
||||
time <- getCurrentTime
|
||||
if shouldCommit time cs
|
||||
then void $ tryIO $ runStateMVar st $ commitStaged
|
||||
then void $ tryIO $ runStateMVar st commitStaged
|
||||
else refillChanges changechan cs
|
||||
where
|
||||
oneSecond = 1000000 -- microseconds
|
||||
|
|
|
@ -37,7 +37,7 @@ perform remotemap key = do
|
|||
unless (null safelocations) $ showLongNote pp
|
||||
pp' <- prettyPrintUUIDs "untrusted" untrustedlocations
|
||||
unless (null untrustedlocations) $ showLongNote $ untrustedheader ++ pp'
|
||||
forM_ (catMaybes $ map (`M.lookup` remotemap) locations) $
|
||||
forM_ (mapMaybe (`M.lookup` remotemap) locations) $
|
||||
performRemote key
|
||||
if null safelocations then stop else next $ return True
|
||||
where
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue