document new function

This commit is contained in:
Mesabloo 2022-04-29 23:20:15 +02:00
parent 4528b2182a
commit 49b1a7b41e

View File

@ -252,6 +252,12 @@ linePrefix leftLen lineNo withUnicode =
in annotate (bold <> color Black) $ mempty <+> pad (leftLen - lineNoLen) ' ' mempty <> pretty lineNo <+> if withUnicode then "" else "|"
{-# INLINE linePrefix #-}
-- | Creates an ellipsis-prefix, when some line numbers are not consecutive.
--
-- Pretty printing yields those results:
--
-- [with unicode] "@␣␣␣␣␣⋮␣@"
-- [without unicode] "@␣␣␣␣...@"
ellipsisPrefix ::
Int ->
Bool ->
@ -440,78 +446,6 @@ prettyAllLines files withUnicode isError tabSize leftLen inline multiline lineNu
showMultilineMarkerMessages (m : ms) = showMultilineMarkerMessage m False : showMultilineMarkerMessages ms
in prefixWithBar colorOfLastMultilineMarker <> prefix <> fold (List.intersperse prefix $ showMultilineMarkerMessages $ reverse multiline)
-- <> {- (3) -} prettyAllLines files withUnicode isError tabSize leftLen inline multiline ls
-- TODO
prettyAllLines _ _ _ _ _ _ [] [] = mempty
prettyAllLines _ withUnicode isError _ leftLen _ multiline [] =
let colorOfLastMultilineMarker = maybe mempty (markerColor isError . snd) (List.safeLast multiline)
-- take the color of the last multiline marker in case we need to add additional bars
prefix = hardline <+> dotPrefix leftLen withUnicode <> space
prefixWithBar color = prefix <> annotate color (if withUnicode then "" else "| ")
showMultilineMarkerMessage (_, marker) isLast =
annotate (markerColor isError marker) $
( if isLast
then if withUnicode then "╰╸ " else "`- "
else if withUnicode then "├╸ " else "|- "
)
<> replaceLinesWith (if isLast then prefix <> " " else prefixWithBar (markerColor isError marker) <> space) (pretty $ markerMessage marker)
showMultilineMarkerMessages [] = []
showMultilineMarkerMessages [m] = [showMultilineMarkerMessage m True]
showMultilineMarkerMessages (m : ms) = showMultilineMarkerMessage m False : showMultilineMarkerMessages ms
in prefixWithBar colorOfLastMultilineMarker <> prefix <> fold (List.intersperse prefix $ showMultilineMarkerMessages $ reverse multiline)
prettyAllLines files withUnicode isError tabSize leftLen inline multiline (line : ls) =
{-
A line of code is composed of:
(1) <line> | <source code>
(2) : <markers>
(3) : <marker messages>
Multline markers may also take additional space (2 characters) on the right of the bar
-}
let allInlineMarkersInLine = snd =<< filter ((==) line . fst) inline
allMultilineMarkersInLine = flip filter multiline \(Position (bl, _) (el, _) _, _) -> bl == line || el == line
allMultilineMarkersSpanningLine = flip filter multiline \(Position (bl, _) (el, _) _, _) -> bl < line && el > line
inSpanOfMultiline = flip any multiline \(Position (bl, _) (el, _) _, _) -> bl <= line && el >= line
colorOfFirstMultilineMarker = maybe id (annotate . markerColor isError . snd) (List.safeHead $ allMultilineMarkersInLine <> allMultilineMarkersSpanningLine)
-- take the first multiline marker to color the entire line, if there is one
!additionalPrefix = case allMultilineMarkersInLine of
[] ->
if not $ null multiline
then
if not $ null allMultilineMarkersSpanningLine
then colorOfFirstMultilineMarker if withUnicode then "" else "| "
else " "
else mempty
(p@(Position _ (el, _) _), marker) : _ ->
let hasPredecessor = el == line || maybe False ((/=) p . fst . fst) (List.safeUncons multiline)
in colorOfFirstMultilineMarker
( if
| hasPredecessor && withUnicode -> ""
| hasPredecessor -> "|"
| withUnicode -> ""
| otherwise -> "+"
)
<> annotate (markerColor isError marker) (if withUnicode then "" else ">")
<> space
allMarkersInLine = {- List.sortOn fst $ -} allInlineMarkersInLine <> allMultilineMarkersInLine
(widths, renderedCode) = getLine_ files (allMarkersInLine <> allMultilineMarkersSpanningLine) line tabSize isError
in hardline
<> {- (1) -} linePrefix leftLen line withUnicode <+> additionalPrefix
<> renderedCode
<> {- (2) -} showAllMarkersInLine (not $ null multiline) inSpanOfMultiline colorOfFirstMultilineMarker withUnicode isError leftLen widths allInlineMarkersInLine
<> {- (3) -} prettyAllLines files withUnicode isError tabSize leftLen inline multiline ls
-- |
getLine_ :: HashMap FilePath [String] -> [(Position, Marker msg)] -> Int -> Int -> Bool -> (IntMap.HashMap Int Int, Doc AnsiStyle)
getLine_ files markers line tabSize isError = case List.safeIndex (line - 1) =<< (HashMap.!?) files . file . fst =<< List.safeHead markers of