twee-lib-2.4.2: An equational theorem prover
Safe HaskellSafe-Inferred
LanguageHaskell2010

Twee.Pretty

Description

Pretty-printing of terms and assorted other values.

Synopsis

Documentation

newtype TermStyle Source #

Defines how to print out a function symbol.

Constructors

TermStyle 

Fields

  • pPrintTerm :: forall a. Pretty a => PrettyLevel -> Rational -> Doc -> [a] -> Doc

    Renders a function application. Takes the following arguments in this order: Pretty-printing level, current precedence, pretty-printed function symbol and list of arguments to the function.

class Pretty f => PrettyTerm f where Source #

A class for customising the printing of function symbols.

Minimal complete definition

Nothing

Methods

termStyle :: f -> TermStyle Source #

The style of the function symbol. Defaults to curried.

data HighlightedTerm f Source #

Constructors

HighlightedTerm [ANSICode] (Maybe [Int]) (Term f) 

Instances

Instances details
(Labelled f, PrettyTerm f) => Pretty (HighlightedTerm f) Source # 
Instance details

Defined in Twee.Pretty

prettyPrint :: Pretty a => a -> IO () Source #

Print a value to the console.

(<#>) :: Doc -> Doc -> Doc infixl 6 Source #

Put one document beside another, i.e., <>. Renamed here because (a different) <> is exported by Prelude.

pPrintEmpty :: Doc Source #

The empty document. Used to avoid name clashes with empty.

pPrintTuple :: [Doc] -> Doc Source #

Print a tuple of values.

pPrintSet :: [Doc] -> Doc Source #

Print a set of vlaues.

supply :: [String] -> [String] Source #

Generate a list of candidate names for pretty-printing.

invisible :: TermStyle Source #

For operators like $ that should be printed as a blank space.

curried :: TermStyle Source #

For functions that should be printed curried.

uncurried :: TermStyle Source #

For functions that should be printed uncurried.

fixedArity :: Int -> TermStyle -> TermStyle Source #

A helper function that deals with under- and oversaturated applications.

implicitArguments :: Int -> TermStyle -> TermStyle Source #

A helper function that drops a certain number of arguments.

prefix :: TermStyle Source #

For prefix operators.

postfix :: TermStyle Source #

For postfix operators.

infixStyle :: Int -> TermStyle Source #

For infix operators.

newtype PrettyLevel #

Level of detail in the pretty printed output. Level 0 is the least detail.

Constructors

PrettyLevel Int 

class Pretty a where #

Pretty printing class. The precedence level is used in a similar way as in the Show class. Minimal complete definition is either pPrintPrec or pPrint.

Minimal complete definition

pPrintPrec | pPrint

Methods

pPrintPrec :: PrettyLevel -> Rational -> a -> Doc #

pPrint :: a -> Doc #

pPrintList :: PrettyLevel -> [a] -> Doc #

Instances

Instances details
Pretty Ordering 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Doc Source # 
Instance details

Defined in Twee.Pretty

Pretty Id Source # 
Instance details

Defined in Twee.Base

Pretty Var Source # 
Instance details

Defined in Twee.Pretty

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty () 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> () -> Doc #

pPrint :: () -> Doc #

pPrintList :: PrettyLevel -> [()] -> Doc #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Char 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Double 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Float 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Int 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

(Eq a, Integral a, Pretty a) => Pretty (Ratio a) Source # 
Instance details

Defined in Twee.Pretty

Pretty a => Pretty (Set a) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Set a -> Doc #

pPrint :: Set a -> Doc #

pPrintList :: PrettyLevel -> [Set a] -> Doc #

Function f => Pretty (Active f) Source # 
Instance details

Defined in Twee

Function f => Pretty (Message f) Source # 
Instance details

Defined in Twee

(Labelled f, PrettyTerm f) => Pretty (CriticalPair f) Source # 
Instance details

Defined in Twee.CP

(Labelled f, PrettyTerm f) => Pretty (Atom f) Source # 
Instance details

Defined in Twee.Constraints

Methods

pPrintPrec :: PrettyLevel -> Rational -> Atom f -> Doc #

pPrint :: Atom f -> Doc #

pPrintList :: PrettyLevel -> [Atom f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Branch f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Formula f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Model f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Equation f) Source # 
Instance details

Defined in Twee.Equation

(Labelled f, PrettyTerm f) => Pretty (HighlightedTerm f) Source # 
Instance details

Defined in Twee.Pretty

(Labelled f, PrettyTerm f) => Pretty (Axiom f) Source # 
Instance details

Defined in Twee.Proof

(Labelled f, PrettyTerm f) => Pretty (Derivation f) Source # 
Instance details

Defined in Twee.Proof

Function f => Pretty (Presentation f) Source # 
Instance details

Defined in Twee.Proof

Function f => Pretty (Proof f) Source # 
Instance details

Defined in Twee.Proof

(Labelled f, PrettyTerm f) => Pretty (Rule f) Source # 
Instance details

Defined in Twee.Rule

Methods

pPrintPrec :: PrettyLevel -> Rational -> Rule f -> Doc #

pPrint :: Rule f -> Doc #

pPrintList :: PrettyLevel -> [Rule f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Subst f) Source # 
Instance details

Defined in Twee.Pretty

(Pretty f, Labelled f) => Pretty (Fun f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Fun f -> Doc #

pPrint :: Fun f -> Doc #

pPrintList :: PrettyLevel -> [Fun f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Term f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Term f -> Doc #

pPrint :: Term f -> Doc #

pPrintList :: PrettyLevel -> [Term f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (TermList f) Source # 
Instance details

Defined in Twee.Pretty

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty a => Pretty [a] 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> [a] -> Doc #

pPrint :: [a] -> Doc #

pPrintList :: PrettyLevel -> [[a]] -> Doc #

(Pretty a, Pretty b) => Pretty (Either a b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> Either a b -> Doc #

pPrint :: Either a b -> Doc #

pPrintList :: PrettyLevel -> [Either a b] -> Doc #

(Pretty k, Pretty v) => Pretty (Map k v) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Map k v -> Doc #

pPrint :: Map k v -> Doc #

pPrintList :: PrettyLevel -> [Map k v] -> Doc #

(Pretty a, Pretty b) => Pretty (a, b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b) -> Doc #

pPrint :: (a, b) -> Doc #

pPrintList :: PrettyLevel -> [(a, b)] -> Doc #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c) -> Doc #

pPrint :: (a, b, c) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d) -> Doc #

pPrint :: (a, b, c, d) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e) -> Doc #

pPrint :: (a, b, c, d, e) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f) -> Doc #

pPrint :: (a, b, c, d, e, f) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g) -> Doc #

pPrint :: (a, b, c, d, e, f, g) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g, h) -> Doc #

