Copyright | (c) 2017 2018 N Steenbergen |
---|---|
License | GPL-3 |
Maintainer | ns@slak.ws |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Plain datastructures, class instances and operations on logical formulas.
- data Formula ext
- = Variable String
- | Constant Bool
- | Extend ext (Formula ext)
- | Negation (Formula ext)
- | Conjunction (Formula ext) (Formula ext)
- | Disjunction (Formula ext) (Formula ext)
- | XDisjunction (Formula ext) (Formula ext)
- | Implication (Formula ext) (Formula ext)
- | BiImplication (Formula ext) (Formula ext)
- data Marked formula = Marked {}
- data Term ext
- newtype Ambiguous term = Ambiguous [term]
- type Proposition = Formula Classical
- type Predicate = Formula Quantifier
- type FormulaML = Formula Modality
- type FormulaJL = Formula Justification
- type Classical = ()
- data Quantifier
- data Modality
- data Justification
- simplify :: Formula ext -> Formula ext
- asTerm :: Marked (Formula ext) -> [Term ext]
- isFormula :: Term ext -> Bool
- isExtension :: Term ext -> Bool
- isMarkedFormula :: Term ext -> Bool
- class Subterm ext term where
- class HasVariables term where
Datastructures
Formulas
For our purposes, a Formula
is a structure that is built upon a formula
of classical propositional logic. It has all the standard connectives, plus
an optional Extension
that may hold quantifiers, modalities, etcetera.
Note that it is generally expected that formulas will be simplify
ed
before being processed.
Variable String | |
Constant Bool | |
Extend ext (Formula ext) | |
Negation (Formula ext) | |
Conjunction (Formula ext) (Formula ext) | |
Disjunction (Formula ext) (Formula ext) | |
XDisjunction (Formula ext) (Formula ext) | |
Implication (Formula ext) (Formula ext) | |
BiImplication (Formula ext) (Formula ext) |
Subterm ext ext => Subterm ext (Formula ext) Source # | |
Subterm ext ext => Subterm ext (Marked (Formula ext)) Source # | |
(Eq ext, Substitutable ext ext) => Substitutable ext (Formula ext) Source # | |
Eq ext => Eq (Formula ext) Source # | |
Ord ext => Ord (Formula ext) Source # | |
HasVariables ext => HasVariables (Formula ext) Source # | |
Parseable e => Parseable (Formula e) Source # | |
Printable ext => Printable (Formula ext) Source # | |
Printable ext => LaTeX (Formula ext) Source # | |
A marked formula is simply a formula with zero or more string annotations. This makes for easy generalisation: marks can carry the polarity of a formula, as well as state information specific to a particular tableau system.
Functor Marked Source # | |
Subterm ext ext => Subterm ext (Marked (Formula ext)) Source # | |
(Eq ext, Substitutable ext a) => Substitutable ext (Marked a) Source # | |
Eq formula => Eq (Marked formula) Source # | |
Ord formula => Ord (Marked formula) Source # | |
HasVariables term => HasVariables (Marked term) Source # | |
Parseable f => Parseable (Marked f) Source # | |
Printable f => Printable (Marked f) Source # | |
LaTeX a => LaTeX (Marked a) Source # | |
The term datastructure disambiguates between terms of the logical language and terms of the logical extension language (e.g. justifications).
The alternative to carrying this information at the value level is to have
a multi-parameter Substructure sub base
class relative to which operations
like pattern
ing or the occurs
check are defined. Although that seemed
prettier in theory, it made the code a whole lot more complicated.
Subterm ext ext => Subterm ext (Ambiguous (Term ext)) Source # | |
Subterm ext ext => Subterm ext (Term ext) Source # | |
(Eq ext, Substitutable ext ext) => Substitutable ext (Term ext) Source # | |
Eq ext => Eq (Term ext) Source # | |
Ord ext => Ord (Term ext) Source # | |
HasVariables ext => HasVariables (Ambiguous (Term ext)) Source # | |
HasVariables ext => HasVariables (Term ext) Source # | |
Parseable e => Parseable (Ambiguous (Term e)) Source # | |
Printable ext => Printable (Term ext) Source # | |
newtype Ambiguous term Source #
A parsed term may be ambiguous: S can be parsed as a Formula or as a Justification. Such ambiguous are stored in an Ambiguous type to be resolved later.
Ambiguous [term] |
Extensions
type Proposition = Formula Classical Source #
Formulas of propositional logic.
type Predicate = Formula Quantifier Source #
Formulas of predicate logic.
type FormulaJL = Formula Justification Source #
Formulas of justification logic.
data Quantifier Source #
Predicate logic is extended with quantifiers (and relation symbols, unimplemented).
Standard modal logics have two (dual) unary modal operators.
data Justification Source #
Justification logics are extended with justification terms.
Operations
simplify :: Formula ext -> Formula ext Source #
Simplify formulae to only falsehood, implication and justification. This reduces the number of rules that need implementation.
asTerm :: Marked (Formula ext) -> [Term ext] Source #
Interpret a marked formula as a choice of terms. Note that it is not
always clear whether a value from Terms
is meant as the marked or the
unmarked version — so we offer both.
isExtension :: Term ext -> Bool Source #
Return true iff the term is a formula extension.
isMarkedFormula :: Term ext -> Bool Source #
Return true iff the term is a marked formula.
Classes
class Subterm ext term where Source #
The Subterm
class represents a relation between terms based on an
extension ext
(that is, formulas or extensions of formulas) and subterms
that may occur within those ext
-terms.
class HasVariables term where Source #
The HasVariables
class is applicable to formulas and formula extensions
that consist of substructures with variables and constants, and operators to
combine them.
variables :: term -> [String] Source #
Return the variables occurring in a term. Note: May contain duplicates.
isVariable :: term -> Bool Source #
Return true if the term is a variable.
isConstant :: term -> Bool Source #
Return true if the term is a constant.
isAtomary :: term -> Bool Source #
Return true if the term is atomary.
Return the number of operators in the term.
HasVariables Justification Source # | |
HasVariables ext => HasVariables (Ambiguous (Term ext)) Source # | |
HasVariables ext => HasVariables (Term ext) Source # | |
HasVariables term => HasVariables (Marked term) Source # | |
HasVariables ext => HasVariables (Formula ext) Source # | |