Introduce internal yaml configuration of auto low likelihood match handling

Why?
====

Handling low likelihood configuration was previously a huge pain,
because the syntax in Haskell was fairly terse. This introduces a yaml
format internally that ships with the app covering basic cases for
Rails, Phoenix, and Haskell. I could imagine getting baselines in here
for other languages and frameworks (especially ones I've used and am
comfortable with) as a baseline.

This also paves the way for searching for user-provided additions and
loading those configurations in addition to what we have here.
This commit is contained in:
Joshua Clayton 2016-05-18 11:11:49 -04:00
parent 6c9912fa29
commit 307dd2030f
13 changed files with 307 additions and 73 deletions

View File

@ -5,6 +5,7 @@ import System.IO (hSetBuffering, BufferMode(NoBuffering), stdout)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Unused.Parser (parseLines) import Unused.Parser (parseLines)
import Unused.Types (ParseResponse, RemovalLikelihood(..)) import Unused.Types (ParseResponse, RemovalLikelihood(..))
import Unused.ResultsClassifier
import Unused.ResponseFilter (withOneOccurrence, withLikelihoods, ignoringPaths) import Unused.ResponseFilter (withOneOccurrence, withLikelihoods, ignoringPaths)
import Unused.Grouping (CurrentGrouping(..), groupedResponses) import Unused.Grouping (CurrentGrouping(..), groupedResponses)
import Unused.CLI (SearchRunner(..), withoutCursor, renderHeader, executeSearch, printParseError, printSearchResults, resetScreen, withInterruptHandler) import Unused.CLI (SearchRunner(..), withoutCursor, renderHeader, executeSearch, printParseError, printSearchResults, resetScreen, withInterruptHandler)
@ -39,8 +40,11 @@ run options = withoutCursor $ do
terms <- pure . lines =<< getContents terms <- pure . lines =<< getContents
renderHeader terms renderHeader terms
languageConfig <- loadLanguageConfig
results <- withCache options $ unlines <$> executeSearch (oSearchRunner options) terms results <- withCache options $ unlines <$> executeSearch (oSearchRunner options) terms
let response = parseLines results
let response = parseLines languageConfig results
resetScreen resetScreen
@ -49,6 +53,9 @@ run options = withoutCursor $ do
return () return ()
loadLanguageConfig :: IO [LanguageConfiguration]
loadLanguageConfig = either (const []) id <$> loadConfig
withCache :: Options -> IO String -> IO String withCache :: Options -> IO String -> IO String
withCache Options{ oWithCache = True } = cached withCache Options{ oWithCache = True } = cached
withCache Options{ oWithCache = False } = id withCache Options{ oWithCache = False } = id

43
data/config.yml Normal file
View File

@ -0,0 +1,43 @@
- name: Rails
allowedTerms: []
autoLowLikelihood:
- name: Migration
pathStartsWith: db/migrate/
classOrModule: true
appOccurrences: 1
- name: Controller
pathStartsWith: app/controllers
termEndsWith: Controller
classOrModule: true
- name: Helper
pathStartsWith: app/helpers
termEndsWith: Helper
classOrModule: true
- name: Phoenix
allowedTerms:
- Mixfile
- __using__
autoLowLikelihood:
- name: Migration
pathStartsWith: priv/repo/migrations
classOrModule: true
- name: View
pathStartsWith: web/views/
termEndsWith: View
classOrModule: true
- name: Test
pathStartsWith: test/
termEndsWith: Test
classOrModule: true
- name: Haskell
allowedTerms:
- instance
- spec
autoLowLikelihood:
- name: Spec
pathStartsWith: test/
termEndsWith: Spec
classOrModule: true
- name: Cabalfile
pathEndsWith: .cabal
appOccurrences: 1

View File

