Extract aggregate data structure

This commit is contained in:
Joshua Clayton 2016-04-30 07:54:06 -04:00
parent 9f006ffd3c
commit 447943f401
2 changed files with 27 additions and 9 deletions

View File

@ -4,7 +4,6 @@ import System.Console.ANSI
import Unused.TermSearch (search) import Unused.TermSearch (search)
import Unused.Parser (parseLines) import Unused.Parser (parseLines)
import Unused.Types import Unused.Types
import Data.Map.Strict (toList)
main :: IO () main :: IO ()
main = do main = do
@ -14,7 +13,7 @@ main = do
case withOneOccurrence $ withOneFile response of case withOneOccurrence $ withOneFile response of
Right termMatchSet -> Right termMatchSet ->
mapM_ printMatchPair $ toList termMatchSet mapM_ printMatchPair $ listFromMatchSet termMatchSet
Left e -> do Left e -> do
setSGR [SetColor Background Vivid Red] setSGR [SetColor Background Vivid Red]
setSGR [SetColor Foreground Vivid White] setSGR [SetColor Foreground Vivid White]

View File

@ -3,11 +3,13 @@ module Unused.Types
, TermMatchSet , TermMatchSet
, ParseResponse(..) , ParseResponse(..)
, responseFromParse , responseFromParse
, listFromMatchSet
, withOneFile , withOneFile
, withOneOccurrence , withOneOccurrence
) where ) where
import Text.Parsec (ParseError) import Text.Parsec (ParseError)
import Data.Bifunctor (second)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Data.List (isInfixOf) import Data.List (isInfixOf)
import Unused.Util (groupBy) import Unused.Util (groupBy)
@ -18,20 +20,37 @@ data TermMatch = TermMatch
, occurrences :: Int , occurrences :: Int
} deriving Show } deriving Show
type TermMatchSet = Map.Map String [TermMatch] data TermResults = TermResults
{ matches :: [TermMatch]
, totalFiles :: Int
, totalOccurrences :: Int
}
type TermMatchSet = Map.Map String TermResults
type ParseResponse = Either ParseError TermMatchSet type ParseResponse = Either ParseError TermMatchSet
resultsFromMatches :: [TermMatch] -> TermResults
resultsFromMatches m =
TermResults
{ matches = m
, totalFiles = totalFiles'
, totalOccurrences = totalOccurrences'
}
where
totalFiles' = length m
totalOccurrences' = sum $ fmap occurrences m
responseFromParse :: Either ParseError [TermMatch] -> ParseResponse responseFromParse :: Either ParseError [TermMatch] -> ParseResponse
responseFromParse = responseFromParse =
fmap $ Map.fromList . groupBy term fmap $ Map.fromList . map (second resultsFromMatches) . groupBy term
withOneFile :: ParseResponse -> ParseResponse withOneFile :: ParseResponse -> ParseResponse
withOneFile = fmap $ Map.filterWithKey (\_ a -> length a == 1) withOneFile = fmap $ Map.filterWithKey (\_ a -> totalFiles a == 1)
withOneOccurrence :: ParseResponse -> ParseResponse withOneOccurrence :: ParseResponse -> ParseResponse
withOneOccurrence = fmap $ Map.filterWithKey (\_ a -> (sum $ fmap occurrences a) == 1) withOneOccurrence = fmap $ Map.filterWithKey (\_ a -> totalOccurrences a == 1)
notMatchingPath :: String -> ParseResponse -> ParseResponse listFromMatchSet :: TermMatchSet -> [(String, [TermMatch])]
notMatchingPath s = listFromMatchSet =
fmap $ Map.map $ filter (not . isInfixOf s . path) map (second matches) . Map.toList