Move additional functionality out of Types and into separate modules

This commit is contained in:
Joshua Clayton 2016-05-07 05:56:46 -04:00
parent a924cb99f3
commit 1f5db58f5e
8 changed files with 138 additions and 111 deletions

View File

@ -3,7 +3,7 @@ module Main where
import Options.Applicative
import System.IO (hSetBuffering, BufferMode(NoBuffering), stdout)
import Unused.Parser (parseLines)
import Unused.Types (withOneOccurrence, withOneFile)
import Unused.ResponseFilter (withOneOccurrence, withOneFile)
import Unused.CLI (SearchRunner(..), executeSearch, printParseError, printSearchResults, resetScreen)
data Options = Options

View File

@ -4,7 +4,9 @@ module Unused.CLI.SearchResult
import Control.Monad (forM_)
import Text.Printf
import qualified Data.Map.Strict as Map
import Unused.Types
import Unused.DirectoryGrouping (DirectoryPrefix(..), responsesGroupedByPath)
import Unused.CLI.Util
printSearchResults :: TermMatchSet -> IO ()
@ -17,6 +19,10 @@ printSearchResults termMatchSet =
termLength = return . length . tmTerm
maxWidth = maximum $ termLength =<< trMatches =<< allResults
listFromMatchSet :: TermMatchSet -> [(String, TermResults)]
listFromMatchSet =
Map.toList
printDirectorySection :: Int -> (DirectoryPrefix, TermMatchSet) -> IO ()
printDirectorySection w (dir, ss) = do
printDirectory dir

View File

@ -0,0 +1,37 @@
module Unused.DirectoryGrouping
( DirectoryPrefix(..)
, responsesGroupedByPath
) where
import System.FilePath (takeDirectory, splitDirectories)
import qualified Data.Map.Strict as Map
import Data.List (intercalate, sort, nub)
import Unused.Types
newtype DirectoryPrefix = DirectoryPrefix String deriving (Eq, Show, Ord)
responsesGroupedByPath :: TermMatchSet -> [(DirectoryPrefix, TermMatchSet)]
responsesGroupedByPath pr =
(\p -> (p, responseForPath p pr)) <$> directoriesForGrouping pr
responseForPath :: DirectoryPrefix -> TermMatchSet -> TermMatchSet
responseForPath s =
filterVByPath . filterKVByPath
where
filterVByPath = Map.map (updateMatchesWith newMatches)
filterKVByPath = Map.filterWithKey (const $ \a -> s `elem` allPaths a)
allPaths = fmap (fileNameGrouping . tmPath) . trMatches
updateMatchesWith f tr = tr { trMatches = f tr }
newMatches = filter ((== s) . fileNameGrouping . tmPath) . trMatches
fileNameGrouping :: String -> DirectoryPrefix
fileNameGrouping =
DirectoryPrefix . grouping
where
grouping = intercalate "/" . take 2 . splitDirectories . takeDirectory
directoriesForGrouping :: TermMatchSet -> [DirectoryPrefix]
directoriesForGrouping =
uniqueValues . Map.map (fmap (fileNameGrouping . tmPath) . trMatches)
where
uniqueValues = sort . nub . concat . Map.elems

View File

@ -0,0 +1,20 @@
module Unused.LikelihoodCalculator
( calculateLikelihood
) where
import Unused.Types (TermResults, RemovalLikelihood(..), trRemovalLikelihood, trTotalOccurrences)
import Unused.ResponseFilter (railsSingleOkay, elixirSingleOkay)
calculateLikelihood :: TermResults -> TermResults
calculateLikelihood r =
r { trRemovalLikelihood = newLikelihood }
where
baseScore = trTotalOccurrences r
railsScore = if railsSingleOkay r then 5 else 0
elixirScore = if elixirSingleOkay r then 5 else 0
totalScore = baseScore + railsScore + elixirScore
newLikelihood
| totalScore < 3 = High
| totalScore < 6 = Medium
| totalScore < 9 = Low
| otherwise = Low

View File

