Better manage column formatting

Why?
====

Formatting each column requires context on the column, as well as
information on alignment. This extracts the column formatting logic to a
specific formatter.

ColumnFormatter is coupled to the order of columns/data displayed to the
user.
This commit is contained in:
Joshua Clayton 2016-05-09 09:31:06 -04:00
parent 11d35a6263
commit 4947e54f27
3 changed files with 63 additions and 17 deletions

View File

@ -3,30 +3,29 @@ module Unused.CLI.SearchResult
) where
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.SearchResult.ColumnFormatter
import Unused.CLI.Util
printSearchResults :: TermMatchSet -> IO ()
printSearchResults termMatchSet =
mapM_ (printDirectorySection maxWidth) responses
mapM_ (printDirectorySection columnFormat) responses
where
responses = responsesGroupedByPath termMatchSet
allSets = listFromMatchSet =<< map snd responses
allResults = map snd allSets
termLength = return . length . tmTerm
maxWidth = maximum $ termLength =<< trMatches =<< allResults
columnFormat = buildColumnFormatter allResults
listFromMatchSet :: TermMatchSet -> [(String, TermResults)]
listFromMatchSet =
Map.toList
printDirectorySection :: Int -> (DirectoryPrefix, TermMatchSet) -> IO ()
printDirectorySection w (dir, ss) = do
printDirectorySection :: ColumnFormat -> (DirectoryPrefix, TermMatchSet) -> IO ()
printDirectorySection cf (dir, ss) = do
printDirectory dir
mapM_ (printTermResults w) $ listFromMatchSet ss
mapM_ (printTermResults cf) $ listFromMatchSet ss
putStr "\n"
printDirectory :: DirectoryPrefix -> IO ()
@ -36,9 +35,9 @@ printDirectory (DirectoryPrefix dir) = do
putStrLn dir
setSGR [Reset]
printTermResults :: Int -> (String, TermResults) -> IO ()
printTermResults w (_, results) =
printMatches w results $ trMatches results
printTermResults :: ColumnFormat -> (String, TermResults) -> IO ()
printTermResults cf (_, results) =
printMatches cf results $ trMatches results
likelihoodColor :: RemovalLikelihood -> Color
likelihoodColor High = Red
@ -46,24 +45,25 @@ likelihoodColor Medium = Yellow
likelihoodColor Low = Green
likelihoodColor Unknown = Black
printMatches :: Int -> TermResults -> [TermMatch] -> IO ()
printMatches w r ms =
printMatches :: ColumnFormat -> TermResults -> [TermMatch] -> IO ()
printMatches cf r ms =
forM_ ms $ \m -> do
setSGR [SetColor Foreground Dull (likelihoodColor $ trRemovalLikelihood r)]
setSGR [SetConsoleIntensity NormalIntensity]
putStr $ " " ++ printf termFormat (tmTerm m)
putStr $ " " ++ printTerm (tmTerm m)
setSGR [Reset]
setSGR [SetColor Foreground Vivid Cyan]
setSGR [SetConsoleIntensity NormalIntensity]
putStr $ printNumber (trTotalFiles r) ++ "," ++ printNumber (trTotalOccurrences r) ++ " "
putStr $ " " ++ printNumber (trTotalFiles r) ++ ", " ++ printNumber (trTotalOccurrences r)
setSGR [Reset]
setSGR [SetColor Foreground Dull Cyan]
setSGR [SetConsoleIntensity FaintIntensity]
putStr $ " " ++ tmPath m
putStr $ " " ++ printPath (tmPath m)
setSGR [Reset]
putStr "\n"
where
termFormat = "%-" ++ show w ++ "s"
printNumber = printf "%2d"
printTerm = cfPrintTerm cf
printPath = cfPrintPath cf
printNumber = cfPrintNumber cf

View File

@ -0,0 +1,45 @@
module Unused.CLI.SearchResult.ColumnFormatter
( ColumnFormat(..)
, buildColumnFormatter
) where
import Text.Printf
import Unused.Types (TermResults(..), TermMatch(..))
data ColumnFormat = ColumnFormat
{ cfPrintTerm :: String -> String
, cfPrintPath :: String -> String
, cfPrintNumber :: Int -> String
}
buildColumnFormatter :: [TermResults] -> ColumnFormat
buildColumnFormatter r =
ColumnFormat (printf $ termFormat r) (printf $ pathFormat r) (printf $ numberFormat r)
termFormat :: [TermResults] -> String
termFormat rs =
"%-" ++ show termWidth ++ "s"
where
termWidth = maximum $ termLength =<< trMatches =<< rs
termLength = return . length . tmTerm
pathFormat :: [TermResults] -> String
pathFormat rs =
"%-" ++ show pathWidth ++ "s"
where
pathWidth = maximum $ pathLength =<< trMatches =<< rs
pathLength = return . length . tmPath
numberFormat :: [TermResults] -> String
numberFormat rs =
"%" ++ show numberWidth ++ "d"
where
numberWidth = maximum [fileWidth, occurrenceWidth]
fileWidth = maximum $ fileLength =<< rs
occurrenceWidth = maximum $ occurrenceLength =<< rs
fileLength = return . numberLength . trTotalFiles
occurrenceLength = return . numberLength . trTotalOccurrences
numberLength :: Int -> Int
numberLength i =
1 + floor (logBase 10 $ fromIntegral i)

View File

@ -27,6 +27,7 @@ library
, Unused.CLI.Search
, Unused.CLI.SearchError
, Unused.CLI.SearchResult
, Unused.CLI.SearchResult.ColumnFormatter
, Unused.CLI.SearchWithProgress
, Unused.CLI.SearchWithoutProgress
, Unused.CLI.Util