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

Safe HaskellNone
LanguageHaskell98

Data.Logic.ATP.Pretty

Contents

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

Instances

Pretty Bool 
Pretty Char 
Pretty Double 
Pretty Float 
Pretty Int 
Pretty Integer 
Pretty Ordering 
Pretty () 

Methods

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

pPrint :: () -> Doc #

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

Pretty FName # 
Pretty V # 

Methods

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

pPrint :: V -> Doc #

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

Pretty Predicate # 
Pretty Depth # 
Pretty Prop # 
Pretty Atom # 
Pretty Function # 
Pretty K # 

Methods

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

pPrint :: K -> Doc #

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

Pretty a => Pretty [a] 

Methods

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

pPrint :: [a] -> Doc #

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

Pretty a => Pretty (Maybe a) 
IsAtom atom => Pretty (LFormula atom) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> LFormula atom -> Doc #

pPrint :: LFormula atom -> Doc #

pPrintList :: PrettyLevel -> [LFormula atom] -> Doc #

Pretty a => Pretty (JL a) # 

Methods

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

pPrint :: JL a -> Doc #

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

Pretty atom => Pretty (TruthTable atom) # 
IsAtom atom => Pretty (PFormula atom) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> PFormula atom -> Doc #

pPrint :: PFormula atom -> Doc #

pPrintList :: PrettyLevel -> [PFormula atom] -> Doc #

(Num a, Show a) => Pretty (Knows a) # 
(Pretty a, Pretty b) => Pretty (Either a b) 

Methods

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

pPrint :: Either a b -> Doc #

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

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

Methods

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

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

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

IsTerm (Term function v) => Pretty (Term function v) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> Term function v -> Doc #

pPrint :: Term function v -> Doc #

pPrintList :: PrettyLevel -> [Term function v] -> Doc #

(IsPredicate predicate, IsTerm term) => Pretty (FOLAP predicate term) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> FOLAP predicate term -> Doc #

pPrint :: FOLAP predicate term -> Doc #

pPrintList :: PrettyLevel -> [FOLAP predicate term] -> Doc #

(HasApply (FOL predicate term), HasEquate (FOL predicate term), IsTerm term) => Pretty (FOL predicate term) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> FOL predicate term -> Doc #

pPrint :: FOL predicate term -> Doc #

pPrintList :: PrettyLevel -> [FOL predicate term] -> Doc #

(HasApply atom, IsTerm term, (~) * term (TermOf atom), (~) * v (TVarOf term)) => Pretty (QFormula v atom) # 

Methods

pPrintPrec :: PrettyLevel -> Rational -> QFormula v atom -> Doc #

pPrint :: QFormula v atom -> Doc #

pPrintList :: PrettyLevel -> [QFormula v atom] -> Doc #

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

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) 

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) 

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) 

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) 

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) 

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 #

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).

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 # 

Methods

precedence :: Term function v -> Precedence Source #

associativity :: Term function v -> Associativity Source #

HasFixity (FOLAP predicate term) Source # 

Methods

precedence :: FOLAP predicate term -> Precedence Source #

associativity :: FOLAP predicate term -> Associativity Source #

(IsPredicate predicate, IsTerm term) => HasFixity (FOL predicate term) Source # 

Methods

precedence :: FOL predicate term -> Precedence Source #

associativity :: FOL predicate term -> Associativity 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 #

Orphan instances

Pretty a => Pretty (Set a) Source # 

Methods

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

pPrint :: Set a -> Doc #

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

(Pretty v, Pretty term) => Pretty (Map v term) Source # 

Methods

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

pPrint :: Map v term -> Doc #

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