diagnose: remove everything

This commit is contained in:
Mesabloo 2021-08-12 20:16:25 +02:00
parent 76e2e88430
commit 00de50a0d0
9 changed files with 0 additions and 331 deletions

View File

@ -20,15 +20,6 @@ source-repository head
location: https://github.com/mesabloo/nihil
library
exposed-modules:
Text.Diagnose
Text.Diagnose.Diagnostic
Text.Diagnose.Format
Text.Diagnose.Format.JSON
Text.Diagnose.Format.Text
Text.Diagnose.Internal.ReportSize
Text.Diagnose.Position
Text.Diagnose.Report
other-modules:
Paths_diagnose
hs-source-dirs:

View File

@ -1,11 +0,0 @@
module Text.Diagnose
( module Text.Diagnose.Diagnostic
, module Text.Diagnose.Report
, module Text.Diagnose.Format
, module Text.Diagnose.Position
) where
import Text.Diagnose.Diagnostic
import Text.Diagnose.Report hiding (prettyReport, Files)
import Text.Diagnose.Position
import Text.Diagnose.Format

View File

@ -1,50 +0,0 @@
module Text.Diagnose.Diagnostic
( Diagnostic
, diagnostic, (<~<), (<++>)
, printDiagnostic
) where
import Text.Diagnose.Report
import Text.Diagnose.Format
import Data.Map (Map)
import qualified Data.Map as Map
import Text.PrettyPrint.ANSI.Leijen
import System.IO (Handle)
import Text.Diagnose.Internal.ReportSize (maxWidth)
-- | A @'Diagnostic' s m a@ is a diagnostic whose stream is a @s a@ and whose message type is @m@.
data Diagnostic s m a
= Diagnostic (Files s a) [Report m]
-- | Creates an empty 'Diagnostic' with no files and no reports.
diagnostic :: Diagnostic s m a
diagnostic = Diagnostic mempty mempty
-- | Appends a file along with its name to the map of files of the 'Diagnostic'.
(<~<) :: Diagnostic s m a -> (FilePath, [s a]) -> Diagnostic s m a
Diagnostic files reports <~< (path, content) = Diagnostic (Map.insert path content files) reports
-- | Appends a report to the list of reports of the 'Diagnostic'.
(<++>) :: Diagnostic s m a -> Report m -> Diagnostic s m a
Diagnostic files reports <++> report = Diagnostic files (reports ++ [report])
infixl 5 <++>
infixl 4 <~<
-- | Checks whether a 'Diagnostic' is empty or not, i.e. it has no reports.
emptyDiag :: Diagnostic s m a -> Bool
emptyDiag (Diagnostic _ []) = True
emptyDiag _ = False
instance (Foldable s, PrettyText (s a), PrettyText m) => PrettyText (Diagnostic s m a) where
prettyText (Diagnostic _ []) = empty
prettyText (Diagnostic files reports) = indent 1 (sep (fmap (prettyReport files) reports)) <> line
-- | Prints a @'Diagnostic' s m a@ To the given @'Handle'@
printDiagnostic :: (Foldable s, PrettyText (s a), PrettyText m) => Bool -> Handle -> Diagnostic s m a -> IO ()
printDiagnostic withColor handle diag
| emptyDiag diag = pure ()
| otherwise = displayIO handle (renderPretty 0.9 maxWidth . (if withColor then id else plain) $ prettyText diag)

View File

@ -1,7 +0,0 @@
module Text.Diagnose.Format
( module Text.Diagnose.Format.Text
, module Text.Diagnose.Format.JSON
) where
import Text.Diagnose.Format.Text
import Text.Diagnose.Format.JSON

View File

@ -1,7 +0,0 @@
module Text.Diagnose.Format.JSON where
import Text.PrettyPrint.ANSI.Leijen
class PrettyJSON a where
-- | Prettifies a value into a JSON representation.
prettyJSON :: a -> Doc

View File

@ -1,22 +0,0 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module Text.Diagnose.Format.Text where
import Text.PrettyPrint.ANSI.Leijen
class PrettyText a where
-- | Prettifies into a simple 'Doc'.
prettyText :: a -> Doc
instance PrettyText String where
prettyText = pretty
instance PrettyText Integer where
prettyText = integer
instance PrettyText Int where
prettyText = int
instance PrettyText Char where
prettyText = text . (: [])

View File

@ -1,8 +0,0 @@
module Text.Diagnose.Internal.ReportSize where
-- | The maximum width the diagnostic can span across.
--
-- __NOTE:__ The diagnostic may be printed larger if any line is bigger than
-- this specified width.
maxWidth :: Int
maxWidth = 80

