mirror of
https://github.com/Mesabloo/diagnose.git
synced 2024-11-25 06:16:42 +03:00
Merge pull request #8 from JaSpa/perf-improvements
Performance improvements
This commit is contained in:
commit
5414562720
@ -1,6 +1,6 @@
|
|||||||
cabal-version: 1.12
|
cabal-version: 1.12
|
||||||
|
|
||||||
-- This file has been generated from package.yaml by hpack version 0.34.6.
|
-- This file has been generated from package.yaml by hpack version 0.34.4.
|
||||||
--
|
--
|
||||||
-- see: https://github.com/sol/hpack
|
-- see: https://github.com/sol/hpack
|
||||||
|
|
||||||
@ -65,8 +65,10 @@ library
|
|||||||
BlockArguments
|
BlockArguments
|
||||||
ghc-options: -Wall -Wextra
|
ghc-options: -Wall -Wextra
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.7 && <5
|
array ==0.5.*
|
||||||
|
, base >=4.7 && <5
|
||||||
, data-default >=0.7 && <1
|
, data-default >=0.7 && <1
|
||||||
|
, dlist ==1.0.*
|
||||||
, hashable >=1.3 && <2
|
, hashable >=1.3 && <2
|
||||||
, prettyprinter >=1.7.0 && <2
|
, prettyprinter >=1.7.0 && <2
|
||||||
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
||||||
@ -108,9 +110,11 @@ test-suite diagnose-megaparsec-tests
|
|||||||
BlockArguments
|
BlockArguments
|
||||||
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.7 && <5
|
array ==0.5.*
|
||||||
|
, base >=4.7 && <5
|
||||||
, data-default >=0.7 && <1
|
, data-default >=0.7 && <1
|
||||||
, diagnose
|
, diagnose
|
||||||
|
, dlist ==1.0.*
|
||||||
, hashable >=1.3 && <2
|
, hashable >=1.3 && <2
|
||||||
, prettyprinter >=1.7.0 && <2
|
, prettyprinter >=1.7.0 && <2
|
||||||
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
||||||
@ -147,9 +151,11 @@ test-suite diagnose-parsec-tests
|
|||||||
BlockArguments
|
BlockArguments
|
||||||
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.7 && <5
|
array ==0.5.*
|
||||||
|
, base >=4.7 && <5
|
||||||
, data-default >=0.7 && <1
|
, data-default >=0.7 && <1
|
||||||
, diagnose
|
, diagnose
|
||||||
|
, dlist ==1.0.*
|
||||||
, hashable >=1.3 && <2
|
, hashable >=1.3 && <2
|
||||||
, prettyprinter >=1.7.0 && <2
|
, prettyprinter >=1.7.0 && <2
|
||||||
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
||||||
@ -185,9 +191,11 @@ test-suite diagnose-rendering-tests
|
|||||||
BlockArguments
|
BlockArguments
|
||||||
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
ghc-options: -Wall -Wextra -threaded -rtsopts -with-rtsopts=-N
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.7 && <5
|
array ==0.5.*
|
||||||
|
, base >=4.7 && <5
|
||||||
, data-default >=0.7 && <1
|
, data-default >=0.7 && <1
|
||||||
, diagnose
|
, diagnose
|
||||||
|
, dlist ==1.0.*
|
||||||
, hashable >=1.3 && <2
|
, hashable >=1.3 && <2
|
||||||
, prettyprinter >=1.7.0 && <2
|
, prettyprinter >=1.7.0 && <2
|
||||||
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
, prettyprinter-ansi-terminal >=1.1.0 && <2
|
||||||
|
@ -8,11 +8,13 @@ category: "Error Reporting"
|
|||||||
|
|
||||||
dependencies:
|
dependencies:
|
||||||
- base >= 4.7 && < 5
|
- base >= 4.7 && < 5
|
||||||
|
- array >= 0.5 && < 0.6
|
||||||
|
- data-default >= 0.7 && < 1
|
||||||
|
- dlist >= 1.0 && < 1.1
|
||||||
|
- hashable >= 1.3 && < 2
|
||||||
- prettyprinter >= 1.7.0 && < 2
|
- prettyprinter >= 1.7.0 && < 2
|
||||||
- prettyprinter-ansi-terminal >= 1.1.0 && < 2
|
- prettyprinter-ansi-terminal >= 1.1.0 && < 2
|
||||||
- unordered-containers >= 0.2 && < 0.3
|
- unordered-containers >= 0.2 && < 0.3
|
||||||
- hashable >= 1.3 && < 2
|
|
||||||
- data-default >= 0.7 && < 1
|
|
||||||
- wcwidth >= 0.0.1 && <1
|
- wcwidth >= 0.0.1 && <1
|
||||||
- text >= 1.0.0.0 && <= 2.0
|
- text >= 1.0.0.0 && <= 2.0
|
||||||
# ^^^ This is unfortunately required, but as 'prettyprinter' already depends on it, it will already have been fetched
|
# ^^^ This is unfortunately required, but as 'prettyprinter' already depends on it, it will already have been fetched
|
||||||
|
@ -20,13 +20,16 @@ import Control.Monad.IO.Class (MonadIO, liftIO)
|
|||||||
import Data.Aeson (ToJSON(..), encode, object, (.=))
|
import Data.Aeson (ToJSON(..), encode, object, (.=))
|
||||||
import Data.ByteString.Lazy (ByteString)
|
import Data.ByteString.Lazy (ByteString)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
import Data.Array (listArray)
|
||||||
|
import Data.DList (DList)
|
||||||
|
import qualified Data.DList as DL
|
||||||
import Data.Default (Default, def)
|
import Data.Default (Default, def)
|
||||||
import Data.Foldable (fold)
|
import Data.Foldable (fold, toList)
|
||||||
import Data.HashMap.Lazy (HashMap)
|
|
||||||
import qualified Data.HashMap.Lazy as HashMap
|
import qualified Data.HashMap.Lazy as HashMap
|
||||||
import Data.List (intersperse)
|
import Data.List (intersperse)
|
||||||
import Error.Diagnose.Report (Report)
|
import Error.Diagnose.Report (Report)
|
||||||
import Error.Diagnose.Report.Internal (prettyReport)
|
import Error.Diagnose.Report.Internal (FileMap, prettyReport)
|
||||||
import Error.Diagnose.Style (Annotation, Style)
|
import Error.Diagnose.Style (Annotation, Style)
|
||||||
import Prettyprinter (Doc, Pretty, hardline, unAnnotate)
|
import Prettyprinter (Doc, Pretty, hardline, unAnnotate)
|
||||||
import Prettyprinter.Render.Terminal (hPutDoc)
|
import Prettyprinter.Render.Terminal (hPutDoc)
|
||||||
@ -38,11 +41,11 @@ import System.IO (Handle)
|
|||||||
-- to create a new empty diagnostic, and 'addFile' and 'addReport' to alter its internal state.
|
-- to create a new empty diagnostic, and 'addFile' and 'addReport' to alter its internal state.
|
||||||
data Diagnostic msg
|
data Diagnostic msg
|
||||||
= Diagnostic
|
= Diagnostic
|
||||||
[Report msg]
|
(DList (Report msg))
|
||||||
-- ^ All the reports contained in a diagnostic.
|
-- ^ All the reports contained in a diagnostic.
|
||||||
--
|
--
|
||||||
-- Reports are output one by one, without connections in between.
|
-- Reports are output one by one, without connections in between.
|
||||||
(HashMap FilePath [String])
|
!FileMap
|
||||||
-- ^ A map associating files with their content as lists of lines.
|
-- ^ A map associating files with their content as lists of lines.
|
||||||
|
|
||||||
instance Default (Diagnostic msg) where
|
instance Default (Diagnostic msg) where
|
||||||
@ -54,7 +57,7 @@ instance Semigroup (Diagnostic msg) where
|
|||||||
#ifdef USE_AESON
|
#ifdef USE_AESON
|
||||||
instance ToJSON msg => ToJSON (Diagnostic msg) where
|
instance ToJSON msg => ToJSON (Diagnostic msg) where
|
||||||
toJSON (Diagnostic reports files) =
|
toJSON (Diagnostic reports files) =
|
||||||
object [ "files" .= fmap toJSONFile (HashMap.toList files)
|
object [ "files" .= fmap toJSONFile (fmap toList <$> (HashMap.toList files))
|
||||||
, "reports" .= reports
|
, "reports" .= reports
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
@ -85,7 +88,7 @@ prettyDiagnostic ::
|
|||||||
Diagnostic msg ->
|
Diagnostic msg ->
|
||||||
Doc Annotation
|
Doc Annotation
|
||||||
prettyDiagnostic withUnicode tabSize (Diagnostic reports file) =
|
prettyDiagnostic withUnicode tabSize (Diagnostic reports file) =
|
||||||
fold . intersperse hardline $ prettyReport file withUnicode tabSize <$> reports
|
fold . intersperse hardline $ prettyReport file withUnicode tabSize <$> toList reports
|
||||||
{-# INLINE prettyDiagnostic #-}
|
{-# INLINE prettyDiagnostic #-}
|
||||||
|
|
||||||
-- | Prints a 'Diagnostic' onto a specific 'Handle'.
|
-- | Prints a 'Diagnostic' onto a specific 'Handle'.
|
||||||
@ -117,7 +120,10 @@ addFile ::
|
|||||||
String ->
|
String ->
|
||||||
Diagnostic msg
|
Diagnostic msg
|
||||||
addFile (Diagnostic reports files) path content =
|
addFile (Diagnostic reports files) path content =
|
||||||
Diagnostic reports (HashMap.insert path (lines content) files)
|
let fileLines = lines content
|
||||||
|
lineCount = length fileLines
|
||||||
|
lineArray = listArray (0, lineCount - 1) fileLines
|
||||||
|
in Diagnostic reports (HashMap.insert path lineArray files)
|
||||||
{-# INLINE addFile #-}
|
{-# INLINE addFile #-}
|
||||||
|
|
||||||
-- | Inserts a new report into a diagnostic.
|
-- | Inserts a new report into a diagnostic.
|
||||||
@ -127,7 +133,7 @@ addReport ::
|
|||||||
Report msg ->
|
Report msg ->
|
||||||
Diagnostic msg
|
Diagnostic msg
|
||||||
addReport (Diagnostic reports files) report =
|
addReport (Diagnostic reports files) report =
|
||||||
Diagnostic (reports <> [report]) files
|
Diagnostic (reports `DL.snoc` report) files
|
||||||
{-# INLINE addReport #-}
|
{-# INLINE addReport #-}
|
||||||
|
|
||||||
#ifdef USE_AESON
|
#ifdef USE_AESON
|
||||||
|
@ -25,6 +25,8 @@ module Error.Diagnose.Report.Internal where
|
|||||||
import Data.Aeson (ToJSON(..), object, (.=))
|
import Data.Aeson (ToJSON(..), object, (.=))
|
||||||
#endif
|
#endif
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
|
import qualified Data.Array.IArray as Array
|
||||||
|
import Data.Array.Unboxed (Array, IArray, Ix, UArray, listArray, (!))
|
||||||
import Data.Bifunctor (bimap, first, second)
|
import Data.Bifunctor (bimap, first, second)
|
||||||
import Data.Char.WCWidth (wcwidth)
|
import Data.Char.WCWidth (wcwidth)
|
||||||
import Data.Default (def)
|
import Data.Default (def)
|
||||||
@ -33,9 +35,9 @@ import Data.Function (on)
|
|||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Data.HashMap.Lazy (HashMap)
|
import Data.HashMap.Lazy (HashMap)
|
||||||
import qualified Data.HashMap.Lazy as HashMap
|
import qualified Data.HashMap.Lazy as HashMap
|
||||||
import qualified Data.HashMap.Lazy as IntMap
|
|
||||||
import qualified Data.List as List
|
import qualified Data.List as List
|
||||||
import qualified Data.List.Safe as List
|
import qualified Data.List.Safe as List
|
||||||
|
import Data.Maybe
|
||||||
import Data.Ord (Down (Down))
|
import Data.Ord (Down (Down))
|
||||||
import Data.String (IsString (fromString))
|
import Data.String (IsString (fromString))
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
@ -44,6 +46,10 @@ import Error.Diagnose.Style (Annotation (..))
|
|||||||
import Prettyprinter (Doc, Pretty (..), align, annotate, colon, hardline, lbracket, rbracket, space, width, (<+>))
|
import Prettyprinter (Doc, Pretty (..), align, annotate, colon, hardline, lbracket, rbracket, space, width, (<+>))
|
||||||
import Prettyprinter.Internal (Doc (..))
|
import Prettyprinter.Internal (Doc (..))
|
||||||
|
|
||||||
|
type FileMap = HashMap FilePath (Array Int String)
|
||||||
|
|
||||||
|
type WidthTable = UArray Int Int
|
||||||
|
|
||||||
-- | The type of diagnostic reports with abstract message type.
|
-- | The type of diagnostic reports with abstract message type.
|
||||||
data Report msg
|
data Report msg
|
||||||
= Report
|
= Report
|
||||||
@ -153,7 +159,7 @@ err = Report True
|
|||||||
prettyReport ::
|
prettyReport ::
|
||||||
Pretty msg =>
|
Pretty msg =>
|
||||||
-- | The content of the file the reports are for
|
-- | The content of the file the reports are for
|
||||||
HashMap FilePath [String] ->
|
FileMap ->
|
||||||
-- | Should we print paths in unicode?
|
-- | Should we print paths in unicode?
|
||||||
Bool ->
|
Bool ->
|
||||||
-- | The number of spaces each TAB character will span
|
-- | The number of spaces each TAB character will span
|
||||||
@ -310,7 +316,7 @@ groupMarkersPerFile markers =
|
|||||||
prettySubReport ::
|
prettySubReport ::
|
||||||
Pretty msg =>
|
Pretty msg =>
|
||||||
-- | The content of files in the diagnostics
|
-- | The content of files in the diagnostics
|
||||||
HashMap FilePath [String] ->
|
FileMap ->
|
||||||
-- | Is the output done with Unicode characters?
|
-- | Is the output done with Unicode characters?
|
||||||
Bool ->
|
Bool ->
|
||||||
-- | Is the current report an error report?
|
-- | Is the current report an error report?
|
||||||
@ -367,7 +373,7 @@ splitMarkersPerLine (m@(Position {..}, _) : ms) =
|
|||||||
-- |
|
-- |
|
||||||
prettyAllLines ::
|
prettyAllLines ::
|
||||||
Pretty msg =>
|
Pretty msg =>
|
||||||
HashMap FilePath [String] ->
|
FileMap ->
|
||||||
Bool ->
|
Bool ->
|
||||||
Bool ->
|
Bool ->
|
||||||
-- | The number of spaces each TAB character will span
|
-- | The number of spaces each TAB character will span
|
||||||
@ -467,34 +473,48 @@ prettyAllLines files withUnicode isError tabSize leftLen inline multiline lineNu
|
|||||||
in prefixWithBar colorOfFirstMultilineMarker <> prefix <> fold (List.intersperse prefix $ showMultilineMarkerMessages multiline)
|
in prefixWithBar colorOfFirstMultilineMarker <> prefix <> fold (List.intersperse prefix $ showMultilineMarkerMessages multiline)
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
getLine_ :: HashMap FilePath [String] -> [(Position, Marker msg)] -> Int -> Int -> Bool -> (IntMap.HashMap Int Int, Doc Annotation)
|
getLine_ ::
|
||||||
getLine_ files markers line tabSize isError = case List.safeIndex (line - 1) =<< (HashMap.!?) files . file . fst =<< List.safeHead markers of
|
FileMap ->
|
||||||
Nothing -> (mempty, annotate NoLineColor "<no line>")
|
[(Position, Marker msg)] ->
|
||||||
Just code ->
|
Int ->
|
||||||
let (tabs, code') = indexedWithTabsReplaced code
|
Int ->
|
||||||
in ( tabs,
|
Bool ->
|
||||||
fold $
|
(WidthTable, Doc Annotation)
|
||||||
code' <&> \(n, c) ->
|
getLine_ files markers line tabSize isError =
|
||||||
let colorizingMarkers = flip
|
case safeArrayIndex (line - 1) =<< (HashMap.!?) files . file . fst =<< List.safeHead markers of
|
||||||
filter
|
Nothing ->
|
||||||
markers
|
( mkWidthTable "",
|
||||||
\(Position (bl, bc) (el, ec) _, _) ->
|
annotate NoLineColor "<no line>"
|
||||||
if bl == el
|
)
|
||||||
then n >= bc && n < ec
|
Just code ->
|
||||||
else (bl == line && n >= bc) || (el == line && n < ec) || (bl < line && el > line)
|
( mkWidthTable code,
|
||||||
in maybe id ((\m -> annotate (MarkerStyle $ markerColor isError m)) . snd) (List.safeHead colorizingMarkers) (pretty c)
|
flip foldMap (zip [1 ..] code) \(n, c) ->
|
||||||
)
|
let cdoc =
|
||||||
|
ifTab (pretty (replicate tabSize ' ')) pretty c
|
||||||
|
colorizingMarkers = flip filter markers \case
|
||||||
|
(Position (bl, bc) (el, ec) _, _)
|
||||||
|
| bl == el ->
|
||||||
|
n >= bc && n < ec
|
||||||
|
| otherwise ->
|
||||||
|
(bl == line && n >= bc)
|
||||||
|
|| (el == line && n < ec)
|
||||||
|
|| (bl < line && el > line)
|
||||||
|
in maybe
|
||||||
|
id
|
||||||
|
((\m -> annotate (MarkerStyle $ markerColor isError m)) . snd)
|
||||||
|
(List.safeHead colorizingMarkers)
|
||||||
|
cdoc
|
||||||
|
)
|
||||||
where
|
where
|
||||||
indexedWithTabsReplaced :: String -> (IntMap.HashMap Int Int, [(Int, Char)])
|
ifTab :: a -> (Char -> a) -> Char -> a
|
||||||
indexedWithTabsReplaced = goIndexed 1
|
ifTab a _ '\t' = a
|
||||||
|
ifTab _ f c = f c
|
||||||
|
|
||||||
goIndexed :: Int -> String -> (IntMap.HashMap Int Int, [(Int, Char)])
|
mkWidthTable :: String -> WidthTable
|
||||||
goIndexed _ [] = (mempty, [])
|
mkWidthTable s = listArray (1, length s) (ifTab tabSize wcwidth <$> s)
|
||||||
goIndexed n ('\t' : xs) = bimap (IntMap.insert n tabSize) (replicate tabSize (n, ' ') <>) (goIndexed (n + 1) xs)
|
|
||||||
goIndexed n (x : xs) = bimap (IntMap.insert n (wcwidth x)) ((n, x) :) (goIndexed (n + 1) xs)
|
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
showAllMarkersInLine :: Pretty msg => Bool -> Bool -> (Doc Annotation -> Doc Annotation) -> Bool -> Bool -> Int -> IntMap.HashMap Int Int -> [(Position, Marker msg)] -> Doc Annotation
|
showAllMarkersInLine :: Pretty msg => Bool -> Bool -> (Doc Annotation -> Doc Annotation) -> Bool -> Bool -> Int -> WidthTable -> [(Position, Marker msg)] -> Doc Annotation
|
||||||
showAllMarkersInLine _ _ _ _ _ _ _ [] = mempty
|
showAllMarkersInLine _ _ _ _ _ _ _ [] = mempty
|
||||||
showAllMarkersInLine hasMultilines inSpanOfMultiline colorMultilinePrefix withUnicode isError leftLen widths ms =
|
showAllMarkersInLine hasMultilines inSpanOfMultiline colorMultilinePrefix withUnicode isError leftLen widths ms =
|
||||||
let maxMarkerColumn = snd $ end $ fst $ List.last $ List.sortOn (snd . end . fst) ms
|
let maxMarkerColumn = snd $ end $ fst $ List.last $ List.sortOn (snd . end . fst) ms
|
||||||
@ -505,19 +525,23 @@ showAllMarkersInLine hasMultilines inSpanOfMultiline colorMultilinePrefix withUn
|
|||||||
in -- get the maximum end column, so that we know when to stop looking for other markers on the same line
|
in -- get the maximum end column, so that we know when to stop looking for other markers on the same line
|
||||||
hardline <+> dotPrefix leftLen withUnicode <+> (if List.null ms then mempty else specialPrefix <> showMarkers 1 maxMarkerColumn <> showMessages specialPrefix ms maxMarkerColumn)
|
hardline <+> dotPrefix leftLen withUnicode <+> (if List.null ms then mempty else specialPrefix <> showMarkers 1 maxMarkerColumn <> showMessages specialPrefix ms maxMarkerColumn)
|
||||||
where
|
where
|
||||||
|
widthAt i = 0 `fromMaybe` safeArrayIndex i widths
|
||||||
|
widthsBetween start end =
|
||||||
|
sum $ take (end - start) $ drop (start - 1) $ Array.elems widths
|
||||||
|
|
||||||
showMarkers n lineLen
|
showMarkers n lineLen
|
||||||
| n > lineLen = mempty -- reached the end of the line
|
| n > lineLen = mempty -- reached the end of the line
|
||||||
| otherwise =
|
| otherwise =
|
||||||
let allMarkers = flip filter ms \(Position (_, bc) (_, ec) _, _) -> n >= bc && n < ec
|
let allMarkers = flip filter ms \(Position (_, bc) (_, ec) _, _) -> n >= bc && n < ec
|
||||||
in -- only consider markers which span onto the current column
|
in -- only consider markers which span onto the current column
|
||||||
case allMarkers of
|
case allMarkers of
|
||||||
[] -> fold (replicate (IntMap.lookupDefault 0 n widths) space) <> showMarkers (n + 1) lineLen
|
[] -> fold (replicate (widthAt n) space) <> showMarkers (n + 1) lineLen
|
||||||
(Position {..}, marker) : _ ->
|
(Position {..}, marker) : _ ->
|
||||||
annotate
|
annotate
|
||||||
(markerColor isError marker)
|
(markerColor isError marker)
|
||||||
( if snd begin == n
|
( if snd begin == n
|
||||||
then (if withUnicode then "┬" else "^") <> fold (replicate (IntMap.lookupDefault 0 n widths - 1) if withUnicode then "─" else "-")
|
then (if withUnicode then "┬" else "^") <> fold (replicate (widthAt n - 1) if withUnicode then "─" else "-")
|
||||||
else fold (replicate (IntMap.lookupDefault 0 n widths) if withUnicode then "─" else "-")
|
else fold (replicate (widthAt n) if withUnicode then "─" else "-")
|
||||||
)
|
)
|
||||||
<> showMarkers (n + 1) lineLen
|
<> showMarkers (n + 1) lineLen
|
||||||
|
|
||||||
@ -532,15 +556,15 @@ showAllMarkersInLine hasMultilines inSpanOfMultiline colorMultilinePrefix withUn
|
|||||||
allColumns _ [] = (1, [])
|
allColumns _ [] = (1, [])
|
||||||
allColumns n ms@((Position (_, bc) _ _, col) : ms')
|
allColumns n ms@((Position (_, bc) _ _, col) : ms')
|
||||||
| n == bc = bimap (+ 1) (col :) (allColumns (n + 1) ms')
|
| n == bc = bimap (+ 1) (col :) (allColumns (n + 1) ms')
|
||||||
| n < bc = bimap (+ 1) (replicate (IntMap.lookupDefault 0 n widths) space <>) (allColumns (n + 1) ms)
|
| n < bc = bimap (+ 1) (replicate (widthAt n) space <>) (allColumns (n + 1) ms)
|
||||||
| otherwise = bimap (+ 1) (replicate (IntMap.lookupDefault 0 n widths) space <>) (allColumns (n + 1) ms')
|
| otherwise = bimap (+ 1) (replicate (widthAt n) space <>) (allColumns (n + 1) ms')
|
||||||
-- transform the list of remaining markers into a single document line
|
-- transform the list of remaining markers into a single document line
|
||||||
|
|
||||||
hasSuccessor = length filteredPipes /= length pipes
|
hasSuccessor = length filteredPipes /= length pipes
|
||||||
|
|
||||||
lineStart pipes =
|
lineStart pipes =
|
||||||
let (n, docs) = allColumns 1 $ List.sortOn (snd . begin . fst) pipes
|
let (n, docs) = allColumns 1 $ List.sortOn (snd . begin . fst) pipes
|
||||||
numberOfSpaces = sum [IntMap.lookupDefault 0 x widths | x <- [n .. bc - 1]] -- bc - n
|
numberOfSpaces = widthsBetween n bc
|
||||||
in dotPrefix leftLen withUnicode <+> specialPrefix <> fold docs <> pretty (replicate numberOfSpaces ' ')
|
in dotPrefix leftLen withUnicode <+> specialPrefix <> fold docs <> pretty (replicate numberOfSpaces ' ')
|
||||||
-- the start of the line contains the "dot"-prefix as well as all the pipes for all the still not rendered marker messages
|
-- the start of the line contains the "dot"-prefix as well as all the pipes for all the still not rendered marker messages
|
||||||
|
|
||||||
@ -555,7 +579,7 @@ showAllMarkersInLine hasMultilines inSpanOfMultiline colorMultilinePrefix withUn
|
|||||||
|
|
||||||
lineLen = case lastBeginPosition of
|
lineLen = case lastBeginPosition of
|
||||||
Nothing -> 0
|
Nothing -> 0
|
||||||
Just col -> sum [IntMap.lookupDefault 0 x widths | x <- [bc .. col - 1]]
|
Just col -> widthsBetween bc col
|
||||||
|
|
||||||
currentPipe =
|
currentPipe =
|
||||||
if
|
if
|
||||||
@ -639,3 +663,8 @@ prettyAllHints (h : hs) leftLen withUnicode =
|
|||||||
|
|
||||||
noteMessage (Note msg) = msg
|
noteMessage (Note msg) = msg
|
||||||
noteMessage (Hint msg) = msg
|
noteMessage (Hint msg) = msg
|
||||||
|
|
||||||
|
safeArrayIndex :: (Ix i, IArray a e) => i -> a i e -> Maybe e
|
||||||
|
safeArrayIndex i a
|
||||||
|
| Array.inRange (Array.bounds a) i = Just (a ! i)
|
||||||
|
| otherwise = Nothing
|
||||||
|
Loading…
Reference in New Issue
Block a user