logic-classes-1.5.3: Framework for propositional and first order logic, theorem proving

Safe HaskellNone
LanguageHaskell98

Data.Logic.Classes.FirstOrder

Synopsis

Documentation

class (Formula formula atom, Combinable formula, Constants formula, Constants atom, HasFixity atom, Variable v, Pretty atom, Pretty v) => FirstOrderFormula formula atom v | formula -> atom v where Source

The FirstOrderFormula type class. Minimal implementation: for_all, exists, foldFirstOrder, foldTerm, (.=.), pApp0-pApp7, fApp, var. The functional dependencies are necessary here so we can write functions that don't fix all of the type parameters. For example, without them the univquant_free_vars function gives the error No instance for (FirstOrderFormula Formula atom V) because the function doesn't mention the Term type.

Methods

for_all :: v -> formula -> formula Source

Universal quantification - for all x (formula x)

exists :: v -> formula -> formula Source

Existential quantification - there exists x such that (formula x)

foldFirstOrder :: (Quant -> v -> formula -> r) -> (Combination formula -> r) -> (Bool -> r) -> (atom -> r) -> formula -> r Source

A fold function similar to the one in PropositionalFormula but extended to cover both the existing formula types and the ones introduced here. foldFirstOrder (.~.) quant binOp infixPred pApp is a no op. The argument order is taken from Logic-TPTP.

Instances

data Quant Source

The Quant and InfixPred types, like the BinOp type in Propositional, could be additional parameters to the type class, but it would add additional complexity with unclear benefits.

Constructors

Forall 
Exists 

zipFirstOrder :: FirstOrderFormula formula atom v => (Quant -> v -> formula -> Quant -> v -> formula -> Maybe r) -> (Combination formula -> Combination formula -> Maybe r) -> (Bool -> Bool -> Maybe r) -> (atom -> atom -> Maybe r) -> formula -> formula -> Maybe r Source

for_all' :: FirstOrderFormula formula atom v => [v] -> formula -> formula Source

for_all with a list of variables, for backwards compatibility.

exists' :: FirstOrderFormula formula atom v => [v] -> formula -> formula Source

exists with a list of variables, for backwards compatibility.

quant :: FirstOrderFormula formula atom v => Quant -> v -> formula -> formula Source

Helper function for building folds.

(!) :: FirstOrderFormula formula atom v => v -> formula -> formula infixr 9 Source

Names for for_all and exists inspired by the conventions of the TPTP project.

(?) :: FirstOrderFormula formula atom v => v -> formula -> formula infixr 9 Source

(∀) :: FirstOrderFormula formula atom v => v -> formula -> formula infixr 9 Source

∀ can't be a function when -XUnicodeSyntax is enabled.

(∃) :: FirstOrderFormula formula atom v => v -> formula -> formula infixr 9 Source

quant' :: FirstOrderFormula formula atom v => Quant -> [v] -> formula -> formula Source

Legacy version of quant from when we supported lists of quantified variables. It also has the virtue of eliding quantifications with empty variable lists (by calling for_all' and exists'.)

convertFOF :: (FirstOrderFormula formula1 atom1 v1, FirstOrderFormula formula2 atom2 v2) => (atom1 -> atom2) -> (v1 -> v2) -> formula1 -> formula2 Source

toPropositional :: forall formula1 atom v formula2 atom2. (FirstOrderFormula formula1 atom v, PropositionalFormula formula2 atom2) => (atom -> atom2) -> formula1 -> formula2 Source

Try to convert a first order logic formula to propositional. This will return Nothing if there are any quantifiers, or if it runs into an atom that it is unable to convert.

withUnivQuants :: FirstOrderFormula formula atom v => ([v] -> formula -> r) -> formula -> r Source

Examine the formula to find the list of outermost universally quantified variables, and call a function with that list and the formula after the quantifiers are removed.

showFirstOrder :: forall formula atom v. (FirstOrderFormula formula atom v, Show v) => (atom -> String) -> formula -> String Source

Display a formula in a format that can be read into the interpreter.

prettyFirstOrder :: forall formula atom v. FirstOrderFormula formula atom v => (Int -> atom -> Doc) -> (v -> Doc) -> Int -> formula -> Doc Source

fixityFirstOrder :: (HasFixity atom, FirstOrderFormula formula atom v) => formula -> Fixity Source

foldAtomsFirstOrder :: FirstOrderFormula fof atom v => (r -> atom -> r) -> r -> fof -> r Source

mapAtomsFirstOrder :: forall formula atom v. FirstOrderFormula formula atom v => (atom -> formula) -> formula -> formula Source

onatoms :: forall formula atom v. FirstOrderFormula formula atom v => (atom -> formula) -> formula -> formula Source

Deprecated - use mapAtoms

overatoms :: forall formula atom v r. FirstOrderFormula formula atom v => (atom -> r -> r) -> formula -> r -> r Source

Deprecated - use foldAtoms

atom_union :: forall formula atom v a. (FirstOrderFormula formula atom v, Ord a) => (atom -> Set a) -> formula -> Set a Source

fromFirstOrder :: forall formula atom v lit atom2. (Formula lit atom2, FirstOrderFormula formula atom v, Literal lit atom2) => (atom -> atom2) -> formula -> Failing lit Source

Just like Logic.FirstOrder.convertFOF except it rejects anything with a construct unsupported in a normal logic formula, i.e. quantifiers and formula combinators other than negation.

fromLiteral :: forall lit atom v fof atom2. (Literal lit atom, FirstOrderFormula fof atom2 v) => (atom -> atom2) -> lit -> fof Source