----------------------------------------------------------------------------- -- | -- Module : Lentil.Print -- Copyright : © 2015 Francesco Ariis -- License : GPLv3 (see the LICENSE file) -- -- printing types ----------------------------------------------------------------------------- module Lentil.Print where import Lentil.Types import Lentil.Query import Text.PrettyPrint.ANSI.Leijen as PP import qualified Data.List as L -- number of spaces + digits in indentation levels indNum :: Int indNum = 6 ---------------- -- PRIMITIVES -- ---------------- -- right align a number in a space of i columns alignNumber :: Int -> Int -> String alignNumber i n = replicate (i - length sn) ' ' ++ sn where sn = show n -- Bool: wheter or not to use colours in rendering myRender :: Bool -> Doc -> String myRender col d = ($ "") . displayS . renderPretty 1 75 $ d' where d' | col = d | otherwise = plain d ------------------ -- PRETTY PRINT -- ------------------ data TagCol = Red | Blue deriving (Eq) ppTag :: TagCol -> Tag -> Doc ppTag c t = col (char openDel) <> string (tagString t) <> col (char closeDel) where col | c == Red = red | otherwise = blue ppIssue :: Int -> Issue -> Doc ppIssue ind is = indent spInd ( fillSep [string iNum, string "", hang 0 (fillSep $ ppDescTags is)] ) where ppDescTags :: Issue -> [Doc] ppDescTags i = map string (words (iPPDesc is)) ++ map (ppTag Blue) (iTags i) spInd = indNum - ind iNum = alignNumber ind $ iRow is ppFile :: Int -> [Issue] -> Doc ppFile ind is = text (prettyFP $ iFile (head is)) PP.<$> vsep (map (ppIssue ind) is) ppIssues :: Bool -> [Issue] -> String ppIssues col is = myRender col $ vsep (L.intersperse softline igr) where ind = maximum . map (length . show . iRow) $ is igr = map (ppFile ind) $ groupIssues iFile is ------------- -- REPORTS -- ------------- -- tagpop pp report ppPopularity :: Bool -> [Issue] -> String ppPopularity col is = myRender col $ text "Tags popularity:" PP.<$> vsep ppPops -- PP.<$> (string "") where listpop = tagPop is ind = maximum . map (length . show . snd) $ listpop spInd = indNum - ind ppPop (t, n) = indent spInd (fillSep [iNum n, string "", hang 0 (ppTag Red t)]) ppPops = map ppPop listpop iNum n = string $ alignNumber ind n