@ -1,26 +1,40 @@
module Unused.LikelihoodCalculator module Unused.LikelihoodCalculator
( calculateLikelihood ( calculateLikelihood
, LanguageConfiguration
) where ) where
import Data.Maybe (isJust)
import Data.List (find, intercalate)
import Unused.ResultsClassifier
import Unused.Types import Unused.Types
import Unused.ResponseFilter (railsSingleOkay, elixirSingleOkay, haskellSingleOkay) import Unused.ResponseFilter (autoLowLikelihood)
calculateLikelihood :: TermResults -> TermResults calculateLikelihood :: [LanguageConfiguration] -> TermResults -> TermResults
calculateLikelihood r = calculateLikelihood lcs r =
r { trRemoval = uncurry Removal newLikelihood } r { trRemoval = uncurry Removal newLikelihood }
where where
baseScore = totalOccurrenceCount r baseScore = totalOccurrenceCount r
totalScore = baseScore totalScore = baseScore
newLikelihood newLikelihood
| railsSingleOkay r = (Low, "a class, module, or migration that often occurs in only one file") | isJust firstAutoLowLikelihood = (Low, autoLowLikelihoodMessage)
| elixirSingleOkay r = (Low, "a class, module, or migration that often occurs in only one file")
| haskellSingleOkay r = (Low, "a module, function, or special case that often occurs in only one file")
| singleNonTestUsage r && testsExist r = (High, "only the definition and corresponding tests exist") | singleNonTestUsage r && testsExist r = (High, "only the definition and corresponding tests exist")
| doubleNonTestUsage r && testsExist r = (Medium, "only the definition and one other use, along with tests, exists") | doubleNonTestUsage r && testsExist r = (Medium, "only the definition and one other use, along with tests, exists")
| totalScore < 2 = (High, "used once") | totalScore < 2 = (High, "used once")
| totalScore < 6 = (Medium, "used semi-frequently") | totalScore < 6 = (Medium, "used semi-frequently")
| totalScore >= 6 = (Low, "used frequently") | totalScore >= 6 = (Low, "used frequently")
| otherwise = (Unknown, "could not determine likelihood") | otherwise = (Unknown, "could not determine likelihood")
firstAutoLowLikelihood = find (`autoLowLikelihood` r) lcs
autoLowLikelihoodMessage =
case firstAutoLowLikelihood of
Nothing -> ""
Just lang -> languageConfirmationMessage lang
languageConfirmationMessage :: LanguageConfiguration -> String
languageConfirmationMessage lc =
langFramework ++ ": allowed term or " ++ lowLikelihoodNames
where
langFramework = lcName lc
lowLikelihoodNames = intercalate ", " $ map smName $ lcAutoLowLikelihood lc
singleNonTestUsage :: TermResults -> Bool singleNonTestUsage :: TermResults -> Bool
singleNonTestUsage = (1 ==) . oOccurrences . trAppOccurrences singleNonTestUsage = (1 ==) . oOccurrences . trAppOccurrences

View File

@ -10,10 +10,10 @@ import Unused.Types (ParseResponse, TermMatch, resultsFromMatches, tmTerm)
import Unused.LikelihoodCalculator import Unused.LikelihoodCalculator
import Unused.Parser.Internal import Unused.Parser.Internal
parseLines :: String -> ParseResponse parseLines :: [LanguageConfiguration] -> String -> ParseResponse
parseLines = parseLines lcs =
responseFromParse . parse parseTermMatches "matches" responseFromParse lcs . parse parseTermMatches "matches"
responseFromParse :: Either ParseError [TermMatch] -> ParseResponse responseFromParse :: [LanguageConfiguration] -> Either ParseError [TermMatch] -> ParseResponse
responseFromParse = responseFromParse lcs =
fmap $ Map.fromList . map (second $ calculateLikelihood . resultsFromMatches) . groupBy tmTerm fmap $ Map.fromList . map (second $ calculateLikelihood lcs . resultsFromMatches) . groupBy tmTerm

View File

