atp-haskell-1.10: Translation from Ocaml to Haskell of John Harrison's ATP code

Safe HaskellNone
LanguageHaskell98

Data.Logic.ATP.Pretty

Synopsis

Documentation

(<>) :: Monoid m => m -> m -> m infixr 6

An infix synonym for mappend.

Since: 4.5.0.0

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

Instances

Pretty Bool 
Pretty Char 
Pretty Double 
Pretty Float 
Pretty Int 
Pretty Integer 
Pretty Ordering 
Pretty () 
Pretty FName 
Pretty V 
Pretty Predicate 
Pretty Depth 
Pretty Prop 
Pretty Atom 
Pretty Function 
Pretty K 
Pretty a => Pretty [a] 
Pretty a => Pretty (Maybe a) 
IsAtom atom => Pretty (LFormula atom) 
Pretty a => Pretty (JL a) 
Pretty atom => Pretty (TruthTable atom) 
IsAtom atom => Pretty (PFormula atom) 
(Num a, Show a) => Pretty (Knows a) 
(Pretty a, Pretty b) => Pretty (Either a b) 
(Pretty a, Pretty b) => Pretty (a, b) 
IsTerm (Term function v) => Pretty (Term function v) 
(IsPredicate predicate, IsTerm term) => Pretty (FOLAP predicate term) 
(HasApply (FOL predicate term), HasEquate (FOL predicate term), IsTerm term) => Pretty (FOL predicate term) 
(HasApply atom, IsTerm term, (~) * term (TermOf atom), (~) * v (TVarOf term)) => Pretty (QFormula v atom) 
(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 
(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) 

type Precedence = forall a. Num a => a Source

Use the same precedence type as the pretty package

class HasFixity x where Source

A class to extract the fixity of a formula so they can be properly parenthesized.

The Haskell FixityDirection type is concerned with how to interpret a formula formatted in a certain way, but here we are concerned with how to format a formula given its interpretation. As such, one case the Haskell type does not capture is whether the operator follows the associative law, so we can omit parentheses in an expression such as a & b & c. Hopefully, we can generate formulas so that an associative operator with left associative fixity direction appears as (a+b)+c rather than a+(b+c).

Minimal complete definition

Nothing

Instances

HasFixity Prop Source 
HasFixity Atom Source 
IsAtom atom => HasFixity (LFormula atom) Source 
HasFixity a => HasFixity (JL a) Source 
IsAtom atom => HasFixity (PFormula atom) Source 
Num a => HasFixity (Knows a) Source 
(IsFunction function, IsVariable v) => HasFixity (Term function v) Source 
HasFixity (FOLAP predicate term) Source 
(IsPredicate predicate, IsTerm term) => HasFixity (FOL predicate term) Source 
IsQuantified (QFormula v atom) => HasFixity (QFormula v atom) Source 

data Side Source

What side of the parent formula are we rendering?

Constructors

Top 
LHS 
RHS 
Unary 

Instances

testParen :: (Eq a, Ord a, Num a) => Side -> a -> a -> Associativity -> Bool Source

Decide whether to parenthesize based on which side of the parent binary operator we are rendering, the parent operator's precedence, and the precedence and associativity of the operator we are rendering. testParen :: Side -> Precedence -> Precedence -> Associativity -> Bool

assertEqual' Source

Arguments

:: (?loc :: CallStack, Eq a, Pretty a) 
=> String

The message prefix

-> a

The expected value

-> a

The actual value

-> Assertion 

Version of assertEqual that uses the pretty printer instead of show.

leafPrec :: Num a => a Source

boolPrec :: Num a => a Source

notPrec :: Num a => a Source

atomPrec :: Num a => a Source

andPrec :: Num a => a Source

orPrec :: Num a => a Source

impPrec :: Num a => a Source

iffPrec :: Num a => a Source

quantPrec :: Num a => a Source

eqPrec :: Num a => a Source

pAppPrec :: Num a => a Source