mirror of
https://github.com/joshuaclayton/unused.git
synced 2024-11-20 12:26:04 +03:00
Format codebase with hindent
This commit is contained in:
parent
5c08c145a5
commit
e630e8d8c8
73
app/App.hs
73
app/App.hs
@ -4,37 +4,39 @@ module App
|
||||
( runProgram
|
||||
) where
|
||||
|
||||
import Control.Monad.Except (runExceptT, throwError)
|
||||
import Control.Monad.Reader (runReaderT, asks, liftIO)
|
||||
import Control.Monad.Except (runExceptT, throwError)
|
||||
import Control.Monad.Reader (asks, liftIO, runReaderT)
|
||||
import qualified Data.Bifunctor as BF
|
||||
import qualified Data.Bool as B
|
||||
import qualified Data.Maybe as M
|
||||
import Types
|
||||
import Unused.Aliases (termsAndAliases)
|
||||
import Unused.CLI (SearchRunner(..), loadGitContext, renderHeader, executeSearch, withRuntime)
|
||||
import Types
|
||||
import Unused.Aliases (termsAndAliases)
|
||||
import Unused.CLI
|
||||
(SearchRunner(..), executeSearch, loadGitContext, renderHeader,
|
||||
withRuntime)
|
||||
import qualified Unused.CLI.Views as V
|
||||
import Unused.Cache (cached)
|
||||
import Unused.Grouping (CurrentGrouping(..), groupedResponses)
|
||||
import Unused.Parser (parseResults)
|
||||
import Unused.ResponseFilter (withOneOccurrence, withLikelihoods, ignoringPaths)
|
||||
import Unused.ResultsClassifier (LanguageConfiguration(..), loadAllConfigurations)
|
||||
import Unused.TagsSource (loadTagsFromFile, loadTagsFromPipe)
|
||||
import Unused.TermSearch (SearchResults(..), SearchBackend(..), SearchTerm, fromResults)
|
||||
import Unused.Types (TermMatchSet, RemovalLikelihood(..))
|
||||
import Unused.Cache (cached)
|
||||
import Unused.Grouping (CurrentGrouping(..), groupedResponses)
|
||||
import Unused.Parser (parseResults)
|
||||
import Unused.ResponseFilter
|
||||
(ignoringPaths, withLikelihoods, withOneOccurrence)
|
||||
import Unused.ResultsClassifier
|
||||
(LanguageConfiguration(..), loadAllConfigurations)
|
||||
import Unused.TagsSource (loadTagsFromFile, loadTagsFromPipe)
|
||||
import Unused.TermSearch
|
||||
(SearchBackend(..), SearchResults(..), SearchTerm, fromResults)
|
||||
import Unused.Types (RemovalLikelihood(..), TermMatchSet)
|
||||
|
||||
runProgram :: Options -> IO ()
|
||||
runProgram options = withRuntime $
|
||||
either renderError return
|
||||
=<< runExceptT (runReaderT (runApp run) options)
|
||||
runProgram options =
|
||||
withRuntime $ either renderError return =<< runExceptT (runReaderT (runApp run) options)
|
||||
|
||||
run :: App ()
|
||||
run = do
|
||||
terms <- termsWithAlternatesFromConfig
|
||||
|
||||
liftIO $ renderHeader terms
|
||||
backend <- searchBackend
|
||||
results <- withCache . flip (executeSearch backend) terms =<< searchRunner
|
||||
|
||||
printResults =<< retrieveGitContext =<< fmap (`parseResults` results) loadAllConfigs
|
||||
|
||||
searchBackend :: AppConfig m => m SearchBackend
|
||||
@ -42,9 +44,7 @@ searchBackend = asks oSearchBackend
|
||||
|
||||
termsWithAlternatesFromConfig :: App [SearchTerm]
|
||||
termsWithAlternatesFromConfig =
|
||||
termsAndAliases
|
||||
<$> (concatMap lcTermAliases <$> loadAllConfigs)
|
||||
<*> calculateTagInput
|
||||
termsAndAliases <$> (concatMap lcTermAliases <$> loadAllConfigs) <*> calculateTagInput
|
||||
|
||||
renderError :: AppError -> IO ()
|
||||
renderError (TagError e) = V.missingTagsFileError e
|
||||
@ -52,9 +52,7 @@ renderError (InvalidConfigError e) = V.invalidConfigError e
|
||||
renderError (CacheError e) = V.fingerprintError e
|
||||
|
||||
retrieveGitContext :: TermMatchSet -> App TermMatchSet
|
||||
retrieveGitContext tms =
|
||||
maybe (return tms) (liftIO . flip loadGitContext tms)
|
||||
=<< numberOfCommits
|
||||
retrieveGitContext tms = maybe (return tms) (liftIO . flip loadGitContext tms) =<< numberOfCommits
|
||||
|
||||
printResults :: TermMatchSet -> App ()
|
||||
printResults tms = do
|
||||
@ -65,42 +63,31 @@ printResults tms = do
|
||||
|
||||
loadAllConfigs :: App [LanguageConfiguration]
|
||||
loadAllConfigs =
|
||||
either throwError return
|
||||
=<< BF.first InvalidConfigError <$> liftIO loadAllConfigurations
|
||||
either throwError return =<< BF.first InvalidConfigError <$> liftIO loadAllConfigurations
|
||||
|
||||
calculateTagInput :: App [String]
|
||||
calculateTagInput =
|
||||
either throwError return
|
||||
=<< liftIO .
|
||||
fmap (BF.first TagError) .
|
||||
B.bool loadTagsFromFile loadTagsFromPipe =<< readFromStdIn
|
||||
either throwError return =<<
|
||||
liftIO . fmap (BF.first TagError) . B.bool loadTagsFromFile loadTagsFromPipe =<< readFromStdIn
|
||||
|
||||
withCache :: IO SearchResults -> App SearchResults
|
||||
withCache f =
|
||||
B.bool (liftIO f) (withCache' f) =<< runWithCache
|
||||
withCache f = B.bool (liftIO f) (withCache' f) =<< runWithCache
|
||||
where
|
||||
withCache' :: IO SearchResults -> App SearchResults
|
||||
withCache' r =
|
||||
either (throwError . CacheError) (return . SearchResults) =<<
|
||||
liftIO (cached "term-matches" $ fmap fromResults r)
|
||||
|
||||
liftIO (cached "term-matches" $ fmap fromResults r)
|
||||
|
||||
optionFilters :: AppConfig m => TermMatchSet -> m TermMatchSet
|
||||
optionFilters tms = foldl (>>=) (pure tms) matchSetFilters
|
||||
where
|
||||
matchSetFilters =
|
||||
[ singleOccurrenceFilter
|
||||
, likelihoodsFilter
|
||||
, ignoredPathsFilter
|
||||
]
|
||||
matchSetFilters = [singleOccurrenceFilter, likelihoodsFilter, ignoredPathsFilter]
|
||||
|
||||
singleOccurrenceFilter :: AppConfig m => TermMatchSet -> m TermMatchSet
|
||||
singleOccurrenceFilter tms =
|
||||
B.bool tms (withOneOccurrence tms) <$> asks oSingleOccurrenceMatches
|
||||
singleOccurrenceFilter tms = B.bool tms (withOneOccurrence tms) <$> asks oSingleOccurrenceMatches
|
||||
|
||||
likelihoodsFilter :: AppConfig m => TermMatchSet -> m TermMatchSet
|
||||
likelihoodsFilter tms =
|
||||
asks $ withLikelihoods . likelihoods <*> pure tms
|
||||
likelihoodsFilter tms = asks $ withLikelihoods . likelihoods <*> pure tms
|
||||
where
|
||||
likelihoods options
|
||||
| oAllLikelihoods options = [High, Medium, Low]
|
||||
|
114
app/Main.hs
114
app/Main.hs
@ -1,59 +1,51 @@
|
||||
module Main where
|
||||
|
||||
import App (runProgram)
|
||||
import Common
|
||||
import App (runProgram)
|
||||
import Common
|
||||
import qualified Data.Maybe as M
|
||||
import Options.Applicative
|
||||
import Types (Options(Options))
|
||||
import Unused.CLI (SearchRunner(..))
|
||||
import Unused.Grouping (CurrentGrouping(..))
|
||||
import Unused.TermSearch (SearchBackend(..))
|
||||
import Unused.Types (RemovalLikelihood(..))
|
||||
import Unused.Util (stringToInt)
|
||||
import Options.Applicative
|
||||
import Types (Options(Options))
|
||||
import Unused.CLI (SearchRunner(..))
|
||||
import Unused.Grouping (CurrentGrouping(..))
|
||||
import Unused.TermSearch (SearchBackend(..))
|
||||
import Unused.Types (RemovalLikelihood(..))
|
||||
import Unused.Util (stringToInt)
|
||||
|
||||
main :: IO ()
|
||||
main = runProgram =<< parseCLI
|
||||
|
||||
parseCLI :: IO Options
|
||||
parseCLI =
|
||||
execParser (withInfo parseOptions pHeader pDescription pFooter)
|
||||
parseCLI = execParser (withInfo parseOptions pHeader pDescription pFooter)
|
||||
where
|
||||
pHeader = "Unused: Analyze potentially unused code"
|
||||
pDescription = "Unused allows a developer to leverage an existing tags file \
|
||||
pHeader = "Unused: Analyze potentially unused code"
|
||||
pDescription =
|
||||
"Unused allows a developer to leverage an existing tags file \
|
||||
\(located at .git/tags, tags, or tmp/tags) to identify tokens \
|
||||
\in a codebase that are unused."
|
||||
pFooter = "CLI USAGE: $ unused"
|
||||
pFooter = "CLI USAGE: $ unused"
|
||||
|
||||
withInfo :: Parser a -> String -> String -> String -> ParserInfo a
|
||||
withInfo opts h d f =
|
||||
info (helper <*> opts) $ header h <> progDesc d <> footer f
|
||||
withInfo opts h d f = info (helper <*> opts) $ header h <> progDesc d <> footer f
|
||||
|
||||
parseOptions :: Parser Options
|
||||
parseOptions =
|
||||
Options
|
||||
<$> parseSearchRunner
|
||||
<*> parseDisplaySingleOccurrenceMatches
|
||||
<*> parseLikelihoods
|
||||
<*> parseAllLikelihoods
|
||||
<*> parseIgnorePaths
|
||||
<*> parseGroupings
|
||||
<*> parseWithoutCache
|
||||
<*> parseFromStdIn
|
||||
<*> parseCommitCount
|
||||
<*> parseSearchBackend
|
||||
Options <$> parseSearchRunner <*> parseDisplaySingleOccurrenceMatches <*> parseLikelihoods <*>
|
||||
parseAllLikelihoods <*>
|
||||
parseIgnorePaths <*>
|
||||
parseGroupings <*>
|
||||
parseWithoutCache <*>
|
||||
parseFromStdIn <*>
|
||||
parseCommitCount <*>
|
||||
parseSearchBackend
|
||||
|
||||
parseSearchRunner :: Parser SearchRunner
|
||||
parseSearchRunner =
|
||||
flag SearchWithProgress SearchWithoutProgress $
|
||||
short 'P'
|
||||
<> long "no-progress"
|
||||
<> help "Don't display progress during analysis"
|
||||
short 'P' <> long "no-progress" <> help "Don't display progress during analysis"
|
||||
|
||||
parseDisplaySingleOccurrenceMatches :: Parser Bool
|
||||
parseDisplaySingleOccurrenceMatches = switch $
|
||||
short 's'
|
||||
<> long "single-occurrence"
|
||||
<> help "Display only single occurrences"
|
||||
parseDisplaySingleOccurrenceMatches =
|
||||
switch $ short 's' <> long "single-occurrence" <> help "Display only single occurrences"
|
||||
|
||||
parseLikelihoods :: Parser [RemovalLikelihood]
|
||||
parseLikelihoods = many (parseLikelihood <$> parseLikelihoodOption)
|
||||
@ -65,26 +57,22 @@ parseLikelihood "low" = Low
|
||||
parseLikelihood _ = Unknown
|
||||
|
||||
parseLikelihoodOption :: Parser String
|
||||
parseLikelihoodOption = strOption $
|
||||
short 'l'
|
||||
<> long "likelihood"
|
||||
<> help "[Allows multiple] [Allowed: high, medium, low] Display results based on likelihood"
|
||||
parseLikelihoodOption =
|
||||
strOption $
|
||||
short 'l' <> long "likelihood" <>
|
||||
help "[Allows multiple] [Allowed: high, medium, low] Display results based on likelihood"
|
||||
|
||||
parseAllLikelihoods :: Parser Bool
|
||||
parseAllLikelihoods = switch $
|
||||
short 'a'
|
||||
<> long "all-likelihoods"
|
||||
<> help "Display all likelihoods"
|
||||
parseAllLikelihoods = switch $ short 'a' <> long "all-likelihoods" <> help "Display all likelihoods"
|
||||
|
||||
parseIgnorePaths :: Parser [String]
|
||||
parseIgnorePaths = many $ strOption $
|
||||
long "ignore"
|
||||
<> metavar "PATH"
|
||||
<> help "[Allows multiple] Ignore paths that contain PATH"
|
||||
parseIgnorePaths =
|
||||
many $
|
||||
strOption $
|
||||
long "ignore" <> metavar "PATH" <> help "[Allows multiple] Ignore paths that contain PATH"
|
||||
|
||||
parseGroupings :: Parser CurrentGrouping
|
||||
parseGroupings =
|
||||
M.fromMaybe GroupByDirectory <$> maybeGroup
|
||||
parseGroupings = M.fromMaybe GroupByDirectory <$> maybeGroup
|
||||
where
|
||||
maybeGroup = optional $ parseGrouping <$> parseGroupingOption
|
||||
|
||||
@ -96,38 +84,30 @@ parseGrouping "none" = NoGroup
|
||||
parseGrouping _ = NoGroup
|
||||
|
||||
parseGroupingOption :: Parser String
|
||||
parseGroupingOption = strOption $
|
||||
short 'g'
|
||||
<> long "group-by"
|
||||
<> help "[Allowed: directory, term, file, none] Group results"
|
||||
parseGroupingOption =
|
||||
strOption $
|
||||
short 'g' <> long "group-by" <> help "[Allowed: directory, term, file, none] Group results"
|
||||
|
||||
parseWithoutCache :: Parser Bool
|
||||
parseWithoutCache = switch $
|
||||
short 'C'
|
||||
<> long "no-cache"
|
||||
<> help "Ignore cache when performing calculations"
|
||||
parseWithoutCache =
|
||||
switch $ short 'C' <> long "no-cache" <> help "Ignore cache when performing calculations"
|
||||
|
||||
parseFromStdIn :: Parser Bool
|
||||
parseFromStdIn = switch $
|
||||
long "stdin"
|
||||
<> help "Read tags from STDIN"
|
||||
parseFromStdIn = switch $ long "stdin" <> help "Read tags from STDIN"
|
||||
|
||||
parseCommitCount :: Parser (Maybe Int)
|
||||
parseCommitCount =
|
||||
(stringToInt =<<) <$> commitParser
|
||||
parseCommitCount = (stringToInt =<<) <$> commitParser
|
||||
where
|
||||
commitParser = optional $ strOption $
|
||||
long "commits"
|
||||
<> help "Number of recent commit SHAs to display per token"
|
||||
commitParser =
|
||||
optional $
|
||||
strOption $ long "commits" <> help "Number of recent commit SHAs to display per token"
|
||||
|
||||
parseSearchBackend :: Parser SearchBackend
|
||||
parseSearchBackend = M.fromMaybe Ag <$> maybeBackend
|
||||
where
|
||||
maybeBackend = optional $ parseBackend <$> parseBackendOption
|
||||
parseBackendOption =
|
||||
strOption $
|
||||
long "search"
|
||||
<> help "[Allowed: ag, rg] Select searching backend"
|
||||
strOption $ long "search" <> help "[Allowed: ag, rg] Select searching backend"
|
||||
|
||||
parseBackend :: String -> SearchBackend
|
||||
parseBackend "ag" = Ag
|
||||
|
@ -9,7 +9,7 @@ module Types
|
||||
) where
|
||||
|
||||
import Control.Monad.Except (ExceptT, MonadError)
|
||||
import Control.Monad.Reader (MonadReader, ReaderT, MonadIO)
|
||||
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT)
|
||||
import Unused.CLI (SearchRunner)
|
||||
import Unused.Cache (FingerprintOutcome)
|
||||
import Unused.Grouping (CurrentGrouping)
|
||||
@ -38,6 +38,6 @@ data AppError
|
||||
| InvalidConfigError [ParseConfigError]
|
||||
| CacheError FingerprintOutcome
|
||||
|
||||
newtype App a = App {
|
||||
runApp :: ReaderT Options (ExceptT AppError IO) a
|
||||
} deriving (Monad, Functor, Applicative, AppConfig, MonadError AppError, MonadIO)
|
||||
newtype App a = App
|
||||
{ runApp :: ReaderT Options (ExceptT AppError IO) a
|
||||
} deriving (Monad, Functor, Applicative, AppConfig, MonadError AppError, MonadIO)
|
||||
|
@ -3,7 +3,6 @@
|
||||
module Common
|
||||
( (<>)
|
||||
) where
|
||||
|
||||
#if MIN_VERSION_base(4, 8, 0)
|
||||
import Data.Monoid ((<>))
|
||||
#endif
|
||||
|
@ -4,11 +4,11 @@ module Unused.Aliases
|
||||
) where
|
||||
|
||||
import qualified Data.List as L
|
||||
import Data.Text (Text)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Unused.ResultsClassifier.Types
|
||||
import Unused.Types (SearchTerm(..), TermMatch, tmTerm)
|
||||
import Unused.Util (groupBy)
|
||||
import Unused.ResultsClassifier.Types
|
||||
import Unused.Types (SearchTerm(..), TermMatch, tmTerm)
|
||||
import Unused.Util (groupBy)
|
||||
|
||||
groupedTermsAndAliases :: [TermMatch] -> [[TermMatch]]
|
||||
groupedTermsAndAliases = map snd . groupBy tmTerm
|
||||
@ -18,17 +18,17 @@ termsAndAliases [] = map OriginalTerm
|
||||
termsAndAliases as = L.nub . concatMap ((as >>=) . generateSearchTerms . T.pack)
|
||||
|
||||
generateSearchTerms :: Text -> TermAlias -> [SearchTerm]
|
||||
generateSearchTerms term TermAlias{taFrom = from, taTransform = transform} =
|
||||
generateSearchTerms term TermAlias {taFrom = from, taTransform = transform} =
|
||||
toTermWithAlias $ parsePatternForMatch (T.pack from) term
|
||||
where
|
||||
toTermWithAlias (Right (Just match)) = [OriginalTerm unpackedTerm, AliasTerm unpackedTerm (aliasedResult match)]
|
||||
toTermWithAlias (Right (Just match)) =
|
||||
[OriginalTerm unpackedTerm, AliasTerm unpackedTerm (aliasedResult match)]
|
||||
toTermWithAlias _ = [OriginalTerm unpackedTerm]
|
||||
unpackedTerm = T.unpack term
|
||||
aliasedResult = T.unpack . transform
|
||||
|
||||
parsePatternForMatch :: Text -> Text -> Either Text (Maybe Text)
|
||||
parsePatternForMatch aliasPattern term =
|
||||
findMatch $ T.splitOn wildcard aliasPattern
|
||||
parsePatternForMatch aliasPattern term = findMatch $ T.splitOn wildcard aliasPattern
|
||||
where
|
||||
findMatch [prefix, suffix] = Right $ T.stripSuffix suffix =<< T.stripPrefix prefix term
|
||||
findMatch _ = Left $ T.pack $ "There was a problem with the pattern: " ++ show aliasPattern
|
||||
|
@ -3,11 +3,12 @@ module Unused.CLI.GitContext
|
||||
) where
|
||||
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Unused.CLI.ProgressIndicator (createProgressBar, progressWithIndicator)
|
||||
import Unused.CLI.ProgressIndicator
|
||||
(createProgressBar, progressWithIndicator)
|
||||
import qualified Unused.CLI.Util as U
|
||||
import qualified Unused.CLI.Views as V
|
||||
import Unused.GitContext (gitContextForResults)
|
||||
import Unused.Types (TermMatchSet)
|
||||
import Unused.GitContext (gitContextForResults)
|
||||
import Unused.Types (TermMatchSet)
|
||||
|
||||
loadGitContext :: Int -> TermMatchSet -> IO TermMatchSet
|
||||
loadGitContext i tms = do
|
||||
|
@ -8,37 +8,38 @@ module Unused.CLI.ProgressIndicator.Internal
|
||||
import qualified Control.Concurrent as CC
|
||||
import qualified Control.Monad as M
|
||||
import qualified System.ProgressBar as PB
|
||||
import Unused.CLI.ProgressIndicator.Types (ProgressIndicator(..))
|
||||
import Unused.CLI.Util
|
||||
import Unused.CLI.ProgressIndicator.Types (ProgressIndicator(..))
|
||||
import Unused.CLI.Util
|
||||
|
||||
start :: ProgressIndicator -> Int -> IO (CC.ThreadId, ProgressIndicator)
|
||||
start s@Spinner{} _ = do
|
||||
start s@Spinner {} _ = do
|
||||
tid <- CC.forkIO $ runSpinner 0 s
|
||||
return (tid, s { sThreadId = Just tid })
|
||||
start ProgressBar{} i = do
|
||||
return (tid, s {sThreadId = Just tid})
|
||||
start ProgressBar {} i = do
|
||||
(ref, tid) <- buildProgressBar $ toInteger i
|
||||
return (tid, ProgressBar (Just ref) (Just tid))
|
||||
|
||||
stop :: ProgressIndicator -> IO ()
|
||||
stop ProgressBar{ pbThreadId = Just tid } = CC.killThread tid
|
||||
stop Spinner{ sThreadId = Just tid } = CC.killThread tid
|
||||
stop ProgressBar {pbThreadId = Just tid} = CC.killThread tid
|
||||
stop Spinner {sThreadId = Just tid} = CC.killThread tid
|
||||
stop _ = return ()
|
||||
|
||||
increment :: ProgressIndicator -> IO ()
|
||||
increment ProgressBar{ pbProgressRef = Just ref } = PB.incProgress ref 1
|
||||
increment ProgressBar {pbProgressRef = Just ref} = PB.incProgress ref 1
|
||||
increment _ = return ()
|
||||
|
||||
printPrefix :: ProgressIndicator -> IO ()
|
||||
printPrefix ProgressBar{} = putStr "\n\n"
|
||||
printPrefix Spinner{} = putStr " "
|
||||
printPrefix ProgressBar {} = putStr "\n\n"
|
||||
printPrefix Spinner {} = putStr " "
|
||||
|
||||
runSpinner :: Int -> ProgressIndicator -> IO ()
|
||||
runSpinner i s@Spinner{ sDelay = delay, sSnapshots = snapshots, sColors = colors, sLength = length' } = M.forever $ do
|
||||
setSGR [SetColor Foreground Dull currentColor]
|
||||
putStr currentSnapshot
|
||||
cursorBackward 1
|
||||
CC.threadDelay delay
|
||||
runSpinner (i + 1) s
|
||||
runSpinner i s@Spinner {sDelay = delay, sSnapshots = snapshots, sColors = colors, sLength = length'} =
|
||||
M.forever $ do
|
||||
setSGR [SetColor Foreground Dull currentColor]
|
||||
putStr currentSnapshot
|
||||
cursorBackward 1
|
||||
CC.threadDelay delay
|
||||
runSpinner (i + 1) s
|
||||
where
|
||||
currentSnapshot = snapshots !! (i `mod` snapshotLength)
|
||||
currentColor = colors !! (i `div` snapshotLength)
|
||||
@ -46,8 +47,7 @@ runSpinner i s@Spinner{ sDelay = delay, sSnapshots = snapshots, sColors = colors
|
||||
runSpinner _ _ = return ()
|
||||
|
||||
buildProgressBar :: Integer -> IO (PB.ProgressRef, CC.ThreadId)
|
||||
buildProgressBar =
|
||||
PB.startProgress (PB.msg message) PB.percentage progressBarWidth
|
||||
buildProgressBar = PB.startProgress (PB.msg message) PB.percentage progressBarWidth
|
||||
where
|
||||
message = "Working"
|
||||
progressBarWidth = 60
|
||||
|
@ -7,14 +7,10 @@ import qualified System.Console.ANSI as ANSI
|
||||
import qualified System.ProgressBar as PB
|
||||
|
||||
data ProgressIndicator
|
||||
= Spinner
|
||||
{ sSnapshots :: [String]
|
||||
, sLength :: Int
|
||||
, sDelay :: Int
|
||||
, sColors :: [ANSI.Color]
|
||||
, sThreadId :: Maybe CC.ThreadId
|
||||
}
|
||||
| ProgressBar
|
||||
{ pbProgressRef :: Maybe PB.ProgressRef
|
||||
, pbThreadId :: Maybe CC.ThreadId
|
||||
}
|
||||
= Spinner { sSnapshots :: [String]
|
||||
, sLength :: Int
|
||||
, sDelay :: Int
|
||||
, sColors :: [ANSI.Color]
|
||||
, sThreadId :: Maybe CC.ThreadId }
|
||||
| ProgressBar { pbProgressRef :: Maybe PB.ProgressRef
|
||||
, pbThreadId :: Maybe CC.ThreadId }
|
||||
|
@ -9,7 +9,9 @@ import qualified Unused.CLI.Util as U
|
||||
import qualified Unused.CLI.Views as V
|
||||
import qualified Unused.TermSearch as TS
|
||||
|
||||
data SearchRunner = SearchWithProgress | SearchWithoutProgress
|
||||
data SearchRunner
|
||||
= SearchWithProgress
|
||||
| SearchWithoutProgress
|
||||
|
||||
renderHeader :: [a] -> IO ()
|
||||
renderHeader terms = do
|
||||
@ -22,5 +24,5 @@ executeSearch backend runner terms = do
|
||||
runSearch backend runner terms <* U.resetScreen
|
||||
|
||||
runSearch :: TS.SearchBackend -> SearchRunner -> [TS.SearchTerm] -> IO TS.SearchResults
|
||||
runSearch b SearchWithProgress = I.progressWithIndicator (TS.search b) I.createProgressBar
|
||||
runSearch b SearchWithProgress = I.progressWithIndicator (TS.search b) I.createProgressBar
|
||||
runSearch b SearchWithoutProgress = I.progressWithIndicator (TS.search b) I.createSpinner
|
||||
|
@ -2,20 +2,18 @@ module Unused.CLI.Views.InvalidConfigError
|
||||
( invalidConfigError
|
||||
) where
|
||||
|
||||
import Unused.CLI.Util
|
||||
import Unused.CLI.Util
|
||||
import qualified Unused.CLI.Views.Error as V
|
||||
import Unused.ResultsClassifier (ParseConfigError(..))
|
||||
import Unused.ResultsClassifier (ParseConfigError(..))
|
||||
|
||||
invalidConfigError :: [ParseConfigError] -> IO ()
|
||||
invalidConfigError es = do
|
||||
V.errorHeader "There was a problem with the following config file(s):"
|
||||
|
||||
mapM_ configError es
|
||||
|
||||
setSGR [Reset]
|
||||
|
||||
configError :: ParseConfigError -> IO ()
|
||||
configError ParseConfigError{ pcePath = path, pceParseError = msg} = do
|
||||
configError ParseConfigError {pcePath = path, pceParseError = msg} = do
|
||||
setSGR [SetConsoleIntensity BoldIntensity]
|
||||
putStrLn path
|
||||
setSGR [Reset]
|
||||
|
@ -6,7 +6,7 @@ import Unused.CLI.Util
|
||||
|
||||
noResultsFound :: IO ()
|
||||
noResultsFound = do
|
||||
setSGR [SetColor Foreground Dull Green]
|
||||
setSGR [SetConsoleIntensity BoldIntensity]
|
||||
setSGR [SetColor Foreground Dull Green]
|
||||
setSGR [SetConsoleIntensity BoldIntensity]
|
||||
putStrLn "Unused found no results"
|
||||
setSGR [Reset]
|
||||
setSGR [Reset]
|
||||
|
@ -3,16 +3,16 @@ module Unused.CLI.Views.SearchResult
|
||||
, searchResults
|
||||
) where
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
import Control.Arrow ((&&&))
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Unused.CLI.Util
|
||||
import Unused.CLI.Util
|
||||
import qualified Unused.CLI.Views.NoResultsFound as V
|
||||
import Unused.CLI.Views.SearchResult.ColumnFormatter
|
||||
import Unused.CLI.Views.SearchResult.ColumnFormatter
|
||||
import qualified Unused.CLI.Views.SearchResult.ListResult as V
|
||||
import qualified Unused.CLI.Views.SearchResult.TableResult as V
|
||||
import Unused.CLI.Views.SearchResult.Types
|
||||
import Unused.Grouping (Grouping(..), GroupedTerms)
|
||||
import Unused.Types (TermMatchSet, TermResults(..), TermMatch)
|
||||
import Unused.CLI.Views.SearchResult.Types
|
||||
import Unused.Grouping (GroupedTerms, Grouping(..))
|
||||
import Unused.Types (TermMatch, TermMatchSet, TermResults(..))
|
||||
|
||||
searchResults :: ResultsFormat -> [GroupedTerms] -> IO ()
|
||||
searchResults format terms = do
|
||||
@ -28,8 +28,7 @@ printFormattedTerms [] = liftIO V.noResultsFound
|
||||
printFormattedTerms ts = mapM_ printGroupingSection ts
|
||||
|
||||
listFromMatchSet :: TermMatchSet -> [(String, TermResults)]
|
||||
listFromMatchSet =
|
||||
Map.toList
|
||||
listFromMatchSet = Map.toList
|
||||
|
||||
printGroupingSection :: GroupedTerms -> ResultsPrinter ()
|
||||
printGroupingSection (g, tms) = do
|
||||
@ -46,8 +45,7 @@ printGrouping g = do
|
||||
setSGR [Reset]
|
||||
|
||||
printTermResults :: (String, TermResults) -> ResultsPrinter ()
|
||||
printTermResults =
|
||||
uncurry printMatches . (id &&& trMatches) . snd
|
||||
printTermResults = uncurry printMatches . (id &&& trMatches) . snd
|
||||
|
||||
printMatches :: TermResults -> [TermMatch] -> ResultsPrinter ()
|
||||
printMatches r ms = do
|
||||
|
@ -3,27 +3,30 @@ module Unused.Cache.DirectoryFingerprint
|
||||
, sha
|
||||
) where
|
||||
|
||||
import Control.Monad.Reader (ReaderT, runReaderT, asks, liftIO)
|
||||
import Control.Monad.Reader (ReaderT, asks, liftIO, runReaderT)
|
||||
import qualified Data.Char as C
|
||||
import qualified Data.Maybe as M
|
||||
import qualified System.Directory as D
|
||||
import qualified System.Process as P
|
||||
import Unused.Cache.FindArgsFromIgnoredPaths (findArgs)
|
||||
import Unused.Util (safeHead, safeReadFile)
|
||||
import Unused.Cache.FindArgsFromIgnoredPaths (findArgs)
|
||||
import Unused.Util (safeHead, safeReadFile)
|
||||
|
||||
newtype MD5ExecutablePath = MD5ExecutablePath { toMD5String :: String }
|
||||
newtype MD5ExecutablePath = MD5ExecutablePath
|
||||
{ toMD5String :: String
|
||||
}
|
||||
|
||||
type MD5Config = ReaderT MD5ExecutablePath IO
|
||||
|
||||
data FingerprintOutcome
|
||||
= MD5ExecutableNotFound [String]
|
||||
data FingerprintOutcome =
|
||||
MD5ExecutableNotFound [String]
|
||||
|
||||
sha :: IO (Either FingerprintOutcome String)
|
||||
sha = do
|
||||
md5Executable' <- md5Executable
|
||||
case md5Executable' of
|
||||
Just exec ->
|
||||
Right . getSha <$> runReaderT (fileList >>= sortInput >>= md5Result) (MD5ExecutablePath exec)
|
||||
Right . getSha <$>
|
||||
runReaderT (fileList >>= sortInput >>= md5Result) (MD5ExecutablePath exec)
|
||||
Nothing -> return $ Left $ MD5ExecutableNotFound supportedMD5Executables
|
||||
where
|
||||
getSha = takeWhile C.isAlphaNum . M.fromMaybe "" . safeHead . lines
|
||||
@ -32,7 +35,9 @@ fileList :: MD5Config String
|
||||
fileList = do
|
||||
filterNamePathArgs <- liftIO $ findArgs <$> ignoredPaths
|
||||
md5exec <- asks toMD5String
|
||||
let args = [".", "-type", "f", "-not", "-path", "*/.git/*"] ++ filterNamePathArgs ++ ["-exec", md5exec, "{}", "+"]
|
||||
let args =
|
||||
[".", "-type", "f", "-not", "-path", "*/.git/*"] ++
|
||||
filterNamePathArgs ++ ["-exec", md5exec, "{}", "+"]
|
||||
liftIO $ P.readProcess "find" args ""
|
||||
|
||||
sortInput :: String -> MD5Config String
|
||||
@ -47,8 +52,7 @@ ignoredPaths :: IO [String]
|
||||
ignoredPaths = either (const []) id <$> (fmap lines <$> safeReadFile ".gitignore")
|
||||
|
||||
md5Executable :: IO (Maybe String)
|
||||
md5Executable =
|
||||
safeHead . concat <$> mapM D.findExecutables supportedMD5Executables
|
||||
md5Executable = safeHead . concat <$> mapM D.findExecutables supportedMD5Executables
|
||||
|
||||
supportedMD5Executables :: [String]
|
||||
supportedMD5Executables = ["md5", "md5sum"]
|
||||
|
@ -38,8 +38,7 @@ isMissingFilename :: String -> Bool
|
||||
isMissingFilename = null . FP.takeFileName
|
||||
|
||||
validIgnoreOptions :: [String] -> [String]
|
||||
validIgnoreOptions =
|
||||
filter isPath
|
||||
validIgnoreOptions = filter isPath
|
||||
where
|
||||
isPath "" = False
|
||||
isPath ('/':_) = True
|
||||
|
@ -4,7 +4,8 @@ module Unused.Grouping.Internal
|
||||
|
||||
import qualified Data.List as L
|
||||
import qualified System.FilePath as FP
|
||||
import Unused.Grouping.Types (CurrentGrouping(..), Grouping(..), GroupFilter)
|
||||
import Unused.Grouping.Types
|
||||
(CurrentGrouping(..), GroupFilter, Grouping(..))
|
||||
import qualified Unused.Types as T
|
||||
|
||||
groupFilter :: CurrentGrouping -> GroupFilter
|
||||
@ -14,5 +15,4 @@ groupFilter GroupByFile = ByFile . T.tmPath
|
||||
groupFilter NoGroup = const NoGrouping
|
||||
|
||||
shortenedDirectory :: String -> String
|
||||
shortenedDirectory =
|
||||
L.intercalate "/" . take 2 . FP.splitDirectories . FP.takeDirectory
|
||||
shortenedDirectory = L.intercalate "/" . take 2 . FP.splitDirectories . FP.takeDirectory
|
||||
|
@ -5,12 +5,23 @@ module Unused.Grouping.Types
|
||||
, GroupFilter
|
||||
) where
|
||||
|
||||
import Unused.Types (TermMatchSet, TermMatch)
|
||||
import Unused.Types (TermMatch, TermMatchSet)
|
||||
|
||||
data Grouping = ByDirectory String | ByTerm String | ByFile String | NoGrouping deriving (Eq, Ord)
|
||||
data CurrentGrouping = GroupByDirectory | GroupByTerm | GroupByFile | NoGroup
|
||||
data Grouping
|
||||
= ByDirectory String
|
||||
| ByTerm String
|
||||
| ByFile String
|
||||
| NoGrouping
|
||||
deriving (Eq, Ord)
|
||||
|
||||
data CurrentGrouping
|
||||
= GroupByDirectory
|
||||
| GroupByTerm
|
||||
| GroupByFile
|
||||
| NoGroup
|
||||
|
||||
type GroupedTerms = (Grouping, TermMatchSet)
|
||||
|
||||
type GroupFilter = TermMatch -> Grouping
|
||||
|
||||
instance Show Grouping where
|
||||
|
@ -2,23 +2,24 @@ module Unused.Parser
|
||||
( parseResults
|
||||
) where
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
import Control.Arrow ((&&&))
|
||||
import qualified Data.Bifunctor as BF
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Unused.Aliases (groupedTermsAndAliases)
|
||||
import Unused.LikelihoodCalculator (calculateLikelihood)
|
||||
import Unused.ResultsClassifier.Types (LanguageConfiguration(..))
|
||||
import Unused.TermSearch (SearchResults, fromResults)
|
||||
import Unused.Types (TermMatchSet, TermMatch, resultsFromMatches, tmDisplayTerm)
|
||||
import Unused.Aliases (groupedTermsAndAliases)
|
||||
import Unused.LikelihoodCalculator (calculateLikelihood)
|
||||
import Unused.ResultsClassifier.Types (LanguageConfiguration(..))
|
||||
import Unused.TermSearch (SearchResults, fromResults)
|
||||
import Unused.Types
|
||||
(TermMatch, TermMatchSet, resultsFromMatches, tmDisplayTerm)
|
||||
|
||||
parseResults :: [LanguageConfiguration] -> SearchResults -> TermMatchSet
|
||||
parseResults lcs =
|
||||
Map.fromList . map (BF.second $ calculateLikelihood lcs . resultsFromMatches) . groupResults . fromResults
|
||||
Map.fromList .
|
||||
map (BF.second $ calculateLikelihood lcs . resultsFromMatches) . groupResults . fromResults
|
||||
|
||||
groupResults :: [TermMatch] -> [(String, [TermMatch])]
|
||||
groupResults ms =
|
||||
map (toKey &&& id) groupedMatches
|
||||
groupResults ms = map (toKey &&& id) groupedMatches
|
||||
where
|
||||
toKey = L.intercalate "|" . L.nub . L.sort . map tmDisplayTerm
|
||||
groupedMatches = groupedTermsAndAliases ms
|
||||
|
@ -1,12 +1,12 @@
|
||||
module Unused.Projection where
|
||||
|
||||
import qualified Data.Bifunctor as BF
|
||||
import Data.Monoid ((<>))
|
||||
import Data.Text (Text)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Text.Megaparsec
|
||||
import Text.Megaparsec.Text
|
||||
import Unused.Projection.Transform
|
||||
import Text.Megaparsec
|
||||
import Text.Megaparsec.Text
|
||||
import Unused.Projection.Transform
|
||||
|
||||
data ParsedTransform = ParsedTransform
|
||||
{ ptPre :: Text
|
||||
@ -18,20 +18,14 @@ translate :: Text -> Either String (Text -> Text)
|
||||
translate template = applyTransform <$> parseTransform template
|
||||
|
||||
applyTransform :: ParsedTransform -> Text -> Text
|
||||
applyTransform pt t =
|
||||
ptPre pt
|
||||
<> runTransformations t (ptTransforms pt)
|
||||
<> ptPost pt
|
||||
applyTransform pt t = ptPre pt <> runTransformations t (ptTransforms pt) <> ptPost pt
|
||||
|
||||
parseTransform :: Text -> Either String ParsedTransform
|
||||
parseTransform = BF.first show . parse parsedTransformParser ""
|
||||
|
||||
parsedTransformParser :: Parser ParsedTransform
|
||||
parsedTransformParser =
|
||||
ParsedTransform
|
||||
<$> preTransformsParser
|
||||
<*> transformsParser
|
||||
<*> postTransformsParser
|
||||
ParsedTransform <$> preTransformsParser <*> transformsParser <*> postTransformsParser
|
||||
|
||||
preTransformsParser :: Parser Text
|
||||
preTransformsParser = T.pack <$> manyTill anyChar (char '{')
|
||||
@ -45,7 +39,8 @@ postTransformsParser = T.pack <$> many anyChar
|
||||
transformParser :: Parser Transform
|
||||
transformParser = do
|
||||
result <- string "camelcase" <|> string "snakecase"
|
||||
return $ case result of
|
||||
"camelcase" -> Camelcase
|
||||
"snakecase" -> Snakecase
|
||||
_ -> Noop
|
||||
return $
|
||||
case result of
|
||||
"camelcase" -> Camelcase
|
||||
"snakecase" -> Snakecase
|
||||
_ -> Noop
|
||||
|
@ -11,8 +11,12 @@ module Unused.ResponseFilter
|
||||
import qualified Data.Char as C
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Unused.ResultsClassifier (Position(..), Matcher(..), LanguageConfiguration(..), LowLikelihoodMatch(..))
|
||||
import Unused.Types (TermResults(..), TermMatchSet, TermMatch(..), RemovalLikelihood, Removal(..), totalOccurrenceCount, appOccurrenceCount)
|
||||
import Unused.ResultsClassifier
|
||||
(LanguageConfiguration(..), LowLikelihoodMatch(..), Matcher(..),
|
||||
Position(..))
|
||||
import Unused.Types
|
||||
(Removal(..), RemovalLikelihood, TermMatch(..), TermMatchSet,
|
||||
TermResults(..), appOccurrenceCount, totalOccurrenceCount)
|
||||
|
||||
withOneOccurrence :: TermMatchSet -> TermMatchSet
|
||||
withOneOccurrence = Map.filterWithKey (const oneOccurence)
|
||||
@ -25,8 +29,7 @@ withLikelihoods [] = id
|
||||
withLikelihoods l = Map.filterWithKey (const $ includesLikelihood l)
|
||||
|
||||
ignoringPaths :: [String] -> TermMatchSet -> TermMatchSet
|
||||
ignoringPaths xs =
|
||||
updateMatches newMatches
|
||||
ignoringPaths xs = updateMatches newMatches
|
||||
where
|
||||
newMatches = filter (not . matchesPath . tmPath)
|
||||
matchesPath p = any (`L.isInfixOf` p) xs
|
||||
@ -35,21 +38,18 @@ includesLikelihood :: [RemovalLikelihood] -> TermResults -> Bool
|
||||
includesLikelihood l = (`elem` l) . rLikelihood . trRemoval
|
||||
|
||||
isClassOrModule :: TermResults -> Bool
|
||||
isClassOrModule =
|
||||
startsWithUpper . trTerm
|
||||
isClassOrModule = startsWithUpper . trTerm
|
||||
where
|
||||
startsWithUpper [] = False
|
||||
startsWithUpper (a:_) = C.isUpper a
|
||||
|
||||
autoLowLikelihood :: LanguageConfiguration -> TermResults -> Bool
|
||||
autoLowLikelihood l r =
|
||||
isAllowedTerm r allowedTerms || or anySinglesOkay
|
||||
autoLowLikelihood l r = isAllowedTerm r allowedTerms || or anySinglesOkay
|
||||
where
|
||||
allowedTerms = lcAllowedTerms l
|
||||
anySinglesOkay = map (\sm -> classOrModule sm r && matchesToBool (smMatchers sm)) singles
|
||||
singles = lcAutoLowLikelihood l
|
||||
classOrModule = classOrModuleFunction . smClassOrModule
|
||||
|
||||
matchesToBool :: [Matcher] -> Bool
|
||||
matchesToBool [] = False
|
||||
matchesToBool a = all (`matcherToBool` r) a
|
||||
@ -73,10 +73,9 @@ paths :: TermResults -> [String]
|
||||
paths = fmap tmPath . trMatches
|
||||
|
||||
updateMatches :: ([TermMatch] -> [TermMatch]) -> TermMatchSet -> TermMatchSet
|
||||
updateMatches fm =
|
||||
Map.map (updateMatchesWith $ fm . trMatches)
|
||||
updateMatches fm = Map.map (updateMatchesWith $ fm . trMatches)
|
||||
where
|
||||
updateMatchesWith f tr = tr { trMatches = f tr }
|
||||
updateMatchesWith f tr = tr {trMatches = f tr}
|
||||
|
||||
isAllowedTerm :: TermResults -> [String] -> Bool
|
||||
isAllowedTerm = elem . trTerm
|
||||
|
@ -9,7 +9,7 @@ import qualified Data.Bifunctor as BF
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Text as T
|
||||
import qualified System.Directory as D
|
||||
import Unused.Util (safeReadFile)
|
||||
import Unused.Util (safeReadFile)
|
||||
|
||||
data TagSearchOutcome
|
||||
= TagsFileNotFound [String]
|
||||
@ -22,8 +22,7 @@ loadTagsFromFile :: IO (Either TagSearchOutcome [String])
|
||||
loadTagsFromFile = fmap (fmap tokensFromTags) tagsContent
|
||||
|
||||
tokensFromTags :: String -> [String]
|
||||
tokensFromTags =
|
||||
filter validTokens . L.nub . tokenLocations
|
||||
tokensFromTags = filter validTokens . L.nub . tokenLocations
|
||||
where
|
||||
tokenLocations = map (token . T.splitOn "\t" . T.pack) . lines
|
||||
token = T.unpack . head
|
||||
|
@ -6,24 +6,23 @@ module Unused.TermSearch
|
||||
) where
|
||||
|
||||
import qualified Data.Maybe as M
|
||||
import GHC.IO.Exception (ExitCode(ExitSuccess))
|
||||
import GHC.IO.Exception (ExitCode(ExitSuccess))
|
||||
import qualified System.Process as P
|
||||
import Unused.TermSearch.Internal (commandLineOptions, parseSearchResult)
|
||||
import Unused.TermSearch.Types (SearchResults(..), SearchBackend(..))
|
||||
import Unused.Types (SearchTerm, searchTermToString)
|
||||
import Unused.TermSearch.Internal
|
||||
(commandLineOptions, parseSearchResult)
|
||||
import Unused.TermSearch.Types
|
||||
(SearchBackend(..), SearchResults(..))
|
||||
import Unused.Types (SearchTerm, searchTermToString)
|
||||
|
||||
search :: SearchBackend -> SearchTerm -> IO SearchResults
|
||||
search backend t =
|
||||
SearchResults . M.mapMaybe (parseSearchResult backend t) <$> (lines <$> performSearch backend (searchTermToString t))
|
||||
SearchResults . M.mapMaybe (parseSearchResult backend t) <$>
|
||||
(lines <$> performSearch backend (searchTermToString t))
|
||||
|
||||
performSearch :: SearchBackend -> String -> IO String
|
||||
performSearch b t = extractSearchResults b <$> searchOutcome
|
||||
where
|
||||
searchOutcome =
|
||||
P.readProcessWithExitCode
|
||||
(backendToCommand b)
|
||||
(commandLineOptions b t)
|
||||
""
|
||||
searchOutcome = P.readProcessWithExitCode (backendToCommand b) (commandLineOptions b t) ""
|
||||
backendToCommand Rg = "rg"
|
||||
backendToCommand Ag = "ag"
|
||||
|
||||
|
@ -6,9 +6,9 @@ module Unused.TermSearch.Internal
|
||||
import qualified Data.Char as C
|
||||
import qualified Data.Maybe as M
|
||||
import qualified Data.Text as T
|
||||
import Unused.TermSearch.Types (SearchBackend(..))
|
||||
import Unused.Types (SearchTerm(..), TermMatch(..))
|
||||
import Unused.Util (stringToInt)
|
||||
import Unused.TermSearch.Types (SearchBackend(..))
|
||||
import Unused.Types (SearchTerm(..), TermMatch(..))
|
||||
import Unused.Util (stringToInt)
|
||||
|
||||
commandLineOptions :: SearchBackend -> String -> [String]
|
||||
commandLineOptions backend t =
|
||||
@ -17,8 +17,7 @@ commandLineOptions backend t =
|
||||
else nonRegexFlags backend t ++ baseFlags backend
|
||||
|
||||
parseSearchResult :: SearchBackend -> SearchTerm -> String -> Maybe TermMatch
|
||||
parseSearchResult backend term =
|
||||
maybeTermMatch backend . map T.unpack . T.splitOn ":" . T.pack
|
||||
parseSearchResult backend term = maybeTermMatch backend . map T.unpack . T.splitOn ":" . T.pack
|
||||
where
|
||||
maybeTermMatch Rg [path, count] = Just $ toTermMatch term path $ countInt count
|
||||
maybeTermMatch Rg _ = Nothing
|
||||
|
@ -7,6 +7,10 @@ module Unused.TermSearch.Types
|
||||
|
||||
import Unused.Types (TermMatch)
|
||||
|
||||
data SearchBackend = Ag | Rg
|
||||
data SearchBackend
|
||||
= Ag
|
||||
| Rg
|
||||
|
||||
newtype SearchResults = SearchResults { fromResults :: [TermMatch] } deriving (Monoid)
|
||||
newtype SearchResults = SearchResults
|
||||
{ fromResults :: [TermMatch]
|
||||
} deriving (Monoid)
|
||||
|
@ -20,17 +20,19 @@ module Unused.Types
|
||||
, resultAliases
|
||||
) where
|
||||
|
||||
import Control.Monad (liftM2)
|
||||
import Data.Csv (FromRecord, ToRecord)
|
||||
import Control.Monad (liftM2)
|
||||
import Data.Csv (FromRecord, ToRecord)
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Maybe as M
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Maybe as M
|
||||
import qualified GHC.Generics as G
|
||||
import qualified Unused.Regex as R
|
||||
|
||||
data SearchTerm
|
||||
= OriginalTerm String
|
||||
| AliasTerm String String deriving (Eq, Show)
|
||||
| AliasTerm String
|
||||
String
|
||||
deriving (Eq, Show)
|
||||
|
||||
searchTermToString :: SearchTerm -> String
|
||||
searchTermToString (OriginalTerm s) = s
|
||||
@ -44,6 +46,7 @@ data TermMatch = TermMatch
|
||||
} deriving (Eq, Show, G.Generic)
|
||||
|
||||
instance FromRecord TermMatch
|
||||
|
||||
instance ToRecord TermMatch
|
||||
|
||||
data Occurrences = Occurrences
|
||||
@ -75,7 +78,13 @@ data GitCommit = GitCommit
|
||||
{ gcSha :: String
|
||||
} deriving (Eq, Show)
|
||||
|
||||
data RemovalLikelihood = High | Medium | Low | Unknown | NotCalculated deriving (Eq, Show)
|
||||
data RemovalLikelihood
|
||||
= High
|
||||
| Medium
|
||||
| Low
|
||||
| Unknown
|
||||
| NotCalculated
|
||||
deriving (Eq, Show)
|
||||
|
||||
type TermMatchSet = Map.Map String TermResults
|
||||
|
||||
@ -100,15 +109,18 @@ tmDisplayTerm = liftM2 M.fromMaybe tmTerm tmAlias
|
||||
resultsFromMatches :: [TermMatch] -> TermResults
|
||||
resultsFromMatches tms =
|
||||
TermResults
|
||||
{ trTerm = resultTerm terms
|
||||
, trTerms = L.sort $ L.nub terms
|
||||
, trMatches = tms
|
||||
, trAppOccurrences = appOccurrence
|
||||
, trTestOccurrences = testOccurrence
|
||||
, trTotalOccurrences = Occurrences (sum $ map oFiles [appOccurrence, testOccurrence]) (sum $ map oOccurrences [appOccurrence, testOccurrence])
|
||||
, trRemoval = Removal NotCalculated "Likelihood not calculated"
|
||||
, trGitContext = Nothing
|
||||
}
|
||||
{ trTerm = resultTerm terms
|
||||
, trTerms = L.sort $ L.nub terms
|
||||
, trMatches = tms
|
||||
, trAppOccurrences = appOccurrence
|
||||
, trTestOccurrences = testOccurrence
|
||||
, trTotalOccurrences =
|
||||
Occurrences
|
||||
(sum $ map oFiles [appOccurrence, testOccurrence])
|
||||
(sum $ map oOccurrences [appOccurrence, testOccurrence])
|
||||
, trRemoval = Removal NotCalculated "Likelihood not calculated"
|
||||
, trGitContext = Nothing
|
||||
}
|
||||
where
|
||||
testOccurrence = testOccurrences tms
|
||||
appOccurrence = appOccurrences tms
|
||||
@ -117,8 +129,7 @@ resultsFromMatches tms =
|
||||
resultTerm _ = ""
|
||||
|
||||
appOccurrences :: [TermMatch] -> Occurrences
|
||||
appOccurrences ms =
|
||||
Occurrences appFiles appOccurrences'
|
||||
appOccurrences ms = Occurrences appFiles appOccurrences'
|
||||
where
|
||||
totalFiles = length $ L.nub $ map tmPath ms
|
||||
totalOccurrences = sum $ map tmOccurrences ms
|
||||
@ -127,8 +138,7 @@ appOccurrences ms =
|
||||
appOccurrences' = totalOccurrences - oOccurrences tests
|
||||
|
||||
testOccurrences :: [TermMatch] -> Occurrences
|
||||
testOccurrences ms =
|
||||
Occurrences totalFiles totalOccurrences
|
||||
testOccurrences ms = Occurrences totalFiles totalOccurrences
|
||||
where
|
||||
testMatches = filter termMatchIsTest ms
|
||||
totalFiles = length $ L.nub $ map tmPath testMatches
|
||||
@ -144,5 +154,5 @@ testCamelCaseFilename :: String -> Bool
|
||||
testCamelCaseFilename = R.matchRegex ".*(Spec|Test)\\."
|
||||
|
||||
termMatchIsTest :: TermMatch -> Bool
|
||||
termMatchIsTest TermMatch{tmPath = path} =
|
||||
termMatchIsTest TermMatch {tmPath = path} =
|
||||
testDir path || testSnakeCaseFilename path || testCamelCaseFilename path
|
||||
|
@ -8,18 +8,16 @@ module Unused.Util
|
||||
, safeReadFile
|
||||
) where
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
import Control.Arrow ((&&&))
|
||||
import qualified Control.Exception as E
|
||||
import qualified Data.ByteString.Char8 as C8
|
||||
import qualified Data.ByteString.Lazy.Char8 as Cl8
|
||||
import qualified Data.Char as C
|
||||
import Data.Function (on)
|
||||
import Data.Function (on)
|
||||
import qualified Data.List as L
|
||||
|
||||
groupBy :: (Ord b) => (a -> b) -> [a] -> [(b, [a])]
|
||||
groupBy f = map (f . head &&& id)
|
||||
. L.groupBy ((==) `on` f)
|
||||
. L.sortBy (compare `on` f)
|
||||
groupBy f = map (f . head &&& id) . L.groupBy ((==) `on` f) . L.sortBy (compare `on` f)
|
||||
|
||||
safeHead :: [a] -> Maybe a
|
||||
safeHead (x:_) = Just x
|
||||
|
@ -10,14 +10,18 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "termsAndAliases" $ do
|
||||
it "returns the terms if no aliases are provided" $
|
||||
termsAndAliases [] ["method_1", "method_2"] `shouldBe` [OriginalTerm "method_1", OriginalTerm "method_2"]
|
||||
|
||||
termsAndAliases [] ["method_1", "method_2"] `shouldBe`
|
||||
[OriginalTerm "method_1", OriginalTerm "method_2"]
|
||||
it "adds aliases to the list of terms" $ do
|
||||
let predicateAlias = TermAlias "*?" "be_{}" ("be_" <>)
|
||||
let pluralizeAlias = TermAlias "really_*" "very_{}" ("very_" <>)
|
||||
|
||||
termsAndAliases [predicateAlias, pluralizeAlias] ["awesome?", "really_cool"]
|
||||
`shouldBe` [OriginalTerm "awesome?", AliasTerm "awesome?" "be_awesome", OriginalTerm "really_cool", AliasTerm "really_cool" "very_cool"]
|
||||
termsAndAliases [predicateAlias, pluralizeAlias] ["awesome?", "really_cool"] `shouldBe`
|
||||
[ OriginalTerm "awesome?"
|
||||
, AliasTerm "awesome?" "be_awesome"
|
||||
, OriginalTerm "really_cool"
|
||||
, AliasTerm "really_cool" "very_cool"
|
||||
]
|
||||
|
@ -10,18 +10,24 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "findArgs" $ do
|
||||
it "converts paths" $
|
||||
findArgs ["a/*", "/b/*", "c/"] `shouldBe` [ "-not", "-path", "*/a/*"
|
||||
, "-not", "-path", "*/b/*"
|
||||
, "-not", "-path", "*/c/*"]
|
||||
|
||||
findArgs ["a/*", "/b/*", "c/"] `shouldBe`
|
||||
["-not", "-path", "*/a/*", "-not", "-path", "*/b/*", "-not", "-path", "*/c/*"]
|
||||
it "converts wildcards" $
|
||||
findArgs ["a/*.csv", "/b/*.csv"] `shouldBe` [ "-not", "-path", "*/a/*.csv"
|
||||
, "-not", "-path", "*/b/*.csv"]
|
||||
|
||||
findArgs ["a/*.csv", "/b/*.csv"] `shouldBe`
|
||||
["-not", "-path", "*/a/*.csv", "-not", "-path", "*/b/*.csv"]
|
||||
it "filenames and paths at the same time" $
|
||||
findArgs ["/.foreman", ".bundle/"] `shouldBe` [ "-not", "-name", "*/.foreman"
|
||||
, "-not", "-path", "*/.foreman/*"
|
||||
, "-not", "-path", "*/.bundle/*"]
|
||||
findArgs ["/.foreman", ".bundle/"] `shouldBe`
|
||||
[ "-not"
|
||||
, "-name"
|
||||
, "*/.foreman"
|
||||
, "-not"
|
||||
, "-path"
|
||||
, "*/.foreman/*"
|
||||
, "-not"
|
||||
, "-path"
|
||||
, "*/.bundle/*"
|
||||
]
|
||||
|
@ -12,24 +12,18 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "groupFilter" $ do
|
||||
it "groups by directory" $ do
|
||||
let termMatch = TermMatch "AwesomeClass" "foo/bar/baz/buzz.rb" Nothing 10
|
||||
|
||||
groupFilter GroupByDirectory termMatch `shouldBe` ByDirectory "foo/bar"
|
||||
|
||||
it "groups by term" $ do
|
||||
let termMatch = TermMatch "AwesomeClass" "foo/bar/baz/buzz.rb" Nothing 10
|
||||
|
||||
groupFilter GroupByTerm termMatch `shouldBe` ByTerm "AwesomeClass"
|
||||
|
||||
it "groups by file" $ do
|
||||
let termMatch = TermMatch "AwesomeClass" "foo/bar/baz/buzz.rb" Nothing 10
|
||||
|
||||
groupFilter GroupByFile termMatch `shouldBe` ByFile "foo/bar/baz/buzz.rb"
|
||||
|
||||
it "groups by nothing" $ do
|
||||
let termMatch = TermMatch "AwesomeClass" "foo/bar/baz/buzz.rb" Nothing 10
|
||||
|
||||
groupFilter NoGroup termMatch `shouldBe` NoGrouping
|
||||
|
@ -12,52 +12,55 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "calculateLikelihood" $ do
|
||||
it "prefers language-specific checks first" $ do
|
||||
let railsMatches = [ TermMatch "ApplicationController" "app/controllers/application_controller.rb" Nothing 1 ]
|
||||
let railsMatches =
|
||||
[ TermMatch
|
||||
"ApplicationController"
|
||||
"app/controllers/application_controller.rb"
|
||||
Nothing
|
||||
1
|
||||
]
|
||||
removalLikelihood' railsMatches `shouldBe` Low
|
||||
|
||||
let elixirMatches = [ TermMatch "AwesomeView" "web/views/awesome_view.ex" Nothing 1 ]
|
||||
let elixirMatches = [TermMatch "AwesomeView" "web/views/awesome_view.ex" Nothing 1]
|
||||
removalLikelihood' elixirMatches `shouldBe` Low
|
||||
|
||||
it "weighs widely-used methods as low likelihood" $ do
|
||||
let matches = [ TermMatch "full_name" "app/models/user.rb" Nothing 4
|
||||
, TermMatch "full_name" "app/views/application/_auth_header.rb" Nothing 1
|
||||
, TermMatch "full_name" "app/mailers/user_mailer.rb" Nothing 1
|
||||
, TermMatch "full_name" "spec/models/user_spec.rb" Nothing 10
|
||||
]
|
||||
|
||||
let matches =
|
||||
[ TermMatch "full_name" "app/models/user.rb" Nothing 4
|
||||
, TermMatch "full_name" "app/views/application/_auth_header.rb" Nothing 1
|
||||
, TermMatch "full_name" "app/mailers/user_mailer.rb" Nothing 1
|
||||
, TermMatch "full_name" "spec/models/user_spec.rb" Nothing 10
|
||||
]
|
||||
removalLikelihood' matches `shouldBe` Low
|
||||
|
||||
it "weighs only-occurs-once methods as high likelihood" $ do
|
||||
let matches = [ TermMatch "obscure_method" "app/models/user.rb" Nothing 1 ]
|
||||
|
||||
let matches = [TermMatch "obscure_method" "app/models/user.rb" Nothing 1]
|
||||
removalLikelihood' matches `shouldBe` High
|
||||
|
||||
it "weighs methods that seem to only be tested and never used as high likelihood" $ do
|
||||
let matches = [ TermMatch "obscure_method" "app/models/user.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "spec/models/user_spec.rb" Nothing 5
|
||||
]
|
||||
|
||||
let matches =
|
||||
[ TermMatch "obscure_method" "app/models/user.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "spec/models/user_spec.rb" Nothing 5
|
||||
]
|
||||
removalLikelihood' matches `shouldBe` High
|
||||
|
||||
it "weighs methods that seem to only be tested and used in one other area as medium likelihood" $ do
|
||||
let matches = [ TermMatch "obscure_method" "app/models/user.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "app/controllers/user_controller.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "spec/models/user_spec.rb" Nothing 5
|
||||
, TermMatch "obscure_method" "spec/controllers/user_controller_spec.rb" Nothing 5
|
||||
]
|
||||
|
||||
it
|
||||
"weighs methods that seem to only be tested and used in one other area as medium likelihood" $ do
|
||||
let matches =
|
||||
[ TermMatch "obscure_method" "app/models/user.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "app/controllers/user_controller.rb" Nothing 1
|
||||
, TermMatch "obscure_method" "spec/models/user_spec.rb" Nothing 5
|
||||
, TermMatch
|
||||
"obscure_method"
|
||||
"spec/controllers/user_controller_spec.rb"
|
||||
Nothing
|
||||
5
|
||||
]
|
||||
removalLikelihood' matches `shouldBe` Medium
|
||||
|
||||
it "doesn't mis-categorize allowed terms from different languages" $ do
|
||||
let matches = [ TermMatch "t" "web/models/foo.ex" Nothing 1 ]
|
||||
|
||||
let matches = [TermMatch "t" "web/models/foo.ex" Nothing 1]
|
||||
removalLikelihood' matches `shouldBe` High
|
||||
|
||||
removalLikelihood' :: [TermMatch] -> RemovalLikelihood
|
||||
removalLikelihood' =
|
||||
rLikelihood . trRemoval . calculateLikelihood config . resultsFromMatches
|
||||
removalLikelihood' = rLikelihood . trRemoval . calculateLikelihood config . resultsFromMatches
|
||||
where
|
||||
(Right config) = loadConfig
|
||||
|
@ -1,64 +1,91 @@
|
||||
module Unused.ParserSpec where
|
||||
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Test.Hspec
|
||||
import Unused.Parser
|
||||
import Unused.ResultsClassifier
|
||||
import Unused.TermSearch
|
||||
import Unused.Types
|
||||
import Test.Hspec
|
||||
import Unused.Parser
|
||||
import Unused.ResultsClassifier
|
||||
import Unused.TermSearch
|
||||
import Unused.Types
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "parseResults" $ do
|
||||
it "parses from the correct format" $ do
|
||||
let r1Matches = [ TermMatch "method_name" "app/path/foo.rb" Nothing 1
|
||||
, TermMatch "method_name" "app/path/other.rb" Nothing 5
|
||||
, TermMatch "method_name" "spec/path/foo_spec.rb" Nothing 10
|
||||
]
|
||||
let r1Results = TermResults "method_name" ["method_name"] r1Matches (Occurrences 1 10) (Occurrences 2 6) (Occurrences 3 16) (Removal Low "used frequently") Nothing
|
||||
|
||||
let r2Matches = [ TermMatch "other" "app/path/other.rb" Nothing 1 ]
|
||||
let r2Results = TermResults "other" ["other"] r2Matches (Occurrences 0 0) (Occurrences 1 1) (Occurrences 1 1) (Removal High "occurs once") Nothing
|
||||
|
||||
let r1Matches =
|
||||
[ TermMatch "method_name" "app/path/foo.rb" Nothing 1
|
||||
, TermMatch "method_name" "app/path/other.rb" Nothing 5
|
||||
, TermMatch "method_name" "spec/path/foo_spec.rb" Nothing 10
|
||||
]
|
||||
let r1Results =
|
||||
TermResults
|
||||
"method_name"
|
||||
["method_name"]
|
||||
r1Matches
|
||||
(Occurrences 1 10)
|
||||
(Occurrences 2 6)
|
||||
(Occurrences 3 16)
|
||||
(Removal Low "used frequently")
|
||||
Nothing
|
||||
let r2Matches = [TermMatch "other" "app/path/other.rb" Nothing 1]
|
||||
let r2Results =
|
||||
TermResults
|
||||
"other"
|
||||
["other"]
|
||||
r2Matches
|
||||
(Occurrences 0 0)
|
||||
(Occurrences 1 1)
|
||||
(Occurrences 1 1)
|
||||
(Removal High "occurs once")
|
||||
Nothing
|
||||
let (Right config) = loadConfig
|
||||
|
||||
let result = parseResults config $ SearchResults $ r1Matches ++ r2Matches
|
||||
|
||||
result `shouldBe`
|
||||
Map.fromList [ ("method_name", r1Results), ("other", r2Results) ]
|
||||
|
||||
result `shouldBe` Map.fromList [("method_name", r1Results), ("other", r2Results)]
|
||||
it "parses when no config is provided" $ do
|
||||
let r1Matches = [ TermMatch "method_name" "app/path/foo.rb" Nothing 1
|
||||
, TermMatch "method_name" "app/path/other.rb" Nothing 5
|
||||
, TermMatch "method_name" "spec/path/foo_spec.rb" Nothing 10
|
||||
]
|
||||
let r1Results = TermResults "method_name" ["method_name"] r1Matches (Occurrences 1 10) (Occurrences 2 6) (Occurrences 3 16) (Removal Low "used frequently") Nothing
|
||||
|
||||
let r1Matches =
|
||||
[ TermMatch "method_name" "app/path/foo.rb" Nothing 1
|
||||
, TermMatch "method_name" "app/path/other.rb" Nothing 5
|
||||
, TermMatch "method_name" "spec/path/foo_spec.rb" Nothing 10
|
||||
]
|
||||
let r1Results =
|
||||
TermResults
|
||||
"method_name"
|
||||
["method_name"]
|
||||
r1Matches
|
||||
(Occurrences 1 10)
|
||||
(Occurrences 2 6)
|
||||
(Occurrences 3 16)
|
||||
(Removal Low "used frequently")
|
||||
Nothing
|
||||
let result = parseResults [] $ SearchResults r1Matches
|
||||
|
||||
result `shouldBe`
|
||||
Map.fromList [ ("method_name", r1Results) ]
|
||||
|
||||
result `shouldBe` Map.fromList [("method_name", r1Results)]
|
||||
it "handles aliases correctly" $ do
|
||||
let r1Matches = [ TermMatch "admin?" "app/path/user.rb" Nothing 3 ]
|
||||
|
||||
let r2Matches = [ TermMatch "admin?" "spec/models/user_spec.rb" (Just "be_admin") 2
|
||||
, TermMatch "admin?" "spec/features/user_promoted_to_admin_spec.rb" (Just "be_admin") 2
|
||||
]
|
||||
|
||||
|
||||
let r1Matches = [TermMatch "admin?" "app/path/user.rb" Nothing 3]
|
||||
let r2Matches =
|
||||
[ TermMatch "admin?" "spec/models/user_spec.rb" (Just "be_admin") 2
|
||||
, TermMatch
|
||||
"admin?"
|
||||
"spec/features/user_promoted_to_admin_spec.rb"
|
||||
(Just "be_admin")
|
||||
2
|
||||
]
|
||||
let (Right config) = loadConfig
|
||||
let searchResults = r1Matches ++ r2Matches
|
||||
|
||||
let result = parseResults config $ SearchResults searchResults
|
||||
|
||||
let results = TermResults "admin?" ["admin?", "be_admin"] searchResults (Occurrences 2 4) (Occurrences 1 3) (Occurrences 3 7) (Removal Low "used frequently") Nothing
|
||||
result `shouldBe`
|
||||
Map.fromList [ ("admin?|be_admin", results) ]
|
||||
|
||||
let results =
|
||||
TermResults
|
||||
"admin?"
|
||||
["admin?", "be_admin"]
|
||||
searchResults
|
||||
(Occurrences 2 4)
|
||||
(Occurrences 1 3)
|
||||
(Occurrences 3 7)
|
||||
(Removal Low "used frequently")
|
||||
Nothing
|
||||
result `shouldBe` Map.fromList [("admin?|be_admin", results)]
|
||||
it "handles empty input" $ do
|
||||
let (Right config) = loadConfig
|
||||
let result = parseResults config $ SearchResults []
|
||||
|
@ -8,16 +8,15 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "translate" $ do
|
||||
it "replaces the text without transforms" $
|
||||
translate' "foo_{}" "bar" `shouldBe` "foo_bar"
|
||||
|
||||
it "replaces the text without transforms" $ translate' "foo_{}" "bar" `shouldBe` "foo_bar"
|
||||
it "handles text transformations" $ do
|
||||
translate' "{camelcase}Validator" "proper_email" `shouldBe` "ProperEmailValidator"
|
||||
translate' "{snakecase}" "ProperEmail" `shouldBe` "proper_email"
|
||||
translate' "{camelcase}Validator" "AlreadyCamelcase" `shouldBe` "AlreadyCamelcaseValidator"
|
||||
|
||||
translate' "{camelcase}Validator" "AlreadyCamelcase" `shouldBe`
|
||||
"AlreadyCamelcaseValidator"
|
||||
it "handles unknown transformations" $
|
||||
translate' "{unknown}Validator" "proper_email" `shouldBe` "proper_email"
|
||||
|
||||
|
@ -7,134 +7,148 @@ import Data.List (find)
|
||||
import Test.Hspec
|
||||
import Unused.ResponseFilter
|
||||
import Unused.ResultsClassifier
|
||||
import Unused.Types (TermMatch(..), TermResults, resultsFromMatches)
|
||||
import Unused.Types
|
||||
(TermMatch(..), TermResults, resultsFromMatches)
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "railsAutoLowLikelihood" $ do
|
||||
it "allows controllers" $ do
|
||||
let match = TermMatch "ApplicationController" "app/controllers/application_controller.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows helpers" $ do
|
||||
let match = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows migrations" $ do
|
||||
let match = TermMatch "CreateUsers" "db/migrate/20160101120000_create_users.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "disallows service objects" $ do
|
||||
let match = TermMatch "CreatePostWithNotifications" "app/services/create_post_with_notifications.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "disallows methods" $ do
|
||||
let match = TermMatch "my_method" "app/services/create_post_with_notifications.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "disallows models that occur in migrations" $ do
|
||||
let model = TermMatch "User" "app/models/user.rb" Nothing 1
|
||||
let migration = TermMatch "User" "db/migrate/20160101120000_create_users.rb" Nothing 1
|
||||
let result = resultsFromMatches [model, migration]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "allows matches intermixed with other results" $ do
|
||||
let appToken = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" Nothing 1
|
||||
let testToken = TermMatch "ApplicationHelper" "spec/helpers/application_helper_spec.rb" Nothing 10
|
||||
let result = resultsFromMatches [appToken, testToken]
|
||||
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
describe "elixirAutoLowLikelihood" $ do
|
||||
it "disallows controllers" $ do
|
||||
let match = TermMatch "PageController" "web/controllers/page_controller.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "allows views" $ do
|
||||
let match = TermMatch "PageView" "web/views/page_view.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows migrations" $ do
|
||||
let match = TermMatch "CreateUsers" "priv/repo/migrations/20160101120000_create_users.exs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows tests" $ do
|
||||
let match = TermMatch "UserTest" "test/models/user_test.exs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows Mixfile" $ do
|
||||
let match = TermMatch "Mixfile" "mix.exs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows __using__" $ do
|
||||
let match = TermMatch "__using__" "web/web.ex" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "disallows service modules" $ do
|
||||
let match = TermMatch "CreatePostWithNotifications" "web/services/create_post_with_notifications.ex" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "disallows functions" $ do
|
||||
let match = TermMatch "my_function" "web/services/create_post_with_notifications.ex" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
|
||||
it "allows matches intermixed with other results" $ do
|
||||
let appToken = TermMatch "UserView" "web/views/user_view.ex" Nothing 1
|
||||
let testToken = TermMatch "UserView" "test/views/user_view_test.exs" Nothing 10
|
||||
let result = resultsFromMatches [appToken, testToken]
|
||||
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
describe "haskellAutoLowLikelihood" $ do
|
||||
it "allows instance" $ do
|
||||
let match = TermMatch "instance" "src/Lib/Types.hs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
haskellAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
it "allows items in the *.cabal file" $ do
|
||||
let match = TermMatch "Lib.SomethingSpec" "lib.cabal" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
|
||||
haskellAutoLowLikelihood result `shouldBe` True
|
||||
|
||||
describe "autoLowLikelihood" $
|
||||
it "doesn't qualify as low when no matchers are present in a language config" $ do
|
||||
let match = TermMatch "AwesomeThing" "app/foo/awesome_thing.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
let languageConfig = LanguageConfiguration "Bad" [] [LowLikelihoodMatch "Match with empty matchers" [] False] []
|
||||
|
||||
autoLowLikelihood languageConfig result `shouldBe` False
|
||||
spec =
|
||||
parallel $ do
|
||||
describe "railsAutoLowLikelihood" $ do
|
||||
it "allows controllers" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"ApplicationController"
|
||||
"app/controllers/application_controller.rb"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
it "allows helpers" $ do
|
||||
let match =
|
||||
TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
it "allows migrations" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"CreateUsers"
|
||||
"db/migrate/20160101120000_create_users.rb"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
it "disallows service objects" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"CreatePostWithNotifications"
|
||||
"app/services/create_post_with_notifications.rb"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
it "disallows methods" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"my_method"
|
||||
"app/services/create_post_with_notifications.rb"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
it "disallows models that occur in migrations" $ do
|
||||
let model = TermMatch "User" "app/models/user.rb" Nothing 1
|
||||
let migration =
|
||||
TermMatch "User" "db/migrate/20160101120000_create_users.rb" Nothing 1
|
||||
let result = resultsFromMatches [model, migration]
|
||||
railsAutoLowLikelihood result `shouldBe` False
|
||||
it "allows matches intermixed with other results" $ do
|
||||
let appToken =
|
||||
TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" Nothing 1
|
||||
let testToken =
|
||||
TermMatch
|
||||
"ApplicationHelper"
|
||||
"spec/helpers/application_helper_spec.rb"
|
||||
Nothing
|
||||
10
|
||||
let result = resultsFromMatches [appToken, testToken]
|
||||
railsAutoLowLikelihood result `shouldBe` True
|
||||
describe "elixirAutoLowLikelihood" $ do
|
||||
it "disallows controllers" $ do
|
||||
let match =
|
||||
TermMatch "PageController" "web/controllers/page_controller.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
it "allows views" $ do
|
||||
let match = TermMatch "PageView" "web/views/page_view.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
it "allows migrations" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"CreateUsers"
|
||||
"priv/repo/migrations/20160101120000_create_users.exs"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
it "allows tests" $ do
|
||||
let match = TermMatch "UserTest" "test/models/user_test.exs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
it "allows Mixfile" $ do
|
||||
let match = TermMatch "Mixfile" "mix.exs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
it "allows __using__" $ do
|
||||
let match = TermMatch "__using__" "web/web.ex" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
it "disallows service modules" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"CreatePostWithNotifications"
|
||||
"web/services/create_post_with_notifications.ex"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
it "disallows functions" $ do
|
||||
let match =
|
||||
TermMatch
|
||||
"my_function"
|
||||
"web/services/create_post_with_notifications.ex"
|
||||
Nothing
|
||||
1
|
||||
let result = resultsFromMatches [match]
|
||||
elixirAutoLowLikelihood result `shouldBe` False
|
||||
it "allows matches intermixed with other results" $ do
|
||||
let appToken = TermMatch "UserView" "web/views/user_view.ex" Nothing 1
|
||||
let testToken = TermMatch "UserView" "test/views/user_view_test.exs" Nothing 10
|
||||
let result = resultsFromMatches [appToken, testToken]
|
||||
elixirAutoLowLikelihood result `shouldBe` True
|
||||
describe "haskellAutoLowLikelihood" $ do
|
||||
it "allows instance" $ do
|
||||
let match = TermMatch "instance" "src/Lib/Types.hs" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
haskellAutoLowLikelihood result `shouldBe` True
|
||||
it "allows items in the *.cabal file" $ do
|
||||
let match = TermMatch "Lib.SomethingSpec" "lib.cabal" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
haskellAutoLowLikelihood result `shouldBe` True
|
||||
describe "autoLowLikelihood" $
|
||||
it "doesn't qualify as low when no matchers are present in a language config" $ do
|
||||
let match = TermMatch "AwesomeThing" "app/foo/awesome_thing.rb" Nothing 1
|
||||
let result = resultsFromMatches [match]
|
||||
let languageConfig =
|
||||
LanguageConfiguration
|
||||
"Bad"
|
||||
[]
|
||||
[LowLikelihoodMatch "Match with empty matchers" [] False]
|
||||
[]
|
||||
autoLowLikelihood languageConfig result `shouldBe` False
|
||||
|
||||
configByName :: String -> LanguageConfiguration
|
||||
configByName s = config'
|
||||
|
@ -12,28 +12,48 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "commandLineOptions" $ do
|
||||
it "does not use regular expressions when the term contains non-word characters" $ do
|
||||
commandLineOptions Ag "can_do_things?" `shouldBe` ["can_do_things?", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "no_way!" `shouldBe` ["no_way!", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "[]=" `shouldBe` ["[]=", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "window.globalOverride" `shouldBe` ["window.globalOverride", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
|
||||
commandLineOptions Rg "can_do_things?" `shouldBe` ["can_do_things?", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "no_way!" `shouldBe` ["no_way!", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "[]=" `shouldBe` ["[]=", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "window.globalOverride" `shouldBe` ["window.globalOverride", ".", "-F", "-c", "-j", "1"]
|
||||
|
||||
it "uses regular expression match with surrounding non-word matches for accuracy" $ do
|
||||
commandLineOptions Ag "awesome_method" `shouldBe` ["(\\W|^)awesome_method(\\W|$)", ".", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Rg "awesome_method" `shouldBe` ["(\\W|^)awesome_method(\\W|$)", ".", "-c", "-j", "1"]
|
||||
|
||||
describe "parseSearchResult" $ do
|
||||
it "parses normal results from `ag` to a TermMatch" $ do
|
||||
parseSearchResult Ag (OriginalTerm "method_name") ":app/models/foo.rb:123" `shouldBe` (Just $ TermMatch "method_name" "app/models/foo.rb" Nothing 123)
|
||||
parseSearchResult Rg (OriginalTerm "method_name") "app/models/foo.rb:123" `shouldBe` (Just $ TermMatch "method_name" "app/models/foo.rb" Nothing 123)
|
||||
|
||||
it "returns Nothing when it cannot parse" $ do
|
||||
parseSearchResult Ag (OriginalTerm "method_name") "" `shouldBe` Nothing
|
||||
parseSearchResult Rg (OriginalTerm "method_name") "" `shouldBe` Nothing
|
||||
spec =
|
||||
parallel $ do
|
||||
describe "commandLineOptions" $ do
|
||||
it "does not use regular expressions when the term contains non-word characters" $ do
|
||||
commandLineOptions Ag "can_do_things?" `shouldBe`
|
||||
["can_do_things?", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "no_way!" `shouldBe`
|
||||
["no_way!", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "[]=" `shouldBe`
|
||||
["[]=", ".", "-Q", "-c", "--ackmate", "--ignore-dir", "tmp/unused"]
|
||||
commandLineOptions Ag "window.globalOverride" `shouldBe`
|
||||
[ "window.globalOverride"
|
||||
, "."
|
||||
, "-Q"
|
||||
, "-c"
|
||||
, "--ackmate"
|
||||
, "--ignore-dir"
|
||||
, "tmp/unused"
|
||||
]
|
||||
commandLineOptions Rg "can_do_things?" `shouldBe`
|
||||
["can_do_things?", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "no_way!" `shouldBe` ["no_way!", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "[]=" `shouldBe` ["[]=", ".", "-F", "-c", "-j", "1"]
|
||||
commandLineOptions Rg "window.globalOverride" `shouldBe`
|
||||
["window.globalOverride", ".", "-F", "-c", "-j", "1"]
|
||||
it "uses regular expression match with surrounding non-word matches for accuracy" $ do
|
||||
commandLineOptions Ag "awesome_method" `shouldBe`
|
||||
[ "(\\W|^)awesome_method(\\W|$)"
|
||||
, "."
|
||||
, "-c"
|
||||
, "--ackmate"
|
||||
, "--ignore-dir"
|
||||
, "tmp/unused"
|
||||
]
|
||||
commandLineOptions Rg "awesome_method" `shouldBe`
|
||||
["(\\W|^)awesome_method(\\W|$)", ".", "-c", "-j", "1"]
|
||||
describe "parseSearchResult" $ do
|
||||
it "parses normal results from `ag` to a TermMatch" $ do
|
||||
parseSearchResult Ag (OriginalTerm "method_name") ":app/models/foo.rb:123" `shouldBe`
|
||||
(Just $ TermMatch "method_name" "app/models/foo.rb" Nothing 123)
|
||||
parseSearchResult Rg (OriginalTerm "method_name") "app/models/foo.rb:123" `shouldBe`
|
||||
(Just $ TermMatch "method_name" "app/models/foo.rb" Nothing 123)
|
||||
it "returns Nothing when it cannot parse" $ do
|
||||
parseSearchResult Ag (OriginalTerm "method_name") "" `shouldBe` Nothing
|
||||
parseSearchResult Rg (OriginalTerm "method_name") "" `shouldBe` Nothing
|
||||
|
@ -7,12 +7,29 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $
|
||||
spec =
|
||||
parallel $
|
||||
describe "resultsFromMatches" $
|
||||
it "batches files together to calculate information" $ do
|
||||
let matches = [ TermMatch "ApplicationController" "app/controllers/application_controller.rb" Nothing 1
|
||||
, TermMatch "ApplicationController" "spec/controllers/application_controller_spec.rb" Nothing 10
|
||||
]
|
||||
|
||||
resultsFromMatches matches `shouldBe`
|
||||
TermResults "ApplicationController" ["ApplicationController"] matches (Occurrences 1 10) (Occurrences 1 1) (Occurrences 2 11) (Removal NotCalculated "Likelihood not calculated") Nothing
|
||||
it "batches files together to calculate information" $ do
|
||||
let matches =
|
||||
[ TermMatch
|
||||
"ApplicationController"
|
||||
"app/controllers/application_controller.rb"
|
||||
Nothing
|
||||
1
|
||||
, TermMatch
|
||||
"ApplicationController"
|
||||
"spec/controllers/application_controller_spec.rb"
|
||||
Nothing
|
||||
10
|
||||
]
|
||||
resultsFromMatches matches `shouldBe`
|
||||
TermResults
|
||||
"ApplicationController"
|
||||
["ApplicationController"]
|
||||
matches
|
||||
(Occurrences 1 10)
|
||||
(Occurrences 1 1)
|
||||
(Occurrences 2 11)
|
||||
(Removal NotCalculated "Likelihood not calculated")
|
||||
Nothing
|
||||
|
@ -15,22 +15,22 @@ main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "groupBy" $ do
|
||||
it "groups by the result of a function" $ do
|
||||
let numbers = [1..10] :: [Int]
|
||||
|
||||
groupBy ((0 ==) . flip mod 2) numbers `shouldBe` [(False, [1, 3, 5, 7, 9]), (True, [2, 4, 6, 8, 10])]
|
||||
|
||||
it "handles records" $ do
|
||||
let people = [Person "Jane" 10, Person "Jane" 20, Person "John" 20]
|
||||
|
||||
groupBy pName people `shouldBe` [("Jane", [Person "Jane" 10, Person "Jane" 20]), ("John", [Person "John" 20])]
|
||||
groupBy pAge people `shouldBe` [(10, [Person "Jane" 10]), (20, [Person "Jane" 20, Person "John" 20])]
|
||||
|
||||
describe "stringToInt" $
|
||||
it "converts a String value to Maybe Int" $ do
|
||||
stringToInt "12345678" `shouldBe` Just 12345678
|
||||
stringToInt "0" `shouldBe` Just 0
|
||||
stringToInt "10591" `shouldBe` Just 10591
|
||||
stringToInt "bad" `shouldBe` Nothing
|
||||
spec =
|
||||
parallel $ do
|
||||
describe "groupBy" $ do
|
||||
it "groups by the result of a function" $ do
|
||||
let numbers = [1 .. 10] :: [Int]
|
||||
groupBy ((0 ==) . flip mod 2) numbers `shouldBe`
|
||||
[(False, [1, 3, 5, 7, 9]), (True, [2, 4, 6, 8, 10])]
|
||||
it "handles records" $ do
|
||||
let people = [Person "Jane" 10, Person "Jane" 20, Person "John" 20]
|
||||
groupBy pName people `shouldBe`
|
||||
[("Jane", [Person "Jane" 10, Person "Jane" 20]), ("John", [Person "John" 20])]
|
||||
groupBy pAge people `shouldBe`
|
||||
[(10, [Person "Jane" 10]), (20, [Person "Jane" 20, Person "John" 20])]
|
||||
describe "stringToInt" $
|
||||
it "converts a String value to Maybe Int" $ do
|
||||
stringToInt "12345678" `shouldBe` Just 12345678
|
||||
stringToInt "0" `shouldBe` Just 0
|
||||
stringToInt "10591" `shouldBe` Just 10591
|
||||
stringToInt "bad" `shouldBe` Nothing
|
||||
|
Loading…
Reference in New Issue
Block a user