View File

@ -1,25 +0,0 @@
{-# LANGUAGE RecordWildCards #-}
module Text.Diagnose.Position where
import Text.PrettyPrint.ANSI.Leijen
-- | Offset in a stream used to determine where to put markers.
data Position
= Position
{ beginning :: (Integer, Integer) -- ^ The beginning line and column
, end :: (Integer, Integer) -- ^ The end line and column
, file :: String -- ^ The name of the file (does not need to be an absolute path)
}
deriving (Show, Eq)
instance Pretty Position where
pretty Position{..} =
let (bLine, bCol) = beginning
in angles (text file <> colon <> integer bLine <> colon <> integer bCol)
instance Ord Position where
p1 <= p2 =
let (b1Line, b1Col) = beginning p1
(b2Line, b2Col) = beginning p2
in b1Line <= b2Line && b1Col <= b2Col

View File

@ -1,192 +0,0 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
module Text.Diagnose.Report
( Report, Marker(..), Files, Kind, Hint
, reportError, reportWarning
, hint
, prettyReport
) where
import Text.Diagnose.Position
import Text.Diagnose.Format
import Text.PrettyPrint.ANSI.Leijen
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Map (Map)
import qualified Data.Map as Map
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as List
import Prelude hiding ((<$>))
import Data.Functor ((<&>))
import Data.Function (on)
import Data.List (sortBy, nub)
import Data.Maybe (fromJust, maybeToList, fromMaybe)
import Text.Diagnose.Internal.ReportSize (maxWidth)
type Files s a = Map FilePath [s a]
type Markers m = Map Position (NonEmpty (Marker m))
-- | A report holds a 'Kind' of report and a message along with the useful 'Marker's and 'Hint'.
--
-- It basically holds either an error or a warning along with additional context such as code.
data Report m
= Report Kind m (Markers m) [Hint m]
-- | The kind of a 'Report', either an error or a warning.
data Kind
= Error
| Warning
-- | A simple polymorphic hint holder
data Hint m
= Hint m
deriving (Eq)
instance (Eq m, Semigroup m) => Semigroup (Report m) where
Report k1 msg1 markers1 hints1 <> Report k2 msg2 markers2 hints2 =
Report detectedKind (msg1 <> msg2) (fmap List.nub $ Map.unionWith (<>) markers1 markers2) (nub $ hints1 <> hints2)
where
detectedKind = case (k1, k2) of
(Error, _) -> Error
(_, Error) -> Error
_ -> Warning
instance (Eq m, Monoid m) => Monoid (Report m) where
mempty = reportError mempty mempty mempty
-- | A polymorphic marker, parameterized on the message type.
--
-- A marker is either:
data Marker m
= This m -- ^ * a "this" marker (@^^^^^ \<message\>@) used to highlight where the error/warning is located at
| Where m -- ^ * a "where" marker (@----- \<message\>@) used to provide some useful information in the context
| Maybe m -- ^ * a "maybe" marker (@~~~~~ \<message\>@) used to provide ideas of potential fixes
| Empty -- ^ * an "empty" marker used to show a line in the error/warning without adding any sort of marker on it
deriving (Eq)
-- | Creates a new report.
reportError, reportWarning :: m -> [(Position, Marker m)] -> [Hint m] -> Report m
reportError = newReport Error
reportWarning = newReport Warning
-- | Internal creation of a new report.
newReport :: Kind -> m -> [(Position, Marker m)] -> [Hint m] -> Report m
newReport sev msg markers hints = Report sev msg markMap hints
where markMap = foldl createMap mempty markers
-- | Extends a 'Map' with a marker at a given position.
--
-- If the position is already in the 'Map', the marker is simply added to the list of markers
-- else it is added as a non-empty list directly in the 'Map'.
createMap m (p, mark) = Map.insertWith (flip (<>)) p (mark List.:| []) m
-- | A simple alias on the constructor of 'Hint', used to avoid exporting the constructor.
hint :: m -> Hint m
hint = Hint
-- | Prettifies a report, when given the files it may want to used.
prettyReport :: (Foldable s, PrettyText (s a), PrettyText m) => Files s a -> Report m -> Doc
prettyReport files (Report kind msg markers hints) =
let (color, margin, sev) = prettyKind kind
in color (bold sev) <> colon <+> align (smartPretty msg) <> hardline <>
mconcat (replicate (margin - 2) space) <> text "In" <> colon <+>
prettyCodeWithMarkers files markers color <> hardline <> line <>
prettyHints hints
-- | Prettifies the kind of a report.
prettyKind :: Kind
-> (Doc -> Doc, Int, Doc) -- ^ Returns the color for "this" markers, the offset for the "In: <file>" part and the label of the report
prettyKind Error = (red, 7, brackets $ text "error")
prettyKind Warning = (yellow, 9, brackets $ text "warning")
-- | Prettifies the code along with the useful markers.
prettyCodeWithMarkers :: (Foldable s, PrettyText m, PrettyText (s a))
=> Files s a -- ^ The potential input files to use to show the code
-> Markers m -- ^ The markers to show
-> (Doc -> Doc) -- ^ The color for "this" markers
-> Doc
prettyCodeWithMarkers files markers color =
let sortedMarkers = sortBy (compare `on` fst) (Map.toList markers)
in case sortedMarkers of
[] -> green (text "???")
(Position{beginning=begin, ..}, _):_ ->
let (bLine, bCol) = begin
((p, _):_) = reverse sortedMarkers
maxLineMarkLen = length (show (fst (beginning p)))
showLine l =
space <> text (replicate (maxLineMarkLen - length (show l)) ' ') <> integer l <> text "|"
fileContent = fromMaybe [] (Map.lookup file files)
showMarkers = sortedMarkers <&> uncurry \ Position{..} markers ->
let (bLine, bCol) = beginning
(eLine, eCol) = end
code = fileContent !!? fromIntegral (bLine - 1)
underlineLen = fromIntegral $ (if eLine == bLine then eCol else fromIntegral (maybe 0 length code)) - bCol
markerOffset = maxLineMarkLen + 2 + fromIntegral bCol
marker m = prettyMarker underlineLen markerOffset m color magenta dullgreen
renderMarker m =
marker m <&> \ x -> mconcat (replicate markerOffset space) <> x
renderedMarkers = List.toList markers >>= maybeToList . renderMarker
in white $ bold (showLine bLine) <+> maybe (text "<no line>") prettyText code <>
mconcat (applyIfNotNull (line :) $ punctuate line renderedMarkers) <>
if bCol + fromIntegral underlineLen > 40 then line else empty
in green (text file) <$>
empty <$>
mconcat (punctuate line showMarkers)
infix 9 !!?
(!!?) :: [a] -> Int -> Maybe a
(!!?) xs i
| i < 0 = Nothing
| otherwise = go i xs
where
go :: Int -> [a] -> Maybe a
go 0 (x:_) = Just x
go j (_:ys) = go (j - 1) ys
go _ [] = Nothing
{-# INLINE (!!?) #-}
-- | Prettifies a list of 'Hint's into a single 'Doc'ument. All 'Hint's are prettified and concatenated with a 'line' in between.
prettyHints :: (PrettyText m) => [Hint m] -> Doc
prettyHints [] = line
prettyHints hs = blue (vsep (fmap render hs)) <> line
where render (Hint msg) = smartPretty msg
-- | Prettifies a marker.
prettyMarker :: (PrettyText m)
=> Int -- ^ The length of the marker
-> Int -- ^ The offset of the marker
-> Marker m -- ^ The marker to show
-> (Doc -> Doc) -- ^ The color if a "this" marker
-> (Doc -> Doc) -- ^ The color for a "where" marker
-> (Doc -> Doc) -- ^ The color for a "maybe" marker
-> Maybe Doc -- ^ 'Nothing' if it is the 'Empty' marker
prettyMarker underlineLen offset marker colorThis colorWhere colorMaybe = case marker of
Empty -> Nothing
This msg -> showMarker '^' msg colorThis
Where msg -> showMarker '-' msg colorWhere
Maybe msg -> showMarker '~' msg colorMaybe
where under = text . replicate underlineLen
showMarker c msg color =
Just $ if offset + underlineLen > fromIntegral (maxWidth `div` 2)
then color $ under c <> line <> indent (offset + 4) (align $ smartPretty msg)
else color $ under c <+> align (smartPretty msg)
-- | A smarter pretty to keep long texts in between the bounds and correctly align them.
smartPretty :: (PrettyText d) => d -> Doc
smartPretty = vsep . fmap (fillSep . fmap text . words) . lines . show . prettyText
-- | Applies a function to the list if it isn't '[]', else returns it.
applyIfNotNull :: ([a] -> [a]) -> [a] -> [a]
applyIfNotNull _ [] = []
applyIfNotNull f l = f l