errata-0.4.0.0: Source code error pretty printing
Copyright(c) 2020- comp
LicenseMIT
Maintaineronecomputer00@gmail.com
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Errata

Description

This module is for creating pretty error messages. We assume very little about the format you want to use, so much of this module is to allow you to customize your error messages.

To get started, see the documentation for prettyErrors. When using this module, we recommend you turn on the OverloadedStrings extension and import Data.Text at the very least due to the use of Text (strict).

The overall workflow to use the printer is to convert your error type to Errata, which entails filling in messages and Blocks. You can create Errata and Block from their constructors, or use the convenience functions for common usecases, like errataSimple and blockSimple.

For premade styles for blocks and pointers, take a look at Errata.Styles.

For easier reading, we define:

type Line = Int
type Column = Int
type Header = Text
type Body = Text
type Label = Text
Synopsis

Error format data

data Errata Source #

A collection of information for pretty printing an error.

Constructors

Errata 

Fields

Instances

Instances details
Show Errata Source # 
Instance details

Defined in Errata.Types

errataSimple Source #

Arguments

:: Maybe Header

The header.

-> Block

The block.

-> Maybe Body

The body.

-> Errata 

Creates a simple error that has a single block, with an optional header or body.

Blocks and pointers

data Block Source #

Information about a block in the source code, such as pointers and messages.

Each block has a style associated with it.

Constructors

Block 

Fields

  • blockStyle :: Style

    The style of the block.

  • blockLocation :: (FilePath, Line, Column)

    The filepath, line, and column of the block. These start at 1.

    This is used to create the text that details the location.

  • blockHeader :: Maybe Header

    The header message for the block.

    This will appear below the location and above the source lines.

  • blockPointers :: [Pointer]

    The block's pointers. These are used to "point out" parts of the source code in this block.

    The locations of each of these pointers must be non-overlapping. If the pointers are touching at a boundary however, that is allowed.

  • blockBody :: Maybe Body

    The body message for the block.

    This will appear below the source lines.

Instances

Instances details
Show Block Source # 
Instance details

Defined in Errata.Types

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

blockSimple Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Column, Maybe Label)

The line number and column span, starting at 1, and a label.

-> Maybe Body

The body message.

-> Block 

A simple block that points to only one line and optionally has a label, header, or body message.

blockSimple' Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Maybe Label)

The line number and column, starting at 1, and a label.

-> Maybe Body

The body message.

-> Block 

A variant of blockSimple that only points at one column.

blockConnected Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Column, Maybe Label)

The first line number and column span, starting at 1, and a label.

-> (Line, Column, Column, Maybe Label)

The second line number and column span, starting at 1, and a label.

-> Maybe Body

The body message.

-> Block 

A block that points to two parts of the source that are visually connected together.

blockConnected' Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Maybe Label)

The first line number and column, starting at 1, and a label.

-> (Line, Column, Maybe Label)

The second line number and column, starting at 1, and a label.

-> Maybe Body

The body message.

-> Block 

A variant of blockConnected where the pointers point at only one column.

blockMerged Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Column, Maybe Label)

The first line number and column span, starting at 1, and a label.

-> (Line, Column, Column, Maybe Label)

The second line number and column span, starting at 1, and a label.

-> Maybe Label

The label for when the two pointers are merged into one.

-> Maybe Body

The body message.

-> Block 

A block that points to two parts of the source that are visually connected together.

If the two parts of the source happen to be on the same line, the pointers are merged into one.

blockMerged' Source #

Arguments

:: Style

The style of the block.

-> PointerStyle

The style of the pointer.

-> FilePath

The filepath.

-> Maybe Header

The header message.

-> (Line, Column, Maybe Label)

The first line number and column, starting at 1, and a label.

-> (Line, Column, Maybe Label)

The second line number and column, starting at 1, and a label.

-> Maybe Label

The label for when the two pointers are merged into one.

-> Maybe Body

The body message.

-> Block 

A variant of blockMerged where the pointers point at only one column.

data Pointer Source #

A pointer is the span of the source code at a line, from one column to another. Each of the positions start at 1.

A pointer may also have a label that will display inline.

A pointer may also be connected to all the other pointers within the same block.

Constructors

Pointer 

Fields

Instances

Instances details
Show Pointer Source # 
Instance details

Defined in Errata.Types

Styling options

data Style Source #

Stylization options for a block, e.g. characters to use.

Constructors

Style 

