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

Safe HaskellNone
LanguageHaskell98

Data.Logic.ATP.Term

Contents

Description

A Term is a expression representing a domain element. It is composed of variables which can be bound to domain elements, or functions which can be applied to terms to yield other domain elements.

Synopsis

Variables

class (Ord v, IsString v, Pretty v, Show v) => IsVariable v where Source

Methods

variant :: v -> Set v -> v Source

Return a variable based on v but different from any set element. The result may be v itself if v is not a member of the set.

prefix :: String -> v -> v Source

Modify a variable by adding a prefix. This unfortunately assumes that v is "string-like" but at least one algorithm in Harrison currently requires this.

variants :: IsVariable v => v -> [v] Source

Return an infinite list of variations on v

Functions

class (IsString function, Ord function, Pretty function, Show function) => IsFunction function Source

newtype FName Source

A simple type to use as the function parameter of Term. The only reason to use this instead of String is to get nicer pretty printing.

Constructors

FName String 

Terms

class (Eq term, Ord term, Pretty term, Show term, IsString term, HasFixity term, IsVariable (TVarOf term), IsFunction (FunOf term)) => IsTerm term where Source

A term is an expression representing a domain element, either as a variable reference or a function applied to a list of terms.

Associated Types

type TVarOf term Source

The associated variable type

type FunOf term Source

The associated function type

Methods

vt :: TVarOf term -> term Source

Build a term which is a variable reference.

fApp :: FunOf term -> [term] -> term Source

Build a term by applying terms to an atomic function (FunOf term).

foldTerm Source

Arguments

:: (TVarOf term -> r)

Variable references are dispatched here

-> (FunOf term -> [term] -> r)

Function applications are dispatched here

-> term 
-> r 

A fold over instances of IsTerm.

Instances

(IsFunction function, IsVariable v) => IsTerm (Term function v) Source 

zipTerms Source

Arguments

:: (IsTerm term1, v1 ~ TVarOf term1, function1 ~ FunOf term1, IsTerm term2, v2 ~ TVarOf term2, function2 ~ FunOf term2) 
=> (v1 -> v2 -> Maybe r)

Combine two variables

-> (function1 -> [term1] -> function2 -> [term2] -> Maybe r)

Combine two function applications

-> term1 
-> term2 
-> Maybe r

Result for dissimilar terms is Nothing.

Combine two terms if they are similar (i.e. two variables or two function applications.)

convertTerm Source

Arguments

:: (IsTerm term1, v1 ~ TVarOf term1, f1 ~ FunOf term1, IsTerm term2, v2 ~ TVarOf term2, f2 ~ FunOf term2) 
=> (v1 -> v2)

convert a variable

-> (f1 -> f2)

convert a function

-> term1 
-> term2 

Convert between two instances of IsTerm

prettyTerm :: (v ~ TVarOf term, function ~ FunOf term, IsTerm term, HasFixity term, Pretty v, Pretty function) => PrettyLevel -> Rational -> term -> Doc Source

Implementation of pPrint for any term

prettyFunctionApply :: (function ~ FunOf term, IsTerm term, HasFixity term) => PrettyLevel -> function -> [term] -> Doc Source

Format a function application: F(x,y)

showTerm :: (v ~ TVarOf term, function ~ FunOf term, IsTerm term, Pretty v, Pretty function) => term -> String Source

Implementation of show for any term

showFunctionApply :: (v ~ TVarOf term, function ~ FunOf term, IsTerm term) => function -> [term] -> String Source

Build an expression for a function application: fApp (F) [x, y]

funcs :: (IsTerm term, function ~ FunOf term) => term -> Set (function, Arity) Source

data Term function v Source

Constructors

Var v 
FApply function [Term function v] 

Instances

JustApply ApAtom Source 
IsFirstOrder EqFormula Source 
IsFirstOrder ApFormula Source 
IsFirstOrder Formula Source 
(Eq function, Eq v) => Eq (Term function v) Source 
(Data function, Data v) => Data (Term function v) Source 
(Ord function, Ord v) => Ord (Term function v) Source 
(Read function, Read v) => Read (Term function v) Source 
(IsVariable v, IsFunction function) => Show (Term function v) Source 
(IsVariable v, IsFunction function) => IsString (Term function v) Source 
IsTerm (Term function v) => Pretty (Term function v) Source 
(IsFunction function, IsVariable v) => HasFixity (Term function v) Source 
(IsFunction function, IsVariable v) => IsTerm (Term function v) Source 
Unify (SkAtom, SkAtom) Source 
type TVarOf (Term function v) = v Source 
type FunOf (Term function v) = function Source 
type UTermOf (SkAtom, SkAtom) = TermOf SkAtom Source 

type FTerm = Term FName V Source

A term type with no Skolem functions