swarm-0.6.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Language.Pretty

Description

Pretty-printing for the Swarm language.

Synopsis

Documentation

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 UnificationError Source # 
Instance details

Defined in Swarm.Language.Pretty

PrettyPrec Capability Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec KindError Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Wildcard Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Comment Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Const Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec InvalidAtomicReason Source # 
Instance details

Defined in Swarm.Language.Pretty

PrettyPrec LocatedTCFrame Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec TCFrame Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec TypeErr Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Arity Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec BaseTy Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec IntVar Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Polytype Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec TyCon Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec UPolytype Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Direction Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec Text Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

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

Defined in Swarm.Language.Pretty

Methods

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

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

Defined in Swarm.Language.Pretty

Methods

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

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

Defined in Swarm.Language.Pretty

Methods

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

PrettyPrec (Syntax' ty) Source #

Pretty-print a syntax node with comments.

Instance details

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> Syntax' ty -> Doc ann Source #

PrettyPrec (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> Term' ty -> Doc ann Source #

(UnchainableFun t, PrettyPrec t, SubstRec t) => PrettyPrec (TypeF t) Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

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

Defined in Swarm.Language.Pretty

Methods

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

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

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

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.

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.

docToString :: Doc a -> String Source #

Render a pretty-printed document as a String.

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

Pretty-print something and render it as a String.

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 Prec a Source #

Constructors

Prec Int a 

data BulletList i Source #

Constructors

BulletList 

Fields

Instances

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

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> BulletList i -> 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.Language.Pretty

Eq Wildcard Source # 
Instance details

Defined in Swarm.Language.Pretty

Ord Wildcard Source # 
Instance details

Defined in Swarm.Language.Pretty

PrettyPrec Wildcard Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

class UnchainableFun t where Source #

Split a function type chain, so that we can pretty print the type parameters aligned on each line when they don't fit.

Methods

unchainFun :: t -> NonEmpty t Source #

Instances

Instances details
UnchainableFun Type Source # 
Instance details

Defined in Swarm.Language.Pretty

UnchainableFun (Free TypeF ty) Source # 
Instance details

Defined in Swarm.Language.Pretty

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

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

prettyLambda :: (Pretty a1, PrettyPrec a2) => (a1, Maybe a2) -> Doc ann Source #

prettyTypeErrText :: Text -> ContextualTypeErr -> Text Source #

Format a ContextualTypeError for the user and render it as Text.

prettyTypeErr :: Text -> ContextualTypeErr -> Doc ann Source #

Format a ContextualTypeError for the user.

filterTCStack :: TCStack -> TCStack Source #

Filter the TCStack of extravagant Binds.

typeDescription :: Source -> UType -> Doc a Source #

Given a type and its source, construct an appropriate description of it to go in a type mismatch error message.

hasAnyUVars :: UType -> Bool Source #

Check whether a type contains any unification variables at all.

isTopLevelConstructor :: UType -> Maybe (TypeF ()) Source #

Check whether a type consists of a top-level type constructor immediately applied to unification variables.

isPure :: Free f a -> Bool Source #

tyNounPhrase :: TypeF () -> Doc a Source #

Return an English noun phrase describing things with the given top-level type constructor.

baseTyNounPhrase :: BaseTy -> Doc a Source #

Return an English noun phrase describing things with the given base type.

fieldMismatchMsg :: Set Var -> Set Var -> Doc a Source #

Generate an appropriate message when the sets of fields in two record types do not match, explaining which fields are extra and which are missing.