portray-prettyprinter-0.2.0: A portray backend using the prettyprinter package.
Safe HaskellNone
LanguageHaskell2010

Data.Portray.Prettyprinter

Description

Provides rendering of Portrayal to Doc.

There are two intended uses of this module: firstly, to use prettyprinter's layout and rendering algorithms to render Portray instances, Diffs, or other Portrayals; and secondly, to derive Pretty instances based on existing Portray instances. I find the former more ergonomic, but in established codebases that want to benefit from deriving, the latter may be more achievable.

The first usage is for codebases with pervasive use of Portray, and involves using e.g. pp and ppd in GHCi, or showPortrayal or showDiff in application code. With this usage, anything you want to pretty-print needs a Portray instance, and the typeclass Pretty is not involved in any way. With this approach, pretty-printable types and the types they include should derive only Portray, and pretty-printing should be done with the aforementioned utility functions:

data MyRecord = MyRecord { anInt :: Int, anotherRecord :: MyOtherRecord }
  deriving Generic
  deriving Portray via Wrapped Generic MyRecord

example = showPortrayal (MyRecord 2 ...)

This usage provides colorized pretty-printing by default with pp. Note if you don't like the default choice of colors or don't want colors at all, you can roll your own pp function with portray, toDocAssocPrec and your prettyprinter rendering backend of choice.

The second usage is to use portray's generic deriving to provide derived Pretty instances, in a codebase that uses Pretty as the preferred typeclass for pretty-printable values. With this usage, things you want to pretty-print need Pretty instances, and Portray is needed for the transitive closure of types included in types you want to derive Pretty instances for. This may result in many types needing both instances of both Pretty (for direct pretty-printing) and Portray (for deriving Portray on downstream types) instances. Note that with this approach, types that derive their Pretty instances via Portray will ignore any custom Pretty instances of nested types, since they recurse to nested Portray instances instead.

To derive an instance for a pretty-printable type, the type itself should look like the following:

data MyRecord = MyRecord { anInt :: Int, anotherRecord :: MyOtherRecord }
  deriving Generic
  deriving Portray via Wrapped Generic MyRecord
  deriving Pretty via WrappedPortray MyRecord

example = renderStrict $ pretty (MyRecord 2 ...)

And any types transitively included in it should look like the following:

data MyOtherRecord = MyOtherRecord
  deriving Generic
  deriving Portray via Wrapped Generic MyRecord

Since the Pretty class requires a universally-quantified annotation type, its instances cannot provide any annotations. As such, this usage cannot provide automatic colorization.

This module also exports the underlying rendering functionality in a variety of forms for more esoteric uses.

Synopsis

Pretty-Printing

showPortrayal :: Portray a => a -> Text Source #

Pretty-print a value using its Portray instance.

This uses no ANSI terminal escape codes and escapes all non-ASCII characters.

pp :: Portray a => a -> IO () Source #

Pretty-print a value to stdout using its Portray instance.

This uses ANSI color codes, so take care not to use it in contexts where it might output to something other than a terminal.

Diffing

showDiff :: Diff a => a -> a -> Text Source #

Pretty-print a diff between two values using a Diff instance.

This uses no ANSI terminal escape codes and escapes all non-ASCII characters.

ppd :: Diff a => a -> a -> IO () Source #

Pretty-print a diff between two values to stdout using a Diff instance.

This uses ANSI color codes, so take care not to use it in contexts where it might output to something other than a terminal.

DerivingVia wrapper

newtype WrappedPortray a Source #

A newtype providing a Pretty instance via Portray, for DerivingVia.

Sadly we can't use Wrapped since it would be an orphan instance. Oh well. We'll just define a unique WrappedPortray newtype in each pretty-printer-integration package.

Constructors

WrappedPortray 

Fields

Instances

Instances details
Eq a => Eq (WrappedPortray a) Source # 
Instance details

Defined in Data.Portray.Prettyprinter

Ord a => Ord (WrappedPortray a) Source # 
Instance details

Defined in Data.Portray.Prettyprinter

Show a => Show (WrappedPortray a) Source # 
Instance details

Defined in Data.Portray.Prettyprinter

Portray a => Pretty (WrappedPortray a) Source #

Provide an instance for Pretty by way of Portray.

Instance details

Defined in Data.Portray.Prettyprinter

Methods

pretty :: WrappedPortray a -> Doc ann #

prettyList :: [WrappedPortray a] -> Doc ann #

Rendering

Configuration

data Config Source #

Configuration for the conversion to Doc.

Includes the following:

  • setShouldEscapeChar, a function determining whether an escapable character should be escaped in a string or character literal. Unprintable characters, backslashes, and the relevant quote for the current literal type are always escaped, and anything that wouldn't be escaped by Show is never escaped.

For forwards-compatibility reasons, the field selectors and constructor of this type are hidden; use the provided setters to build a config. For example:

config =
  defaultConfig
    & setShouldEscapeChar (const True) -- Escape everything we can.

defaultConfig :: Config Source #

A sensible default configuration to build on.

Uses escapeNonASCII.

Escape Sequences

setShouldEscapeChar :: (Char -> Bool) -> Config -> Config Source #

Set the predicate for whether to escape a given character; see Config.

escapeNonASCII :: Char -> Bool Source #

An escape-sequence predicate to escape any non-ASCII character.

escapeSpecialOnly :: Char -> Bool Source #

An escape-sequence predicate to escape as little as possible.

Colorization

data SyntaxClass Source #

The kind of syntactic element represented by an annotated Doc.

Constructors

Identifier IdentKind

Identifiers, whether alphanumeric names or operators.

Literal LitKind

Literals, including integers, floats/rationals, chars, and strings.

EscapeSequence

Escaped characters in strings and char literals.

Keyword

Alphanumeric keywords, e.g. case.

Bracket

Matched pairs of symbols that denote nesting, e.g. parens.

Separator

Syntactic separators/terminators, e.g. , and ;.

Structural

Other fixed syntactic symbols, e.g. ::, @, ->, \.

data LitKind Source #

The particular kind of literal represented by a Literal.

Constructors

IntLit 
RatLit 
CharLit 
StrLit 

defaultStyling :: SyntaxClass -> Maybe AnsiStyle Source #

A fairly arbitrary colorization style based on what looked good to me.

To use a custom color mapping, define it the same way this function is defined, then use it as an argument to styleShowPortrayal. Consider also wrapping that up into a custom pp function for use at the REPL or even as the interactive print function.

subtleStyling :: SyntaxClass -> Maybe AnsiStyle Source #

A subtler style that colorizes only operators (blue) and literals (cyan).

noStyling :: SyntaxClass -> Maybe AnsiStyle Source #

Disable all syntax highlighting.

With Associativity

type DocAssocPrec ann = Assoc -> Rational -> Doc ann Source #

A Doc that varies according to associativity and precedence context.

toDocAssocPrec :: Config -> Portrayal -> DocAssocPrec SyntaxClass Source #

Render a Portrayal to a Doc with support for operator associativity.

Convenience Functions

styleShowPortrayal :: Config -> (SyntaxClass -> Maybe AnsiStyle) -> Portrayal -> Text Source #

Convenience function for rendering a Portrayal to stylized Text.

prettyShowPortrayal :: Portrayal -> Text Source #

Convenience function for rendering a Portrayal to colorized Text.

basicShowPortrayal :: Portrayal -> Text Source #

Convenience function for rendering a Portrayal to a Text.