pPrint :: (a, b, c, d, e, f, g, h) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g, h)] -> Doc #

prettyShow :: Pretty a => a -> String #

Pretty print a value with the prettyNormal level.

prettyParen :: Bool -> Doc -> Doc #

Parenthesize an value if the boolean is true.

prettyNormal :: PrettyLevel #

The "normal" (Level 0) of detail.

data Doc #

The abstract type of documents. A Doc represents a set of layouts. A Doc with no occurrences of Union or NoDoc represents just one layout.

Instances

Instances details
IsString Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

fromString :: String -> Doc #

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Semigroup Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Show Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

NFData Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

rnf :: Doc -> () #

Eq Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

(==) :: Doc -> Doc -> Bool #

(/=) :: Doc -> Doc -> Bool #

Pretty Doc Source # 
Instance details

Defined in Twee.Pretty

type Rep Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

type Rep Doc = D1 ('MetaData "Doc" "Text.PrettyPrint.HughesPJ" "pretty-1.1.3.6" 'True) (C1 ('MetaCons "Doc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ()))))

zeroWidthText :: String -> Doc #

Some text, but without any width. Use for non-printing text such as a HTML or Latex tags

vcat :: [Doc] -> Doc #

List version of $$.

text :: String -> Doc #

A document of height 1 containing a literal string. text satisfies the following laws:

The side condition on the last law is necessary because text "" has height 1, while empty has no height.

space #

Arguments

:: Doc

A space character

sizedText :: Int -> String -> Doc #

Some text with any width. (text s = sizedText (length s) s)

sep :: [Doc] -> Doc #

Either hsep or vcat.

semi #

Arguments

:: Doc

A ';' character

rparen #

Arguments

:: Doc

A ')' character

renderStyle :: Style -> Doc -> String #

Render the Doc to a String using the given Style.

render :: Doc -> String #

Render the Doc to a String using the default Style (see style).

reduceDoc :: Doc -> RDoc #

Perform some simplification of a built up GDoc.

rbrack #

Arguments

:: Doc

A ']' character

rbrace #

Arguments

:: Doc

A '}' character

rational #

Arguments

:: Rational 
-> Doc
rational n = text (show n)

quotes #

Arguments

:: Doc 
-> Doc

Wrap document in '...'

punctuate :: Doc -> [Doc] -> [Doc] #

punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]

ptext :: String -> Doc #

Same as text. Used to be used for Bytestrings.

parens #

Arguments

:: Doc 
-> Doc

Wrap document in (...)

nest :: Int -> Doc -> Doc #

Nest (or indent) a document by a given number of positions (which may also be negative). nest satisfies the laws:

The side condition on the last law is needed because empty is a left identity for <>.

maybeQuotes :: Bool -> Doc -> Doc #

Apply quotes to Doc if boolean is true.

maybeParens :: Bool -> Doc -> Doc #

Apply parens to Doc if boolean is true.

maybeDoubleQuotes :: Bool -> Doc -> Doc #

Apply doubleQuotes to Doc if boolean is true.

maybeBrackets :: Bool -> Doc -> Doc #

Apply brackets to Doc if boolean is true.

maybeBraces :: Bool -> Doc -> Doc #

Apply braces to Doc if boolean is true.

lparen #

Arguments

:: Doc

A '(' character

lbrack #

Arguments

:: Doc

A '[' character

lbrace #

Arguments

:: Doc

A '{' character

isEmpty :: Doc -> Bool #

Returns True if the document is empty

integer #

Arguments

:: Integer 
-> Doc
integer n = text (show n)

int #

Arguments

:: Int 
-> Doc
int n = text (show n)

hsep :: [Doc] -> Doc #

List version of <+>.

hcat :: [Doc] -> Doc #

List version of <>.

hang :: Doc -> Int -> Doc -> Doc #

hang d1 n d2 = sep [d1, nest n d2]

fullRender #

Arguments

:: Mode

Rendering mode.

-> Int

Line length.

-> Float

Ribbons per line.

-> (TextDetails -> a -> a)

What to do with text.

-> a

What to do at the end.

-> Doc

The document.

-> a

Result.

The general rendering interface. Please refer to the Style and Mode types for a description of rendering mode, line length and ribbons.

fsep :: [Doc] -> Doc #

"Paragraph fill" version of sep.

float #

Arguments

:: Float 
-> Doc
float n = text (show n)

first :: Doc -> Doc -> Doc #

first returns its first argument if it is non-empty, otherwise its second.

fcat :: [Doc] -> Doc #

"Paragraph fill" version of cat.

equals #

Arguments

:: Doc

A '=' character

doubleQuotes #

Arguments

:: Doc 
-> Doc

Wrap document in "..."

double #

Arguments

:: Double 
-> Doc
double n = text (show n)

comma #

Arguments

:: Doc

A ',' character

colon #

Arguments

:: Doc

A : character

char :: Char -> Doc #

A document of height and width 1, containing a literal character.

cat :: [Doc] -> Doc #

Either hcat or vcat.

brackets #

Arguments

:: Doc 
-> Doc

Wrap document in [...]

braces #

Arguments

:: Doc 
-> Doc

Wrap document in {...}

(<+>) :: Doc -> Doc -> Doc infixl 6 #

Beside, separated by space, unless one of the arguments is empty. <+> is associative, with identity empty.

($+$) :: Doc -> Doc -> Doc infixl 5 #

Above, with no overlapping. $+$ is associative, with identity empty.

($$) :: Doc -> Doc -> Doc infixl 5 #

Above, except that if the last line of the first argument stops at least one position before the first line of the second begins, these two lines are overlapped. For example:

   text "hi" $$ nest 5 (text "there")

lays out as

   hi   there

rather than

   hi
        there

$$ is associative, with identity empty, and also satisfies

  • (x $$ y) <> z = x $$ (y <> z), if y non-empty.

data TextDetails #

A TextDetails represents a fragment of text that will be output at some point in a Doc.

Constructors

Chr !Char

A single Char fragment

Str String

A whole String fragment

PStr String

Used to represent a Fast String fragment but now deprecated and identical to the Str constructor.

Instances

Instances details
Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type #

Show TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

NFData TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: TextDetails -> () #

Eq TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

data Style #

A rendering style. Allows us to specify constraints to choose among the many different rendering options.

Constructors

Style 

Fields

  • mode :: Mode

    The rendering mode.

  • lineLength :: Int

    Maximum length of a line, in characters.

  • ribbonsPerLine :: Float

    Ratio of line length to ribbon length. A ribbon refers to the characters on a line excluding indentation. So a lineLength of 100, with a ribbonsPerLine of 2.0 would only allow up to 50 characters of ribbon to be displayed on a line, while allowing it to be indented up to 50 characters.

Instances

Instances details
Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Eq Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

(==) :: Style -> Style -> Bool #

(/=) :: Style -> Style -> Bool #

type Rep Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Style = D1 ('MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mode) :*: (S1 ('MetaSel ('Just "lineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ribbonsPerLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))

data Mode #

Rendering mode.

Constructors

PageMode

Normal rendering (lineLength and ribbonsPerLine respected').

ZigZagMode

With zig-zag cuts.

LeftMode

No indentation, infinitely long lines (lineLength ignored), but explicit new lines, i.e., text "one" $$ text "two", are respected.

OneLineMode

All on one line, lineLength ignored and explicit new lines ($$) are turned into spaces.

Instances

Instances details
Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Eq Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

type Rep Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Mode = D1 ('MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) ((C1 ('MetaCons "PageMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZigZagMode" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OneLineMode" 'PrefixI 'False) (U1 :: Type -> Type)))

style :: Style #

The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).

class Pretty a where #

Pretty printing class. The precedence level is used in a similar way as in the Show class. Minimal complete definition is either pPrintPrec or pPrint.

Minimal complete definition

pPrintPrec | pPrint

Methods

pPrintPrec :: PrettyLevel -> Rational -> a -> Doc #

pPrint :: a -> Doc #

pPrintList :: PrettyLevel -> [a] -> Doc #

Instances

Instances details
Pretty Ordering 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Doc Source # 
Instance details

Defined in Twee.Pretty

Pretty Id Source # 
Instance details

Defined in Twee.Base

Pretty Var Source # 
Instance details

Defined in Twee.Pretty

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty () 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> () -> Doc #

pPrint :: () -> Doc #

pPrintList :: PrettyLevel -> [()] -> Doc #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Char 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Double 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Float 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Int 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

(Eq a, Integral a, Pretty a) => Pretty (Ratio a) Source # 
Instance details

Defined in Twee.Pretty

Pretty a => Pretty (Set a) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Set a -> Doc #

pPrint :: Set a -> Doc #

pPrintList :: PrettyLevel -> [Set a] -> Doc #

Function f => Pretty (Active f) Source # 
Instance details

Defined in Twee

Function f => Pretty (Message f) Source # 
Instance details

Defined in Twee

(Labelled f, PrettyTerm f) => Pretty (CriticalPair f) Source # 
Instance details

Defined in Twee.CP

(Labelled f, PrettyTerm f) => Pretty (Atom f) Source # 
Instance details

Defined in Twee.Constraints

Methods

pPrintPrec :: PrettyLevel -> Rational -> Atom f -> Doc #

pPrint :: Atom f -> Doc #

pPrintList :: PrettyLevel -> [Atom f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Branch f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Formula f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Model f) Source # 
Instance details

Defined in Twee.Constraints

(Labelled f, PrettyTerm f) => Pretty (Equation f) Source # 
Instance details

Defined in Twee.Equation

(Labelled f, PrettyTerm f) => Pretty (HighlightedTerm f) Source # 
Instance details

Defined in Twee.Pretty

(Labelled f, PrettyTerm f) => Pretty (Axiom f) Source # 
Instance details

Defined in Twee.Proof

(Labelled f, PrettyTerm f) => Pretty (Derivation f) Source # 
Instance details

Defined in Twee.Proof

Function f => Pretty (Presentation f) Source # 
Instance details

Defined in Twee.Proof

Function f => Pretty (Proof f) Source # 
Instance details

Defined in Twee.Proof

(Labelled f, PrettyTerm f) => Pretty (Rule f) Source # 
Instance details

Defined in Twee.Rule

Methods

pPrintPrec :: PrettyLevel -> Rational -> Rule f -> Doc #

pPrint :: Rule f -> Doc #

pPrintList :: PrettyLevel -> [Rule f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Subst f) Source # 
Instance details

Defined in Twee.Pretty

(Pretty f, Labelled f) => Pretty (Fun f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Fun f -> Doc #

pPrint :: Fun f -> Doc #

pPrintList :: PrettyLevel -> [Fun f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Term f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Term f -> Doc #

pPrint :: Term f -> Doc #

pPrintList :: PrettyLevel -> [Term f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (TermList f) Source # 
Instance details

Defined in Twee.Pretty

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty a => Pretty [a] 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> [a] -> Doc #

pPrint :: [a] -> Doc #

pPrintList :: PrettyLevel -> [[a]] -> Doc #

(Pretty a, Pretty b) => Pretty (Either a b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> Either a b -> Doc #

pPrint :: Either a b -> Doc #

pPrintList :: PrettyLevel -> [Either a b] -> Doc #

(Pretty k, Pretty v) => Pretty (Map k v) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Map k v -> Doc #

pPrint :: Map k v -> Doc #

pPrintList :: PrettyLevel -> [Map k v] -> Doc #

(Pretty a, Pretty b) => Pretty (a, b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b) -> Doc #

pPrint :: (a, b) -> Doc #

pPrintList :: PrettyLevel -> [(a, b)] -> Doc #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c) -> Doc #

pPrint :: (a, b, c) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d) -> Doc #

pPrint :: (a, b, c, d) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e) -> Doc #

pPrint :: (a, b, c, d, e) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f) -> Doc #

pPrint :: (a, b, c, d, e, f) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g) -> Doc #

pPrint :: (a, b, c, d, e, f, g) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g, h) -> Doc #

pPrint :: (a, b, c, d, e, f, g, h) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g, h)] -> Doc #

Orphan instances

Pretty Doc Source # 
Instance details

Pretty Var Source # 
Instance details

(Eq a, Integral a, Pretty a) => Pretty (Ratio a) Source # 
Instance details

Pretty a => Pretty (Set a) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> Set a -> Doc #

pPrint :: Set a -> Doc #

pPrintList :: PrettyLevel -> [Set a] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Subst f) Source # 
Instance details

(Pretty f, Labelled f) => Pretty (Fun f) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> Fun f -> Doc #

pPrint :: Fun f -> Doc #

pPrintList :: PrettyLevel -> [Fun f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (Term f) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> Term f -> Doc #

pPrint :: Term f -> Doc #

pPrintList :: PrettyLevel -> [Term f] -> Doc #

(Labelled f, PrettyTerm f) => Pretty (TermList f) Source # 
Instance details

(Pretty k, Pretty v) => Pretty (Map k v) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> Map k v -> Doc #

pPrint :: Map k v -> Doc #

pPrintList :: PrettyLevel -> [Map k v] -> Doc #