@ -4,9 +4,7 @@ module Unused.ResponseFilter
, oneOccurence , oneOccurence
, ignoringPaths , ignoringPaths
, isClassOrModule , isClassOrModule
, railsSingleOkay , autoLowLikelihood
, elixirSingleOkay
, haskellSingleOkay
, updateMatches , updateMatches
) where ) where
@ -14,6 +12,7 @@ import qualified Data.Map.Strict as Map
import Data.List (isInfixOf) import Data.List (isInfixOf)
import Unused.Regex (matchRegex) import Unused.Regex (matchRegex)
import Unused.Types import Unused.Types
import Unused.ResultsClassifier
withOneOccurrence :: ParseResponse -> ParseResponse withOneOccurrence :: ParseResponse -> ParseResponse
withOneOccurrence = applyFilter (const oneOccurence) withOneOccurrence = applyFilter (const oneOccurence)
@ -38,33 +37,33 @@ includesLikelihood l = (`elem` l) . rLikelihood . trRemoval
isClassOrModule :: TermResults -> Bool isClassOrModule :: TermResults -> Bool
isClassOrModule = matchRegex "^[A-Z]" . trTerm isClassOrModule = matchRegex "^[A-Z]" . trTerm
railsSingleOkay :: TermResults -> Bool autoLowLikelihood :: LanguageConfiguration -> TermResults -> Bool
railsSingleOkay r = autoLowLikelihood l r =
isClassOrModule r && (controller || helper || migration) isAllowedTerm r allowedTerms || or anySinglesOkay
where where
controller = any (matchRegex "^app/controllers/") paths && matchRegex "Controller$" (trTerm r) allowedTerms = lcAllowedTerms l
helper = any (matchRegex "^app/helpers/") paths && matchRegex "Helper$" (trTerm r) anySinglesOkay = map (\sm -> classOrModule sm r && matchesToBool (smMatchers sm)) singles
migration = any (matchRegex "^db/migrate/") paths singles = lcAutoLowLikelihood l
paths = tmPath <$> trMatches r classOrModule = classOrModuleFunction . smClassOrModule
elixirSingleOkay :: TermResults -> Bool matchesToBool :: [Matcher] -> Bool
elixirSingleOkay r = matchesToBool = all (`matcherToBool` r)
isAllowedTerm r allowedTerms ||
isClassOrModule r && (view || test || migration)
where
migration = any (matchRegex "^priv/repo/migrations/") paths
view = any (matchRegex "^web/views/") paths && matchRegex "View$" (trTerm r)
test = any (matchRegex "^test/") paths && matchRegex "Test$" (trTerm r)
allowedTerms = ["Mixfile", "__using__"]
paths = tmPath <$> trMatches r
haskellSingleOkay :: TermResults -> Bool classOrModuleFunction :: Bool -> TermResults -> Bool
haskellSingleOkay r = classOrModuleFunction True = isClassOrModule
isAllowedTerm r allowedTerms || cabalFile classOrModuleFunction False = const True
where
allowedTerms = ["instance"] matcherToBool :: Matcher -> TermResults -> Bool
cabalFile = any (matchRegex "^*.cabal$") paths matcherToBool (Path p v) = any (positionToRegex p v) . paths
paths = tmPath <$> trMatches r matcherToBool (Term p v) = positionToRegex p v . trTerm
matcherToBool (AppOccurrences i) = (== i) . appOccurrenceCount
positionToRegex :: Position -> (String -> String -> Bool)
positionToRegex StartsWith = \v -> matchRegex ("^" ++ v)
positionToRegex EndsWith = \v -> matchRegex (v ++ "$")
paths :: TermResults -> [String]
paths r = tmPath <$> trMatches r
updateMatches :: ([TermMatch] -> [TermMatch]) -> TermMatchSet -> TermMatchSet updateMatches :: ([TermMatch] -> [TermMatch]) -> TermMatchSet -> TermMatchSet
updateMatches fm = updateMatches fm =

View File

@ -0,0 +1,10 @@
module Unused.ResultsClassifier
( LanguageConfiguration(..)
, LowLikelihoodMatch(..)
, Position(..)
, Matcher(..)
, loadConfig
) where
import Unused.ResultsClassifier.Types
import Unused.ResultsClassifier.Config

