Follow naming conventions for record fields

This commit is contained in:
Joshua Clayton 2016-05-03 22:13:01 -04:00
parent 67e52ed017
commit 961585ce6e
3 changed files with 43 additions and 43 deletions

View File

@ -85,8 +85,8 @@ printDirectorySection (dir, ss) = do
where where
allSets = listFromMatchSet ss allSets = listFromMatchSet ss
allResults = fmap snd allSets allResults = fmap snd allSets
termLength = return . length . term termLength = return . length . tmTerm
maxWidth = maximum $ termLength =<< matches =<< allResults maxWidth = maximum $ termLength =<< trMatches =<< allResults
printDirectory :: DirectoryPrefix -> IO () printDirectory :: DirectoryPrefix -> IO ()
printDirectory (DirectoryPrefix dir) = do printDirectory (DirectoryPrefix dir) = do
@ -97,7 +97,7 @@ printDirectory (DirectoryPrefix dir) = do
printTermResults :: Int -> (String, TermResults) -> IO () printTermResults :: Int -> (String, TermResults) -> IO ()
printTermResults w (_, results) = printTermResults w (_, results) =
printMatches w results $ matches results printMatches w results $ trMatches results
likelihoodColor :: RemovalLikelihood -> Color likelihoodColor :: RemovalLikelihood -> Color
likelihoodColor High = Red likelihoodColor High = Red
@ -107,13 +107,13 @@ likelihoodColor Low = Green
printMatches :: Int -> TermResults -> [TermMatch] -> IO () printMatches :: Int -> TermResults -> [TermMatch] -> IO ()
printMatches w r ms = printMatches w r ms =
forM_ ms $ \m -> do forM_ ms $ \m -> do
setSGR [SetColor Foreground Dull (likelihoodColor $ removalLikelihood r)] setSGR [SetColor Foreground Dull (likelihoodColor $ trRemovalLikelihood r)]
setSGR [SetConsoleIntensity NormalIntensity] setSGR [SetConsoleIntensity NormalIntensity]
putStr $ " " ++ (printf termFormat $ term m) putStr $ " " ++ (printf termFormat $ tmTerm m)
setSGR [Reset] setSGR [Reset]
setSGR [SetColor Foreground Dull Cyan] setSGR [SetColor Foreground Dull Cyan]
setSGR [SetConsoleIntensity FaintIntensity] setSGR [SetConsoleIntensity FaintIntensity]
putStr $ " " ++ path m putStr $ " " ++ tmPath m
setSGR [Reset] setSGR [Reset]
putStr "\n" putStr "\n"
where where

View File

@ -17,7 +17,7 @@ parseLines =
responseFromParse :: Either ParseError [TermMatch] -> ParseResponse responseFromParse :: Either ParseError [TermMatch] -> ParseResponse
responseFromParse = responseFromParse =
fmap $ Map.fromList . map (second resultsFromMatches) . groupBy term fmap $ Map.fromList . map (second resultsFromMatches) . groupBy tmTerm
parseTermMatches :: Parser [TermMatch] parseTermMatches :: Parser [TermMatch]
parseTermMatches = do parseTermMatches = do

View File

