swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Pretty

Description

Common pretty-printing infrastructure for the Swarm project.

Synopsis

The PrettyPrec class

class PrettyPrec a where Source #

Type class for things that can be pretty-printed, given a precedence level of their context.

Methods

prettyPrec :: Int -> a -> Doc ann Source #

Instances

Instances details
PrettyPrec Asset Source # 
Instance details

Defined in Swarm.Failure

Methods

prettyPrec :: Int -> Asset -> Doc ann Source #

PrettyPrec AssetData Source # 
Instance details

Defined in Swarm.Failure

Methods

prettyPrec :: Int -> AssetData -> Doc ann Source #

PrettyPrec Entry Source # 
Instance details

Defined in Swarm.Failure

Methods

prettyPrec :: Int -> Entry -> Doc ann Source #

PrettyPrec LoadingFailure Source # 
Instance details

Defined in Swarm.Failure

Methods

prettyPrec :: Int -> LoadingFailure -> Doc ann Source #

PrettyPrec OrderFileWarning Source # 
Instance details

Defined in Swarm.Failure

PrettyPrec SystemFailure Source # 
Instance details

Defined in Swarm.Failure

Methods

prettyPrec :: Int -> SystemFailure -> Doc ann Source #

PrettyPrec Direction Source # 
Instance details

Defined in Swarm.Language.Syntax.Direction

Methods

prettyPrec :: Int -> Direction -> Doc ann Source #

PrettyPrec Wildcard Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> Wildcard -> Doc ann Source #

PrettyPrec Text Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> Text -> Doc ann Source #

PrettyPrec (t (Fix t)) => PrettyPrec (Fix t) Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> Fix t -> Doc ann Source #

PrettyPrec i => PrettyPrec (BulletList i) Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> BulletList i -> Doc ann Source #

(PrettyPrec (t (Free t v)), PrettyPrec v) => PrettyPrec (Free t v) Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> Free t v -> Doc ann Source #

Running pretty-printers

ppr :: PrettyPrec a => a -> Doc ann Source #

Pretty-print a thing, with a context precedence level of zero.

prettyText :: PrettyPrec a => a -> Text Source #

Pretty-print something and render it as Text.

prettyTextWidth :: PrettyPrec a => a -> Int -> Text Source #

Pretty-print something and render it as Text. This is different than prettyText in the sense that it also consumes number of allowed characters in a line before introducing a line break.

prettyTextLine :: PrettyPrec a => a -> Text Source #

Pretty-print something and render it as (preferably) one line Text.

prettyString :: PrettyPrec a => a -> String Source #

Pretty-print something and render it as a String.

docToText :: Doc a -> Text Source #

Render a pretty-printed document as Text.

docToTextWidth :: Doc a -> Int -> Text Source #

Render a pretty-printed document as Text. This function consumes number of allowed characters in a line before introducing a line break. In other words, it expects the space of the layouter to be supplied.

docToString :: Doc a -> String Source #

Render a pretty-printed document as a String.

Pretty-printing utilities

pparens :: Bool -> Doc ann -> Doc ann Source #

Optionally surround a document with parentheses depending on the Bool argument and if it does not fit on line, indent the lines, with the parens on separate lines.

pparens' :: Bool -> Doc ann -> Doc ann Source #

Same as pparens but does not indent the lines. Only encloses the document with parantheses.

encloseWithIndent :: Int -> Doc ann -> Doc ann -> Doc ann -> Doc ann Source #

bquote :: Doc ann -> Doc ann Source #

Surround a document with backticks.

prettyShowLow :: Show a => a -> Doc ann Source #

Turn a Show instance into a Doc, lowercasing it in the process.

reportBug :: Doc ann Source #

An invitation to report an error as a bug.

data BulletList i Source #

Constructors

BulletList 

Fields

Instances

Instances details
PrettyPrec i => PrettyPrec (BulletList i) Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> BulletList i -> Doc ann Source #

prettyBinding :: (PrettyPrec a, PrettyPrec b) => (a, b) -> Doc ann Source #

prettyEquality :: (PrettyPrec a, PrettyPrec b) => (a, Maybe b) -> Doc ann Source #

data Wildcard Source #

We can use the Wildcard value to replace unification variables when we don't care about them, e.g. to print out the shape of a type like (_ -> _) * _

Constructors

Wildcard 

Instances

Instances details
Show Wildcard Source # 
Instance details

Defined in Swarm.Pretty

Eq Wildcard Source # 
Instance details

Defined in Swarm.Pretty

Ord Wildcard Source # 
Instance details

Defined in Swarm.Pretty

PrettyPrec Wildcard Source # 
Instance details

Defined in Swarm.Pretty

Methods

prettyPrec :: Int -> Wildcard -> Doc ann Source #