View File

@ -0,0 +1,15 @@
module Unused.ResultsClassifier.Config
( loadConfig
) where
import qualified Data.Yaml as Y
import qualified Data.ByteString as BS
import System.FilePath ((</>))
import Paths_unused (getDataFileName)
import Unused.ResultsClassifier.Types (LanguageConfiguration)
loadConfig :: IO (Either String [LanguageConfiguration])
loadConfig = Y.decodeEither <$> readConfig
readConfig :: IO BS.ByteString
readConfig = getDataFileName ("data" </> "config.yml") >>= BS.readFile

View File

@ -0,0 +1,99 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module Unused.ResultsClassifier.Types
( LanguageConfiguration(..)
, LowLikelihoodMatch(..)
, Position(..)
, Matcher(..)
) where
import Control.Monad (mzero)
import qualified Data.Text as T
import qualified Data.Yaml as Y
import qualified Data.List as L
import Data.HashMap.Strict (keys)
import Control.Applicative (Alternative, empty)
import Data.Yaml (FromJSON(..), (.:), (.:?), (.!=))
data LanguageConfiguration = LanguageConfiguration
{ lcName :: String
, lcAllowedTerms :: [String]
, lcAutoLowLikelihood :: [LowLikelihoodMatch]
} deriving Show
data LowLikelihoodMatch = LowLikelihoodMatch
{ smName :: String
, smMatchers :: [Matcher]
, smClassOrModule :: Bool
} deriving Show
data Position = StartsWith | EndsWith deriving Show
data Matcher = Term Position String | Path Position String | AppOccurrences Int deriving Show
instance FromJSON LanguageConfiguration where
parseJSON (Y.Object o) = LanguageConfiguration
<$> o .: "name"
<*> o .: "allowedTerms"
<*> o .: "autoLowLikelihood"
parseJSON _ = mzero
instance FromJSON LowLikelihoodMatch where
parseJSON (Y.Object o) = LowLikelihoodMatch
<$> o .: "name"
<*> parseMatchers o
<*> o .:? "classOrModule" .!= False
parseJSON _ = mzero
data MatchHandler a = MatchHandler
{ mhKeys :: [String]
, mhKeyToMatcher :: T.Text -> Either T.Text (a -> Matcher)
}
intHandler :: MatchHandler Int
intHandler = MatchHandler
{ mhKeys = ["appOccurrences"]
, mhKeyToMatcher = keyToMatcher
}
where
keyToMatcher "appOccurrences" = Right AppOccurrences
keyToMatcher t = Left t
stringHandler :: MatchHandler String
stringHandler = MatchHandler
{ mhKeys = ["pathStartsWith", "pathEndsWith", "termStartsWith", "termEndsWith"]
, mhKeyToMatcher = keyToMatcher
}
where
keyToMatcher "pathStartsWith" = Right $ Path StartsWith
keyToMatcher "pathEndsWith" = Right $ Path EndsWith
keyToMatcher "termStartsWith" = Right $ Term StartsWith
keyToMatcher "termEndsWith" = Right $ Term EndsWith
keyToMatcher t = Left t
parseMatchers :: Y.Object -> Y.Parser [Matcher]
parseMatchers o =
myFold (++) [buildMatcherList o intHandler, buildMatcherList o stringHandler]
where
myFold :: (Foldable t, Monad m) => (a -> a -> a) -> t (m a) -> m a
myFold f = foldl1 (\acc i -> acc >>= (\l -> f l <$> i))
buildMatcherList :: FromJSON a => Y.Object -> MatchHandler a -> Y.Parser [Matcher]
buildMatcherList o mh =
sequenceA $ matcherParserForKey <$> keysToParse
where
matcherParserForKey k = extractMatcher (mhKeyToMatcher mh k) $ mKey k
keysToParse = positionKeysforMatcher o (mhKeys mh)
mKey = (.:?) o
positionKeysforMatcher :: Y.Object -> [String] -> [T.Text]
positionKeysforMatcher o ls = L.intersect (T.pack <$> ls) $ keys o
extractMatcher :: Either T.Text (a -> Matcher) -> Y.Parser (Maybe a) -> Y.Parser Matcher
extractMatcher e p = either displayFailure (convertFoundObjectToMatcher p) e
convertFoundObjectToMatcher :: (Monad m, Alternative m) => m (Maybe a) -> (a -> b) -> m b
convertFoundObjectToMatcher p f = maybe empty (pure . f) =<< p
displayFailure :: T.Text -> a
displayFailure t = error $ "Parse error: '" ++ T.unpack t ++ "' is not a valid key in a singleOnly matcher"