Fields

  • styleLocation :: (FilePath, Line, Column) -> Text

    Shows the location of a block at a file, line, and column.

    This is put on its own line just above the source lines.

  • styleNumber :: Line -> Text

    Shows the line number n for a source line.

    The result should visually be the same length as just show n.

  • styleLine :: [(PointerStyle, (Column, Column))] -> Text -> Text

    Stylize a source line.

    The style and the column span (sorted, starting at 1) of the text that is being underlined are given for highlighting purposes (see highlight). They can be ignored for source code highlighting instead, for example. The result of this should visually take up the same space as the original line.

  • styleEllipsis :: Text

    The text to use as an ellipsis in the position of line numbers for when lines are omitted.

    This should visually be one character.

  • styleLinePrefix :: Text

    The prefix before the source lines.

    Before it may be the line number, and after it the source line.

  • styleVertical :: Text

    The text to use as a vertical bar when connecting pointers.

    This should visually be one character.

  • styleHorizontal :: Text

    The text to use as a horizontal bar when connecting pointers.

    This should visually be one character.

  • styleDownRight :: Text

    The text to use as a connector downwards and rightwards when connecting pointers.

    This should visually be one character.

  • styleUpRight :: Text

    The text to use as a connector upwards and rightwards when connecting pointers.

    This should visually be one character.

  • styleUpDownRight :: Text

    The text to use as a connector upwards, downwards, and rightwards when connecting pointers.

    This should visually be one character.

  • styleTabWidth :: Int

    The number of spaces a tab character is equivalent to.

    Your source will have tabs replaced with this many spaces.

  • styleExtraLinesAfter :: Int

    Maximum number of extra lines that can be added after the first line when skipping lines between two lines.

  • styleExtraLinesBefore :: Int

    Maximum number of extra lines that can be added before the second line when skipping lines between two lines.

  • stylePaddingTop :: Bool

    Whether to add a padding line before the first source line.

  • stylePaddingBottom :: Bool

    Whether to add a padding line after the last source line.

  • styleEnableDecorations :: Bool

    Whether to enable decorations at all in this block.

    This includes the pointer connectors (as in Style) and the underlines, connectors, and labels (as in PointerStyle). However, highlighting will still be applied.

  • styleEnableLinePrefix :: Bool

    Whether to enable the line prefix.

Instances

Instances details
Show Style Source # 
Instance details

Defined in Errata.Types

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

data PointerStyle Source #

Stylization options for an individual pointer, e.g. characters to use.

Constructors

PointerStyle 

Fields

  • styleHighlight :: Text -> Text

    Stylize the text that this pointer is underlining.

    This is only used if styleLine uses the given pointer styles, for example with highlight. The result of this should visually take up the same space as the original text.

  • styleUnderline :: Text

    The text to underline a character in a pointer.

    This should visually be one character.

  • styleHook :: Text

    The text to use as a connector upwards and hooking to the right for the label of a pointer that drops down.

    This probably looks best as one character.

  • styleConnector :: Text

    The text to use as a vertical bar when connecting a pointer that drops down to its label.

    This should visually be one character.

  • styleEnableHook :: Bool

    Whether to use the hook for labels that drop down, or simply start the label directly under the connector.

Instances

Instances details
Show PointerStyle Source # 
Instance details

Defined in Errata.Types

Pretty printer

prettyErrors :: Source source => source -> [Errata] -> Text Source #

Pretty prints errors. The original source is required. Returns Text (lazy). If the list is empty, an empty string is returned.

Suppose we had an error of this type:

data ParseError = ParseError
    { peFile       :: FilePath
    , peLine       :: Int
    , peCol        :: Int
    , peUnexpected :: T.Text
    , peExpected   :: [T.Text]
    }

Then we can create a simple pretty printer like so:

import qualified Data.Text as T
import qualified Data.Text.Lazy.IO as TL
import           Errata

toErrata :: ParseError -> Errata
toErrata (ParseError fp l c unexpected expected) =
    errataSimple
        (Just "an error occured!")
        (blockSimple basicStyle basicPointer fp
            (Just "error: invalid syntax")
            (l, c, c + T.length unexpected, Just "this one")
            (Just $ "unexpected " <> unexpected <> "\nexpected " <> T.intercalate ", " expected))
        Nothing

printErrors :: T.Text -> [ParseError] -> IO ()
printErrors source es = TL.putStrLn $ prettyErrors source (map toErrata es)

Note that in the above example, we have OverloadedStrings enabled to reduce uses of pack.

An example error message from this might be:

an error occured!
--> ./comma.json:2:18
error: invalid syntax
  |
2 |     "bad": [1, 2,]
  |                  ^ this one
unexpected ]
expected null, true, false, ", -, digit, [, {