{-# LANGUAGE RecordWildCards #-} -- | Generate a markdown that summarizes the builtin hints. module Test.Summary (genBuiltinSummaryMd) where import qualified Data.Map as Map import Config.Type import Test.Util genBuiltinSummaryMd :: BuiltinSummary -> String genBuiltinSummaryMd builtins = unlines $ [ "# Built-in Hints" , "" , "This page is auto-generated from `cabal run hlint test -- --generate-summary`" , "or `stack run hlint test -- --generate-summary`." , "" ] ++ table builtins table :: BuiltinSummary -> [String] table builtins = [""] ++ row ["", "", ""] ++ Map.foldMapWithKey showHint builtins ++ ["
HintSeveritySupport Refactoring?
"] row :: [String] -> [String] row xs = [""] ++ xs ++ [""] -- | Render using if it is single-line, otherwise using
.
haskell :: String -> [String]
haskell s
  | '\n' `elem` s = ["
", s, "
"] | otherwise = ["", s, "", "
"] showHint :: (String, Severity, Bool) -> BuiltinEx -> [String] showHint (hint, sev, refact) BuiltinEx{..} = row1 ++ row2 where row1 = row [ "" ++ hint ++ "" , "" ++ show sev ++ "" , "" ++ if refact then "Yes" else "No" ++ "" ] row2 = row example example = [ "" , "Example:" ] ++ haskell builtinInp ++ ["Found:"] ++ haskell builtinFrom ++ ["Suggestion:"] ++ haskell to ++ [""] to = case builtinTo of Nothing -> "" Just "" -> "Perhaps you should remove it." Just s -> s