View File

@ -9,6 +9,7 @@ module Unused.Types
, resultsFromMatches , resultsFromMatches
, totalFileCount , totalFileCount
, totalOccurrenceCount , totalOccurrenceCount
, appOccurrenceCount
) where ) where
import Text.Parsec (ParseError) import Text.Parsec (ParseError)
@ -52,6 +53,9 @@ totalFileCount = oFiles . trTotalOccurrences
totalOccurrenceCount :: TermResults -> Int totalOccurrenceCount :: TermResults -> Int
totalOccurrenceCount = oOccurrences . trTotalOccurrences totalOccurrenceCount = oOccurrences . trTotalOccurrences
appOccurrenceCount :: TermResults -> Int
appOccurrenceCount = oOccurrences . trAppOccurrences
resultsFromMatches :: [TermMatch] -> TermResults resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m = resultsFromMatches m =
TermResults TermResults

View File

@ -6,6 +6,7 @@ module Unused.LikelihoodCalculatorSpec
import Test.Hspec import Test.Hspec
import Unused.Types import Unused.Types
import Unused.LikelihoodCalculator import Unused.LikelihoodCalculator
import Unused.ResultsClassifier
main :: IO () main :: IO ()
main = hspec spec main = hspec spec
@ -15,10 +16,10 @@ spec = parallel $
describe "calculateLikelihood" $ do describe "calculateLikelihood" $ do
it "prefers language-specific checks first" $ do it "prefers language-specific checks first" $ do
let railsMatches = [ TermMatch "ApplicationController" "app/controllers/application_controller.rb" 1 ] let railsMatches = [ TermMatch "ApplicationController" "app/controllers/application_controller.rb" 1 ]
removalLikelihood railsMatches `shouldBe` Low removalLikelihood railsMatches `shouldReturn` Low
let elixirMatches = [ TermMatch "AwesomeView" "web/views/awesome_view.ex" 1 ] let elixirMatches = [ TermMatch "AwesomeView" "web/views/awesome_view.ex" 1 ]
removalLikelihood elixirMatches `shouldBe` Low removalLikelihood elixirMatches `shouldReturn` Low
it "weighs widely-used methods as low likelihood" $ do it "weighs widely-used methods as low likelihood" $ do
let matches = [ TermMatch "full_name" "app/models/user.rb" 4 let matches = [ TermMatch "full_name" "app/models/user.rb" 4
@ -27,19 +28,19 @@ spec = parallel $
, TermMatch "full_name" "spec/models/user_spec.rb" 10 , TermMatch "full_name" "spec/models/user_spec.rb" 10
] ]
removalLikelihood matches `shouldBe` Low removalLikelihood matches `shouldReturn` Low
it "weighs only-used-once methods as high likelihood" $ do it "weighs only-used-once methods as high likelihood" $ do
let matches = [ TermMatch "obscure_method" "app/models/user.rb" 1 ] let matches = [ TermMatch "obscure_method" "app/models/user.rb" 1 ]
removalLikelihood matches `shouldBe` High removalLikelihood matches `shouldReturn` High
it "weighs methods that seem to only be tested and never used as high likelihood" $ do 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" 1 let matches = [ TermMatch "obscure_method" "app/models/user.rb" 1
, TermMatch "obscure_method" "spec/models/user_spec.rb" 5 , TermMatch "obscure_method" "spec/models/user_spec.rb" 5
] ]
removalLikelihood matches `shouldBe` High removalLikelihood matches `shouldReturn` High
it "weighs methods that seem to only be tested and used in one other area as medium likelihood" $ do 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" 1 let matches = [ TermMatch "obscure_method" "app/models/user.rb" 1
@ -48,8 +49,9 @@ spec = parallel $
, TermMatch "obscure_method" "spec/controllers/user_controller_spec.rb" 5 , TermMatch "obscure_method" "spec/controllers/user_controller_spec.rb" 5
] ]
removalLikelihood matches `shouldBe` Medium removalLikelihood matches `shouldReturn` Medium
removalLikelihood :: [TermMatch] -> RemovalLikelihood removalLikelihood :: [TermMatch] -> IO RemovalLikelihood
removalLikelihood = removalLikelihood ms = do
rLikelihood . trRemoval . calculateLikelihood . resultsFromMatches (Right config) <- loadConfig
return $ rLikelihood $ trRemoval $ calculateLikelihood config $ resultsFromMatches ms