@ -9,7 +9,8 @@ import Text.Parsec
import Text.Parsec.String (Parser)
import qualified Data.Map.Strict as Map
import Unused.Util (groupBy)
import Unused.Types (TermMatch(..), ParseResponse, resultsFromMatches)
import Unused.Types
import Unused.LikelihoodCalculator
parseLines :: String -> ParseResponse
parseLines =
@ -19,6 +20,22 @@ responseFromParse :: Either ParseError [TermMatch] -> ParseResponse
responseFromParse =
fmap $ Map.fromList . map (second resultsFromMatches) . groupBy tmTerm
resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m =
calculateLikelihood TermResults
{ trTerm = resultTerm terms
, trMatches = m
, trTotalFiles = totalFiles
, trTotalOccurrences = totalOccurrences
, trRemovalLikelihood = High
}
where
totalFiles = length m
totalOccurrences = sum $ fmap tmOccurrences m
terms = map tmTerm m
resultTerm (x:_) = x
resultTerm _ = ""
parseTermMatches :: Parser [TermMatch]
parseTermMatches = do
tm <- many1 $ do

View File

@ -0,0 +1,53 @@
module Unused.ResponseFilter
( withOneFile
, withOneOccurrence
, oneFile
, oneOccurence
, isClassOrModule
, railsSingleOkay
, elixirSingleOkay
) where
import qualified Data.Map.Strict as Map
import Unused.Regex (matchRegex)
import Unused.Types
withOneFile :: ParseResponse -> ParseResponse
withOneFile = applyFilter (const oneFile)
withOneOccurrence :: ParseResponse -> ParseResponse
withOneOccurrence = applyFilter (const oneOccurence)
oneOccurence :: TermResults -> Bool
oneOccurence = (== 1) . trTotalOccurrences
oneFile :: TermResults -> Bool
oneFile = (== 1) . trTotalFiles
isClassOrModule :: TermResults -> Bool
isClassOrModule = matchRegex "^[A-Z]" . trTerm
railsSingleOkay :: TermResults -> Bool
railsSingleOkay r =
and [isClassOrModule r, oneFile r, oneOccurence r, controller || helper || migration]
where
controller = matchRegex "^app/controllers/" singlePath && matchRegex "Controller$" (trTerm r)
helper = matchRegex "^app/helpers/" singlePath && matchRegex "Helper$" (trTerm r)
migration = matchRegex "^db/migrate/" singlePath
singlePath = path $ tmPath <$> trMatches r
path (x:_) = x
path [] = ""
elixirSingleOkay :: TermResults -> Bool
elixirSingleOkay r =
and [isClassOrModule r, oneFile r, oneOccurence r, view || test || migration]
where
migration = matchRegex "^priv/repo/migrations/" singlePath
view = matchRegex "^web/views/" singlePath && matchRegex "View$" (trTerm r)
test = matchRegex "^test/" singlePath && matchRegex "Test$" (trTerm r)
singlePath = path $ tmPath <$> trMatches r
path (x:_) = x
path [] = ""
applyFilter :: (String -> TermResults -> Bool) -> ParseResponse -> ParseResponse
applyFilter = fmap . Map.filterWithKey

View File

