----------------------------------------------------------------------------- -- | -- Module : Lentil.Export -- Copyright : © 2015 Francesco Ariis -- License : GPLv3 (see the LICENSE file) -- -- Exporting issues to various formats ----------------------------------------------------------------------------- module Lentil.Export where import Text.CSV import Lentil.Types import qualified Data.List as L import Data.Function (on) --------------- -- FUNCTIONS -- --------------- issues2CSV :: [Issue] -> String issues2CSV is = printCSV (firstLine : map i2r is) where firstLine = ["Filepath", "Row", "Description", "Tags"] i2r i = [(prettyFP . iFile) i, show (iRow i), iPPDesc i, tags2String (iTags i)] -- compiler-like (gcc/ghc) warnings, parseable by emacs issues2Compiler :: [Issue] -> String issues2Compiler is = L.intercalate "\n" (map i2c is) where i2c i = (prettyFP . iFile) i ++ ":" ++ show (iRow i) ++ ":\n" ++ " " ++ iPPDesc i ++ " " ++ tags2StringPretty (iTags i) ++ "\n" -- TODO: maybe use a dedicated library to format xml? [design] -- xml output issues2Xml :: [Issue] -> String issues2Xml is = concat ["", concatMap is2x (groupBy is), "", "\n"] where i2x i = concat ["", "", show (iRow i), "", maybe "" d2x (iDesc i), "", concatMap t2x (iTags i), "", ""] d2x d = concat ["", cdata d, ""] t2x t = concat ["", tagString t, ""] is2x [] = "" is2x is'@(i:_) = let fp = file i in concat ["", "", cdata fp, "", concatMap i2x is', ""] cdata x = concat [""] file = prettyFP . iFile groupBy = L.groupBy ((==) `on` file) ----------------- -- ANCILLARIES -- ----------------- -- tag1 tag2 etc tags2String :: [Tag] -> String tags2String ts = unwords (map tagString ts) -- [tag1] [tag2] etc. tags2StringPretty :: [Tag] -> String tags2StringPretty ts = unwords . map ((openDel:) . (++[closeDel]) . tagString) $ ts