View File

@ -3,6 +3,7 @@ module Unused.ParserSpec where
import Test.Hspec import Test.Hspec
import Unused.Types import Unused.Types
import Unused.Parser import Unused.Parser
import Unused.ResultsClassifier
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
main :: IO () main :: IO ()
@ -26,11 +27,13 @@ spec = parallel $
let r2Matches = [ TermMatch "other" "app/path/other.rb" 1 ] let r2Matches = [ TermMatch "other" "app/path/other.rb" 1 ]
let r2Results = TermResults "other" r2Matches (Occurrences 0 0) (Occurrences 1 1) (Occurrences 1 1) (Removal High "used once") let r2Results = TermResults "other" r2Matches (Occurrences 0 0) (Occurrences 1 1) (Occurrences 1 1) (Removal High "used once")
let (Right result) = parseLines input (Right config) <- loadConfig
let (Right result) = parseLines config input
result `shouldBe` result `shouldBe`
Map.fromList [ ("method_name", r1Results), ("other", r2Results) ] Map.fromList [ ("method_name", r1Results), ("other", r2Results) ]
it "handles empty input" $ do it "handles empty input" $ do
let (Left result) = parseLines "" (Right config) <- loadConfig
let (Left result) = parseLines config ""
show result `shouldContain` "unexpected end of input" show result `shouldContain` "unexpected end of input"

View File

