Add flag to filter by likelihood

This commit is contained in:
Joshua Clayton 2016-05-07 16:25:54 -04:00
parent cb6eb12af4
commit ee1c4cd0f6
3 changed files with 30 additions and 3 deletions

View File

@ -3,13 +3,14 @@ module Main where
import Options.Applicative
import System.IO (hSetBuffering, BufferMode(NoBuffering), stdout)
import Unused.Parser (parseLines)
import Unused.Types (ParseResponse)
import Unused.ResponseFilter (withOneOccurrence, withOneFile)
import Unused.Types (ParseResponse, RemovalLikelihood(..))
import Unused.ResponseFilter (withOneOccurrence, withOneFile, withLikelihoods)
import Unused.CLI (SearchRunner(..), executeSearch, printParseError, printSearchResults, resetScreen)
data Options = Options
{ oSearchRunner :: SearchRunner
, oAllOccurrencesAndFiles :: Bool
, oLikelihoods :: [RemovalLikelihood]
}
main :: IO ()
@ -40,6 +41,7 @@ optionFilters o =
where
filters =
[ if oAllOccurrencesAndFiles o then id else withOneOccurrence . withOneFile
, withLikelihoods $ oLikelihoods o
]
parseOptions :: Parser Options
@ -47,6 +49,7 @@ parseOptions =
Options
<$> parseSearchRunner
<*> parseDisplayAllMatches
<*> parseLikelihoods
parseSearchRunner :: Parser SearchRunner
parseSearchRunner =
@ -60,3 +63,19 @@ parseDisplayAllMatches = switch $
short 'a'
<> long "all"
<> help "Display all files and occurrences"
parseLikelihoods :: Parser [RemovalLikelihood]
parseLikelihoods = many $
parseLikelihood <$> parseLikelihoodOption
parseLikelihood :: String -> RemovalLikelihood
parseLikelihood "high" = High
parseLikelihood "medium" = Medium
parseLikelihood "low" = Low
parseLikelihood _ = Unknown
parseLikelihoodOption :: Parser String
parseLikelihoodOption = strOption $
short 'l'
<> long "likelihood"
<> help "[Allows multiple] [Allowed values: high, medium, low] Display results based on likelihood"

View File

@ -1,6 +1,7 @@
module Unused.ResponseFilter
( withOneFile
, withOneOccurrence
, withLikelihoods
, oneFile
, oneOccurence
, isClassOrModule
@ -22,9 +23,16 @@ withOneOccurrence = applyFilter (const oneOccurence)
oneOccurence :: TermResults -> Bool
oneOccurence = (== 1) . trTotalOccurrences
withLikelihoods :: [RemovalLikelihood] -> ParseResponse -> ParseResponse
withLikelihoods [] = id
withLikelihoods l = applyFilter (const $ includesLikelihood l)
oneFile :: TermResults -> Bool
oneFile = (== 1) . trTotalFiles
includesLikelihood :: [RemovalLikelihood] -> TermResults -> Bool
includesLikelihood l = (`elem` l) . trRemovalLikelihood
isClassOrModule :: TermResults -> Bool
isClassOrModule = matchRegex "^[A-Z]" . trTerm

View File

@ -23,7 +23,7 @@ data TermResults = TermResults
, trRemovalLikelihood :: RemovalLikelihood
} deriving Show
data RemovalLikelihood = High | Medium | Low deriving Show
data RemovalLikelihood = High | Medium | Low | Unknown deriving (Eq, Show)
type TermMatchSet = Map.Map String TermResults