@ -20,17 +20,17 @@ import qualified Data.Map.Strict as Map
import Unused.Regex (matchRegex) import Unused.Regex (matchRegex)
data TermMatch = TermMatch data TermMatch = TermMatch
{ term :: String { tmTerm :: String
, path :: String , tmPath :: String
, occurrences :: Int , tmOccurrences :: Int
} deriving Show } deriving Show
data TermResults = TermResults data TermResults = TermResults
{ resultTerm :: String { trTerm :: String
, matches :: [TermMatch] , trMatches :: [TermMatch]
, totalFiles :: Int , trTotalFiles :: Int
, totalOccurrences :: Int , trTotalOccurrences :: Int
, removalLikelihood :: RemovalLikelihood , trRemovalLikelihood :: RemovalLikelihood
} deriving Show } deriving Show
data RemovalLikelihood = High | Medium | Low deriving Show data RemovalLikelihood = High | Medium | Low deriving Show
@ -44,18 +44,18 @@ newtype DirectoryPrefix = DirectoryPrefix String deriving (Eq, Show, Ord)
resultsFromMatches :: [TermMatch] -> TermResults resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m = resultsFromMatches m =
calculateLikelihood $ TermResults calculateLikelihood $ TermResults
{ resultTerm = resultTerm' terms { trTerm = resultTerm terms
, matches = m , trMatches = m
, totalFiles = totalFiles' , trTotalFiles = totalFiles
, totalOccurrences = totalOccurrences' , trTotalOccurrences = totalOccurrences
, removalLikelihood = High , trRemovalLikelihood = High
} }
where where
totalFiles' = length m totalFiles = length m
totalOccurrences' = sum $ fmap occurrences m totalOccurrences = sum $ fmap tmOccurrences m
terms = map term m terms = map tmTerm m
resultTerm' (x:_) = x resultTerm (x:_) = x
resultTerm' _ = "" resultTerm _ = ""
withOneFile :: ParseResponse -> ParseResponse withOneFile :: ParseResponse -> ParseResponse
withOneFile = fmap $ Map.filterWithKey (const oneFile) withOneFile = fmap $ Map.filterWithKey (const oneFile)
@ -64,35 +64,35 @@ withOneOccurrence :: ParseResponse -> ParseResponse
withOneOccurrence = fmap $ Map.filterWithKey (const oneOccurence) withOneOccurrence = fmap $ Map.filterWithKey (const oneOccurence)
oneOccurence :: TermResults -> Bool oneOccurence :: TermResults -> Bool
oneOccurence = (== 1) . totalOccurrences oneOccurence = (== 1) . trTotalOccurrences
oneFile :: TermResults -> Bool oneFile :: TermResults -> Bool
oneFile = (== 1) . totalFiles oneFile = (== 1) . trTotalFiles
isClassOrModule :: TermResults -> Bool isClassOrModule :: TermResults -> Bool
isClassOrModule = matchRegex "^[A-Z]" . resultTerm isClassOrModule = matchRegex "^[A-Z]" . trTerm
railsSingleOkay :: TermResults -> Bool railsSingleOkay :: TermResults -> Bool
railsSingleOkay r = railsSingleOkay r =
foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (controller || helper || migration)] foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (controller || helper || migration)]
where where
controller = (matchRegex "^app/controllers/" singlePath) && (matchRegex "Controller$" $ resultTerm r) controller = (matchRegex "^app/controllers/" singlePath) && (matchRegex "Controller$" $ trTerm r)
helper = (matchRegex "^app/helpers/" singlePath) && (matchRegex "Helper$" $ resultTerm r) helper = (matchRegex "^app/helpers/" singlePath) && (matchRegex "Helper$" $ trTerm r)
migration = matchRegex "^db/migrate/" singlePath migration = matchRegex "^db/migrate/" singlePath
singlePath = path' $ fmap path $ matches r singlePath = path $ fmap tmPath $ trMatches r
path' (x:_) = x path (x:_) = x
path' [] = "" path [] = ""
elixirSingleOkay :: TermResults -> Bool elixirSingleOkay :: TermResults -> Bool
elixirSingleOkay r = elixirSingleOkay r =
foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (view || test || migration)] foldl1 (&&) [isClassOrModule r, oneFile r, oneOccurence r, (view || test || migration)]
where where
migration = matchRegex "^priv/repo/migrations/" singlePath migration = matchRegex "^priv/repo/migrations/" singlePath
view = (matchRegex "^web/views/" singlePath) && (matchRegex "View$" $ resultTerm r) view = (matchRegex "^web/views/" singlePath) && (matchRegex "View$" $ trTerm r)
test = (matchRegex "^test/" singlePath) && (matchRegex "Test$" $ resultTerm r) test = (matchRegex "^test/" singlePath) && (matchRegex "Test$" $ trTerm r)
singlePath = path' $ fmap path $ matches r singlePath = path $ fmap tmPath $ trMatches r
path' (x:_) = x path (x:_) = x
path' [] = "" path [] = ""
listFromMatchSet :: TermMatchSet -> [(String, TermResults)] listFromMatchSet :: TermMatchSet -> [(String, TermResults)]
listFromMatchSet = listFromMatchSet =
@ -106,9 +106,9 @@ responseForPath :: DirectoryPrefix -> TermMatchSet -> TermMatchSet
responseForPath s = responseForPath s =
filterVByPath . filterKVByPath filterVByPath . filterKVByPath
where where
filterVByPath = Map.map (resultsFromMatches . filter (((==) s) . fileNameGrouping . path) . matches) filterVByPath = Map.map (resultsFromMatches . filter (((==) s) . fileNameGrouping . tmPath) . trMatches)
filterKVByPath = Map.filterWithKey (\_ a -> s `elem` allPaths a) filterKVByPath = Map.filterWithKey (\_ a -> s `elem` allPaths a)
allPaths = fmap (fileNameGrouping . path) . matches allPaths = fmap (fileNameGrouping . tmPath) . trMatches
fileNameGrouping :: String -> DirectoryPrefix fileNameGrouping :: String -> DirectoryPrefix
fileNameGrouping = fileNameGrouping =
@ -118,15 +118,15 @@ fileNameGrouping =
directoriesForGrouping :: TermMatchSet -> [DirectoryPrefix] directoriesForGrouping :: TermMatchSet -> [DirectoryPrefix]
directoriesForGrouping = directoriesForGrouping =
uniqueValues . Map.map (fmap (fileNameGrouping . path) . matches) uniqueValues . Map.map (fmap (fileNameGrouping . tmPath) . trMatches)
where where
uniqueValues = sort . nub . concat . Map.elems uniqueValues = sort . nub . concat . Map.elems
calculateLikelihood :: TermResults -> TermResults calculateLikelihood :: TermResults -> TermResults
calculateLikelihood r = calculateLikelihood r =
r { removalLikelihood = newLikelihood } r { trRemovalLikelihood = newLikelihood }
where where
baseScore = totalOccurrences r baseScore = trTotalOccurrences r
railsScore = if railsSingleOkay r then 5 else 0 railsScore = if railsSingleOkay r then 5 else 0
elixirScore = if elixirSingleOkay r then 5 else 0 elixirScore = if elixirSingleOkay r then 5 else 0
totalScore = baseScore + railsScore + elixirScore totalScore = baseScore + railsScore + elixirScore