@ -1,117 +1,145 @@
module Unused.ResponseFilterSpec where module Unused.ResponseFilterSpec
( main
, spec
) where
import Test.Hspec import Test.Hspec
import Unused.Types (TermMatch(..), resultsFromMatches) import Data.List (find)
import Unused.Types (TermMatch(..), TermResults, resultsFromMatches)
import Unused.ResponseFilter import Unused.ResponseFilter
import Unused.ResultsClassifier
main :: IO () main :: IO ()
main = hspec spec main = hspec spec
spec :: Spec spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "railsSingleOkay" $ do describe "railsAutoLowLikelihood" $ do
it "allows controllers" $ do it "allows controllers" $ do
let match = TermMatch "ApplicationController" "app/controllers/application_controller.rb" 1 let match = TermMatch "ApplicationController" "app/controllers/application_controller.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
railsSingleOkay result `shouldBe` True railsAutoLowLikelihood result `shouldReturn` True
it "allows helpers" $ do it "allows helpers" $ do
let match = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" 1 let match = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
railsSingleOkay result `shouldBe` True railsAutoLowLikelihood result `shouldReturn` True
it "allows migrations" $ do it "allows migrations" $ do
let match = TermMatch "CreateUsers" "db/migrate/20160101120000_create_users.rb" 1 let match = TermMatch "CreateUsers" "db/migrate/20160101120000_create_users.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
railsSingleOkay result `shouldBe` True railsAutoLowLikelihood result `shouldReturn` True
it "disallows service objects" $ do it "disallows service objects" $ do
let match = TermMatch "CreatePostWithNotifications" "app/services/create_post_with_notifications.rb" 1 let match = TermMatch "CreatePostWithNotifications" "app/services/create_post_with_notifications.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
railsSingleOkay result `shouldBe` False railsAutoLowLikelihood result `shouldReturn` False
it "disallows methods" $ do it "disallows methods" $ do
let match = TermMatch "my_method" "app/services/create_post_with_notifications.rb" 1 let match = TermMatch "my_method" "app/services/create_post_with_notifications.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
railsSingleOkay result `shouldBe` False railsAutoLowLikelihood result `shouldReturn` False
it "disallows models that occur in migrations" $ do
let model = TermMatch "User" "app/models/user.rb" 1
let migration = TermMatch "User" "db/migrate/20160101120000_create_users.rb" 1
let result = resultsFromMatches [model, migration]
railsAutoLowLikelihood result `shouldReturn` False
it "allows matches intermixed with other results" $ do it "allows matches intermixed with other results" $ do
let appToken = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" 1 let appToken = TermMatch "ApplicationHelper" "app/helpers/application_helper.rb" 1
let testToken = TermMatch "ApplicationHelper" "spec/helpers/application_helper_spec.rb" 10 let testToken = TermMatch "ApplicationHelper" "spec/helpers/application_helper_spec.rb" 10
let result = resultsFromMatches [appToken, testToken] let result = resultsFromMatches [appToken, testToken]
railsSingleOkay result `shouldBe` True railsAutoLowLikelihood result `shouldReturn` True
describe "elixirSingleOkay" $ do describe "elixirAutoLowLikelihood" $ do
it "disallows controllers" $ do it "disallows controllers" $ do
let match = TermMatch "PageController" "web/controllers/page_controller.rb" 1 let match = TermMatch "PageController" "web/controllers/page_controller.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` False elixirAutoLowLikelihood result `shouldReturn` False
it "allows views" $ do it "allows views" $ do
let match = TermMatch "PageView" "web/views/page_view.rb" 1 let match = TermMatch "PageView" "web/views/page_view.rb" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
it "allows migrations" $ do it "allows migrations" $ do
let match = TermMatch "CreateUsers" "priv/repo/migrations/20160101120000_create_users.exs" 1 let match = TermMatch "CreateUsers" "priv/repo/migrations/20160101120000_create_users.exs" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
it "allows tests" $ do it "allows tests" $ do
let match = TermMatch "UserTest" "test/models/user_test.exs" 1 let match = TermMatch "UserTest" "test/models/user_test.exs" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
it "allows Mixfile" $ do it "allows Mixfile" $ do
let match = TermMatch "Mixfile" "mix.exs" 1 let match = TermMatch "Mixfile" "mix.exs" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
it "allows __using__" $ do it "allows __using__" $ do
let match = TermMatch "__using__" "web/web.ex" 1 let match = TermMatch "__using__" "web/web.ex" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
it "disallows service modules" $ do it "disallows service modules" $ do
let match = TermMatch "CreatePostWithNotifications" "web/services/create_post_with_notifications.ex" 1 let match = TermMatch "CreatePostWithNotifications" "web/services/create_post_with_notifications.ex" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` False elixirAutoLowLikelihood result `shouldReturn` False
it "disallows functions" $ do it "disallows functions" $ do
let match = TermMatch "my_function" "web/services/create_post_with_notifications.ex" 1 let match = TermMatch "my_function" "web/services/create_post_with_notifications.ex" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
elixirSingleOkay result `shouldBe` False elixirAutoLowLikelihood result `shouldReturn` False
it "allows matches intermixed with other results" $ do it "allows matches intermixed with other results" $ do
let appToken = TermMatch "UserView" "web/views/user_view.ex" 1 let appToken = TermMatch "UserView" "web/views/user_view.ex" 1
let testToken = TermMatch "UserView" "test/views/user_view_test.exs" 10 let testToken = TermMatch "UserView" "test/views/user_view_test.exs" 10
let result = resultsFromMatches [appToken, testToken] let result = resultsFromMatches [appToken, testToken]
elixirSingleOkay result `shouldBe` True elixirAutoLowLikelihood result `shouldReturn` True
describe "haskellSingleOkay" $ do describe "haskellAutoLowLikelihood" $ do
it "allows instance" $ do it "allows instance" $ do
let match = TermMatch "instance" "src/Lib/Types.hs" 1 let match = TermMatch "instance" "src/Lib/Types.hs" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
haskellSingleOkay result `shouldBe` True haskellAutoLowLikelihood result `shouldReturn` True
it "allows items in the *.cabal file" $ do it "allows items in the *.cabal file" $ do
let match = TermMatch "Lib.SomethingSpec" "lib.cabal" 1 let match = TermMatch "Lib.SomethingSpec" "lib.cabal" 1
let result = resultsFromMatches [match] let result = resultsFromMatches [match]
haskellSingleOkay result `shouldBe` True haskellAutoLowLikelihood result `shouldReturn` True
configByName :: String -> IO LanguageConfiguration
configByName s = do
(Right config) <- loadConfig
let (Just config') = find ((==) s . lcName) config
return config'
railsAutoLowLikelihood :: TermResults -> IO Bool
railsAutoLowLikelihood r = (`autoLowLikelihood` r) <$> configByName "Rails"
elixirAutoLowLikelihood :: TermResults -> IO Bool
elixirAutoLowLikelihood r = (`autoLowLikelihood` r) <$> configByName "Phoenix"
haskellAutoLowLikelihood :: TermResults -> IO Bool
haskellAutoLowLikelihood r = (`autoLowLikelihood` r) <$> configByName "Haskell"

View File

@ -12,6 +12,7 @@ category: Development
build-type: Simple build-type: Simple
-- extra-source-files: -- extra-source-files:
cabal-version: >=1.10 cabal-version: >=1.10
data-files: data/config.yml
library library
hs-source-dirs: src hs-source-dirs: src
@ -23,6 +24,9 @@ library
, Unused.Util , Unused.Util
, Unused.Regex , Unused.Regex
, Unused.ResponseFilter , Unused.ResponseFilter
, Unused.ResultsClassifier
, Unused.ResultsClassifier.Types
, Unused.ResultsClassifier.Config
, Unused.Grouping , Unused.Grouping
, Unused.Grouping.Internal , Unused.Grouping.Internal
, Unused.Grouping.Types , Unused.Grouping.Types
@ -38,6 +42,7 @@ library
, Unused.CLI.ProgressIndicator , Unused.CLI.ProgressIndicator
, Unused.CLI.ProgressIndicator.Internal , Unused.CLI.ProgressIndicator.Internal
, Unused.CLI.ProgressIndicator.Types , Unused.CLI.ProgressIndicator.Types
other-modules: Paths_unused
build-depends: base >= 4.7 && < 5 build-depends: base >= 4.7 && < 5
, process , process
, parsec , parsec
@ -49,6 +54,10 @@ library
, ansi-terminal , ansi-terminal
, unix , unix
, parallel-io , parallel-io
, yaml
, bytestring
, text
, unordered-containers
ghc-options: -Wall -Werror -O2 ghc-options: -Wall -Werror -O2
default-language: Haskell2010 default-language: Haskell2010
@ -77,6 +86,7 @@ test-suite unused-test
, Unused.Grouping.InternalSpec , Unused.Grouping.InternalSpec
, Unused.TermSearch.InternalSpec , Unused.TermSearch.InternalSpec
, Unused.UtilSpec , Unused.UtilSpec
, Paths_unused
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall -Werror ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall -Werror
default-language: Haskell2010 default-language: Haskell2010