summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex/Branch.hs2
-rw-r--r--Annex/Content.hs2
-rw-r--r--Command/Commit.hs2
-rw-r--r--Command/Fsck.hs6
-rw-r--r--Command/Get.hs2
-rw-r--r--Command/Move.hs4
-rw-r--r--Command/Uninit.hs4
-rw-r--r--Command/Watch.hs6
-rw-r--r--Command/Whereis.hs2
-rw-r--r--Config.hs2
-rw-r--r--Crypto.hs2
-rw-r--r--Locations.hs2
-rw-r--r--Messages.hs2
-rw-r--r--Utility/Directory.hs3
14 files changed, 20 insertions, 21 deletions
diff --git a/Annex/Branch.hs b/Annex/Branch.hs
index 7b433cc6e..8e7f45a4a 100644
--- a/Annex/Branch.hs
+++ b/Annex/Branch.hs
@@ -68,7 +68,7 @@ siblingBranches = inRepo $ Git.Ref.matchingUniq name
{- Creates the branch, if it does not already exist. -}
create :: Annex ()
-create = void $ getBranch
+create = void getBranch
{- Returns the ref of the branch, creating it first if necessary. -}
getBranch :: Annex Git.Ref
diff --git a/Annex/Content.hs b/Annex/Content.hs
index 232b43b2c..3e3e95868 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -87,7 +87,7 @@ lockContent key a = do
- to fiddle with permissions to open for an exclusive lock. -}
openforlock f = catchMaybeIO $ ifM (doesFileExist f)
( withModifiedFileMode f
- (\cur -> cur `unionFileModes` ownerWriteMode)
+ (`unionFileModes` ownerWriteMode)
open
, open
)
diff --git a/Command/Commit.hs b/Command/Commit.hs
index 1c82ed7df..f53ab7e09 100644
--- a/Command/Commit.hs
+++ b/Command/Commit.hs
@@ -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 []
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index 1fc656207..7bfc46f4a 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -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
diff --git a/Command/Get.hs b/Command/Get.hs
index 772fbd90c..c4ba48312 100644
--- a/Command/Get.hs
+++ b/Command/Get.hs
@@ -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
diff --git a/Command/Move.hs b/Command/Move.hs
index 8612c9f2d..6ec7cd90a 100644
--- a/Command/Move.hs
+++ b/Command/Move.hs
@@ -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
diff --git a/Command/Uninit.hs b/Command/Uninit.hs
index 5724bffd0..46a2480e6 100644
--- a/Command/Uninit.hs
+++ b/Command/Uninit.hs
@@ -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
diff --git a/Command/Watch.hs b/Command/Watch.hs
index e049591e9..0ee932dba 100644
--- a/Command/Watch.hs
+++ b/Command/Watch.hs
@@ -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
diff --git a/Command/Whereis.hs b/Command/Whereis.hs
index eb6ea7c56..b697bf554 100644
--- a/Command/Whereis.hs
+++ b/Command/Whereis.hs
@@ -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
diff --git a/Config.hs b/Config.hs
index f579e40b2..e66947e2c 100644
--- a/Config.hs
+++ b/Config.hs
@@ -114,6 +114,6 @@ getDiskReserve = fromMaybe megabyte . readSize dataUnits
getHttpHeaders :: Annex [String]
getHttpHeaders = do
cmd <- getConfig (annexConfig "http-headers-command") ""
- if (null cmd)
+ if null cmd
then fromRepo $ Git.Config.getList "annex.http-headers"
else lines . snd <$> liftIO (pipeFrom "sh" ["-c", cmd])
diff --git a/Crypto.hs b/Crypto.hs
index 58c0e6d00..8941f7637 100644
--- a/Crypto.hs
+++ b/Crypto.hs
@@ -138,7 +138,7 @@ withDecryptedContent = pass withDecryptedHandle
pass :: (Cipher -> IO L.ByteString -> (Handle -> IO a) -> IO a)
-> Cipher -> IO L.ByteString -> (L.ByteString -> IO a) -> IO a
-pass to n s a = to n s $ \h -> a =<< L.hGetContents h
+pass to n s a = to n s $ a <=< L.hGetContents
hmacWithCipher :: Cipher -> String -> String
hmacWithCipher c = hmacWithCipher' (cipherHmac c)
diff --git a/Locations.hs b/Locations.hs
index 9d27fbdae..0c9935614 100644
--- a/Locations.hs
+++ b/Locations.hs
@@ -165,7 +165,7 @@ gitAnnexRemotesDir r = addTrailingPathSeparator $ gitAnnexDir r </> "remotes"
{- Checks a symlink target to see if it appears to point to annexed content. -}
isLinkToAnnex :: FilePath -> Bool
-isLinkToAnnex s = ("/" ++ d) `isInfixOf` s || d `isPrefixOf` s
+isLinkToAnnex s = ('/':d) `isInfixOf` s || d `isPrefixOf` s
where
d = ".git" </> objectDir
diff --git a/Messages.hs b/Messages.hs
index 96bf3ae4b..1b48c119b 100644
--- a/Messages.hs
+++ b/Messages.hs
@@ -183,7 +183,7 @@ setupConsole = do
fileEncoding stderr
handle :: IO () -> IO () -> Annex ()
-handle json normal = withOutputType $ go
+handle json normal = withOutputType go
where
go NormalOutput = liftIO normal
go QuietOutput = q
diff --git a/Utility/Directory.hs b/Utility/Directory.hs
index 52f2396d7..78bb6e701 100644
--- a/Utility/Directory.hs
+++ b/Utility/Directory.hs
@@ -10,12 +10,11 @@ module Utility.Directory where
import System.IO.Error
import System.Posix.Files
import System.Directory
-import Control.Exception (throw)
+import Control.Exception (throw, bracket_)
import Control.Monad
import Control.Monad.IfElse
import System.FilePath
import Control.Applicative
-import Control.Exception (bracket_)
import System.Posix.Directory
import System.IO.Unsafe (unsafeInterleaveIO)