@ -3,21 +3,11 @@ module Unused.Types
, TermResults(..)
, TermMatchSet
, ParseResponse
, DirectoryPrefix(..)
, RemovalLikelihood(..)
, listFromMatchSet
, withOneFile
, withOneOccurrence
, resultsFromMatches
, responsesGroupedByPath
) where
import System.FilePath (takeDirectory, splitDirectories)
import Text.Parsec (ParseError)
import Data.Bifunctor (second)
import Data.List (intercalate, sort, nub)
import qualified Data.Map.Strict as Map
import Unused.Regex (matchRegex)
data TermMatch = TermMatch
{ tmTerm :: String
@ -38,102 +28,3 @@ data RemovalLikelihood = High | Medium | Low deriving Show
type TermMatchSet = Map.Map String TermResults
type ParseResponse = Either ParseError TermMatchSet
newtype DirectoryPrefix = DirectoryPrefix String deriving (Eq, Show, Ord)
resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m =
calculateLikelihood TermResults
{ trTerm = resultTerm terms
, trMatches = m
, trTotalFiles = totalFiles
, trTotalOccurrences = totalOccurrences
, trRemovalLikelihood = High
}
where
totalFiles = length m
totalOccurrences = sum $ fmap tmOccurrences m
terms = map tmTerm m
resultTerm (x:_) = x
resultTerm _ = ""
withOneFile :: ParseResponse -> ParseResponse
withOneFile = fmap $ Map.filterWithKey (const oneFile)
withOneOccurrence :: ParseResponse -> ParseResponse
withOneOccurrence = fmap $ Map.filterWithKey (const oneOccurence)
oneOccurence :: TermResults -> Bool
oneOccurence = (== 1) . trTotalOccurrences
oneFile :: TermResults -> Bool
oneFile = (== 1) . trTotalFiles
isClassOrModule :: TermResults -> Bool
isClassOrModule = matchRegex "^[A-Z]" . trTerm
railsSingleOkay :: TermResults -> Bool
railsSingleOkay r =
and [isClassOrModule r, oneFile r, oneOccurence r, controller || helper || migration]
where
controller = matchRegex "^app/controllers/" singlePath && matchRegex "Controller$" (trTerm r)
helper = matchRegex "^app/helpers/" singlePath && matchRegex "Helper$" (trTerm r)
migration = matchRegex "^db/migrate/" singlePath
singlePath = path $ tmPath <$> trMatches r
path (x:_) = x
path [] = ""
elixirSingleOkay :: TermResults -> Bool
elixirSingleOkay r =
and [isClassOrModule r, oneFile r, oneOccurence r, view || test || migration]
where
migration = matchRegex "^priv/repo/migrations/" singlePath
view = matchRegex "^web/views/" singlePath && matchRegex "View$" (trTerm r)
test = matchRegex "^test/" singlePath && matchRegex "Test$" (trTerm r)
singlePath = path $ tmPath <$> trMatches r
path (x:_) = x
path [] = ""
listFromMatchSet :: TermMatchSet -> [(String, TermResults)]
listFromMatchSet =
Map.toList
responsesGroupedByPath :: TermMatchSet -> [(DirectoryPrefix, TermMatchSet)]
responsesGroupedByPath pr =
(\p -> (p, responseForPath p pr)) <$> directoriesForGrouping pr
responseForPath :: DirectoryPrefix -> TermMatchSet -> TermMatchSet
responseForPath s =
filterVByPath . filterKVByPath
where
filterVByPath = Map.map (updateMatchesWith newMatches)
filterKVByPath = Map.filterWithKey (const $ \a -> s `elem` allPaths a)
allPaths = fmap (fileNameGrouping . tmPath) . trMatches
updateMatchesWith f tr = tr { trMatches = f tr }
newMatches = filter ((== s) . fileNameGrouping . tmPath) . trMatches
fileNameGrouping :: String -> DirectoryPrefix
fileNameGrouping =
DirectoryPrefix . grouping
where
grouping = intercalate "/" . take 2 . splitDirectories . takeDirectory
directoriesForGrouping :: TermMatchSet -> [DirectoryPrefix]
directoriesForGrouping =
uniqueValues . Map.map (fmap (fileNameGrouping . tmPath) . trMatches)
where
uniqueValues = sort . nub . concat . Map.elems
calculateLikelihood :: TermResults -> TermResults
calculateLikelihood r =
r { trRemovalLikelihood = newLikelihood }
where
baseScore = trTotalOccurrences r
railsScore = if railsSingleOkay r then 5 else 0
elixirScore = if elixirSingleOkay r then 5 else 0
totalScore = baseScore + railsScore + elixirScore
newLikelihood
| totalScore < 3 = High
| totalScore < 6 = Medium
| totalScore < 9 = Low
| otherwise = Low

View File

@ -20,6 +20,9 @@ library
, Unused.Types
, Unused.Util
, Unused.Regex
, Unused.ResponseFilter
, Unused.DirectoryGrouping
, Unused.LikelihoodCalculator
, Unused.CLI
, Unused.CLI.Search
, Unused.CLI.SearchError