diff options
author | Joey Hess <joey@kitenet.net> | 2013-04-03 03:52:41 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2013-04-03 03:52:41 -0400 |
commit | 6543d5406c64bb00a58e74305ec9ca09a49faf0b (patch) | |
tree | 5e33ceb3ea5b5bf5ad4f2cbb7d08b19cb1026897 /Logs | |
parent | f0dd3c6c1624cb5441eab175c6f5a683d3806885 (diff) |
hlint
Diffstat (limited to 'Logs')
-rw-r--r-- | Logs/Group.hs | 4 | ||||
-rw-r--r-- | Logs/Remote.hs | 2 | ||||
-rw-r--r-- | Logs/Transfer.hs | 20 | ||||
-rw-r--r-- | Logs/Trust.hs | 2 | ||||
-rw-r--r-- | Logs/Unused.hs | 2 |
5 files changed, 15 insertions, 15 deletions
diff --git a/Logs/Group.hs b/Logs/Group.hs index a069edcdf..c08feffde 100644 --- a/Logs/Group.hs +++ b/Logs/Group.hs @@ -66,11 +66,11 @@ makeGroupMap :: M.Map UUID (S.Set Group) -> GroupMap makeGroupMap byuuid = GroupMap byuuid bygroup where bygroup = M.fromListWith S.union $ - concat $ map explode $ M.toList byuuid + concatMap explode $ M.toList byuuid explode (u, s) = map (\g -> (g, S.singleton u)) (S.toList s) {- If a repository is in exactly one standard group, returns it. -} getStandardGroup :: S.Set Group -> Maybe StandardGroup -getStandardGroup s = case catMaybes $ map toStandardGroup $ S.toList s of +getStandardGroup s = case mapMaybe toStandardGroup $ S.toList s of [g] -> Just g _ -> Nothing diff --git a/Logs/Remote.hs b/Logs/Remote.hs index 55fb40f4b..89792b054 100644 --- a/Logs/Remote.hs +++ b/Logs/Remote.hs @@ -93,7 +93,7 @@ prop_idempotent_configEscape s = s == (configUnEscape . configEscape) s prop_parse_show_Config :: RemoteConfig -> Bool prop_parse_show_Config c -- whitespace and '=' are not supported in keys - | any (\k -> any isSpace k || any (== '=') k) (M.keys c) = True + | any (\k -> any isSpace k || elem '=' k) (M.keys c) = True | otherwise = parseConfig (showConfig c) ~~ Just c where normalize v = sort . M.toList <$> v diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 921d8f815..778932510 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -130,8 +130,8 @@ runTransfer t file shouldretry a = do Just fd -> do locked <- catchMaybeIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0) - when (locked == Nothing) $ - error $ "transfer already in progress" + when (isNothing locked) $ + error "transfer already in progress" void $ tryIO $ writeTransferInfoFile info tfile return mfd cleanup _ Nothing = noop @@ -169,7 +169,7 @@ mkProgressUpdater t info = do where updater tfile mvar b = modifyMVar_ mvar $ \oldbytes -> do let newbytes = fromBytesProcessed b - if (newbytes - oldbytes >= mindelta) + if newbytes - oldbytes >= mindelta then do let info' = info { bytesComplete = Just newbytes } _ <- tryIO $ writeTransferInfoFile info' tfile @@ -213,7 +213,7 @@ checkTransfer t = do {- Gets all currently running transfers. -} getTransfers :: Annex [(Transfer, TransferInfo)] getTransfers = do - transfers <- catMaybes . map parseTransferFile . concat <$> findfiles + transfers <- mapMaybe parseTransferFile . concat <$> findfiles infos <- mapM checkTransfer transfers return $ map (\(t, Just i) -> (t, i)) $ filter running $ zip transfers infos @@ -265,7 +265,7 @@ transferLockFile infofile = let (d,f) = splitFileName infofile in {- Parses a transfer information filename to a Transfer. -} parseTransferFile :: FilePath -> Maybe Transfer parseTransferFile file - | "lck." `isPrefixOf` (takeFileName file) = Nothing + | "lck." `isPrefixOf` takeFileName file = Nothing | otherwise = case drop (length bits - 3) bits of [direction, u, key] -> Transfer <$> readLcDirection direction @@ -291,17 +291,17 @@ writeTransferInfoFile info tfile = do writeTransferInfo :: TransferInfo -> String writeTransferInfo info = unlines [ (maybe "" show $ startedTime info) ++ - (maybe "" (\b -> " " ++ show b) $ bytesComplete info) + (maybe "" (\b -> ' ' : show b) (bytesComplete info)) , fromMaybe "" $ associatedFile info -- comes last; arbitrary content ] -readTransferInfoFile :: (Maybe ProcessID) -> FilePath -> IO (Maybe TransferInfo) +readTransferInfoFile :: Maybe ProcessID -> FilePath -> IO (Maybe TransferInfo) readTransferInfoFile mpid tfile = catchDefaultIO Nothing $ do h <- openFile tfile ReadMode fileEncoding h hClose h `after` (readTransferInfo mpid <$> hGetContentsStrict h) -readTransferInfo :: (Maybe ProcessID) -> String -> Maybe TransferInfo +readTransferInfo :: Maybe ProcessID -> String -> Maybe TransferInfo readTransferInfo mpid s = TransferInfo <$> time <*> pure mpid @@ -353,8 +353,8 @@ instance Arbitrary TransferInfo where prop_read_write_transferinfo :: TransferInfo -> Bool prop_read_write_transferinfo info - | transferRemote info /= Nothing = True -- remote not stored - | transferTid info /= Nothing = True -- tid not stored + | isJust (transferRemote info) = True -- remote not stored + | isJust (transferTid info) = True -- tid not stored | otherwise = Just (info { transferPaused = False }) == info' where info' = readTransferInfo (transferPid info) (writeTransferInfo info) diff --git a/Logs/Trust.hs b/Logs/Trust.hs index 058250740..89a5404f7 100644 --- a/Logs/Trust.hs +++ b/Logs/Trust.hs @@ -70,7 +70,7 @@ trustPartition level ls return $ partition (`elem` candidates) ls {- Filters UUIDs to those not matching a TrustLevel. -} -trustExclude :: TrustLevel -> [UUID] -> Annex ([UUID]) +trustExclude :: TrustLevel -> [UUID] -> Annex [UUID] trustExclude level ls = snd <$> trustPartition level ls {- trustLog in a map, overridden with any values from forcetrust or diff --git a/Logs/Unused.hs b/Logs/Unused.hs index bef78a992..437b01f71 100644 --- a/Logs/Unused.hs +++ b/Logs/Unused.hs @@ -31,7 +31,7 @@ readUnusedLog :: FilePath -> Annex UnusedMap readUnusedLog prefix = do f <- fromRepo $ gitAnnexUnusedLog prefix ifM (liftIO $ doesFileExist f) - ( M.fromList . catMaybes . map parse . lines + ( M.fromList . mapMaybe parse . lines <$> liftIO (readFile f) , return M.empty ) |