hlint suggestions

This commit is contained in:
Joshua Clayton 2016-05-05 18:06:25 -04:00
parent e34f6951f1
commit 4175effffb
5 changed files with 22 additions and 25 deletions

View File

@ -1,11 +1,8 @@
module Unused.CLI module Unused.CLI
( module Unused.CLI.Search ( module X
, module Unused.CLI.SearchError
, module Unused.CLI.SearchResult
, module Unused.CLI.Util
) where ) where
import Unused.CLI.Search import Unused.CLI.Search as X
import Unused.CLI.SearchError import Unused.CLI.SearchError as X
import Unused.CLI.SearchResult import Unused.CLI.SearchResult as X
import Unused.CLI.Util import Unused.CLI.Util as X

View File

@ -44,12 +44,12 @@ printMatches w r ms =
forM_ ms $ \m -> do forM_ ms $ \m -> do
setSGR [SetColor Foreground Dull (likelihoodColor $ trRemovalLikelihood r)] setSGR [SetColor Foreground Dull (likelihoodColor $ trRemovalLikelihood r)]
setSGR [SetConsoleIntensity NormalIntensity] setSGR [SetConsoleIntensity NormalIntensity]
putStr $ " " ++ (printf termFormat $ tmTerm m) putStr $ " " ++ printf termFormat (tmTerm m)
setSGR [Reset] setSGR [Reset]
setSGR [SetColor Foreground Vivid Cyan] setSGR [SetColor Foreground Vivid Cyan]
setSGR [SetConsoleIntensity NormalIntensity] setSGR [SetConsoleIntensity NormalIntensity]
putStr $ (printNumber $ trTotalFiles r) ++ "," ++ (printNumber $ trTotalOccurrences r) ++ " " putStr $ printNumber (trTotalFiles r) ++ "," ++ printNumber (trTotalOccurrences r) ++ " "
setSGR [Reset] setSGR [Reset]
setSGR [SetColor Foreground Dull Cyan] setSGR [SetColor Foreground Dull Cyan]
@ -58,5 +58,5 @@ printMatches w r ms =
setSGR [Reset] setSGR [Reset]
putStr "\n" putStr "\n"
where where
termFormat = "%-" ++ (show w) ++ "s" termFormat = "%-" ++ show w ++ "s"
printNumber = printf "%2d" printNumber = printf "%2d"

View File

@ -41,7 +41,7 @@ parseTermMatch = do
return $ TermMatch term' path' $ toInt occurrences' return $ TermMatch term' path' $ toInt occurrences'
where where
toInt i = read i :: Int toInt i = read i :: Int
colonSep = do { void $ try $ char ':' } colonSep = void $ try $ char ':'
termChars :: Parser Char termChars :: Parser Char
termChars = choice [alphaNum, char '_', char '!', char '?', char '=', char '>', char '<', char '[', char ']', char '.'] termChars = choice [alphaNum, char '_', char '!', char '?', char '=', char '>', char '<', char '[', char ']', char '.']

View File

@ -9,13 +9,13 @@ search t = do
results <- ag t results <- ag t
return $ linesMap prefixTerm results return $ linesMap prefixTerm results
where where
prefixTerm = ((++) t) prefixTerm = (t ++)
linesMap :: (String -> String) -> String -> [String] linesMap :: (String -> String) -> String -> [String]
linesMap f = linesMap f =
filter empty . map f . lines filter empty . map f . lines
where where
empty = (/= 0) . length empty = not . null
ag :: String -> IO String ag :: String -> IO String
ag t = do ag t = do

View File

@ -43,7 +43,7 @@ newtype DirectoryPrefix = DirectoryPrefix String deriving (Eq, Show, Ord)
resultsFromMatches :: [TermMatch] -> TermResults resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m = resultsFromMatches m =
calculateLikelihood $ TermResults calculateLikelihood TermResults
{ trTerm = resultTerm terms { trTerm = resultTerm terms
, trMatches = m , trMatches = m
, trTotalFiles = totalFiles , trTotalFiles = totalFiles
@ -74,23 +74,23 @@ isClassOrModule = matchRegex "^[A-Z]" . trTerm
railsSingleOkay :: TermResults -> Bool railsSingleOkay :: TermResults -> Bool
railsSingleOkay r = railsSingleOkay r =
foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (controller || helper || migration)] and [isClassOrModule r, oneFile r, oneOccurence r, controller || helper || migration]
where where
controller = (matchRegex "^app/controllers/" singlePath) && (matchRegex "Controller$" $ trTerm r) controller = matchRegex "^app/controllers/" singlePath && matchRegex "Controller$" (trTerm r)
helper = (matchRegex "^app/helpers/" singlePath) && (matchRegex "Helper$" $ trTerm r) helper = matchRegex "^app/helpers/" singlePath && matchRegex "Helper$" (trTerm r)
migration = matchRegex "^db/migrate/" singlePath migration = matchRegex "^db/migrate/" singlePath
singlePath = path $ fmap tmPath $ trMatches r singlePath = path $ tmPath <$> trMatches r
path (x:_) = x path (x:_) = x
path [] = "" path [] = ""
elixirSingleOkay :: TermResults -> Bool elixirSingleOkay :: TermResults -> Bool
elixirSingleOkay r = elixirSingleOkay r =
foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (view || test || migration)] and [isClassOrModule r, oneFile r, oneOccurence r, view || test || migration]
where where
migration = matchRegex "^priv/repo/migrations/" singlePath migration = matchRegex "^priv/repo/migrations/" singlePath
view = (matchRegex "^web/views/" singlePath) && (matchRegex "View$" $ trTerm r) view = matchRegex "^web/views/" singlePath && matchRegex "View$" (trTerm r)
test = (matchRegex "^test/" singlePath) && (matchRegex "Test$" $ trTerm r) test = matchRegex "^test/" singlePath && matchRegex "Test$" (trTerm r)
singlePath = path $ fmap tmPath $ trMatches r singlePath = path $ tmPath <$> trMatches r
path (x:_) = x path (x:_) = x
path [] = "" path [] = ""
@ -100,7 +100,7 @@ listFromMatchSet =
responsesGroupedByPath :: TermMatchSet -> [(DirectoryPrefix, TermMatchSet)] responsesGroupedByPath :: TermMatchSet -> [(DirectoryPrefix, TermMatchSet)]
responsesGroupedByPath pr = responsesGroupedByPath pr =
fmap (\p -> (p, responseForPath p pr)) $ directoriesForGrouping pr (\p -> (p, responseForPath p pr)) <$> directoriesForGrouping pr
responseForPath :: DirectoryPrefix -> TermMatchSet -> TermMatchSet responseForPath :: DirectoryPrefix -> TermMatchSet -> TermMatchSet
responseForPath s = responseForPath s =
@ -110,7 +110,7 @@ responseForPath s =
filterKVByPath = Map.filterWithKey (const $ \a -> s `elem` allPaths a) filterKVByPath = Map.filterWithKey (const $ \a -> s `elem` allPaths a)
allPaths = fmap (fileNameGrouping . tmPath) . trMatches allPaths = fmap (fileNameGrouping . tmPath) . trMatches
updateMatchesWith f tr = tr { trMatches = f tr } updateMatchesWith f tr = tr { trMatches = f tr }
newMatches = (filter ((== s) . fileNameGrouping . tmPath) . trMatches) newMatches = filter ((== s) . fileNameGrouping . tmPath) . trMatches
fileNameGrouping :: String -> DirectoryPrefix fileNameGrouping :: String -> DirectoryPrefix
fileNameGrouping = fileNameGrouping =