atp-haskell-1.14: 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 #

Minimal complete definition

variant, prefix

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

newtype V Source #

Constructors

V String 

Instances

Eq V Source # 

Methods

(==) :: V -> V -> Bool #

(/=) :: V -> V -> Bool #

Data V Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V -> c V #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c V #

toConstr :: V -> Constr #

dataTypeOf :: V -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c V) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c V) #

gmapT :: (forall b. Data b => b -> b) -> V -> V #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V -> r #

gmapQ :: (forall d. Data d => d -> u) -> V -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V -> m V #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V -> m V #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V -> m V #

Ord V Source # 

Methods

compare :: V -> V -> Ordering #

(<) :: V -> V -> Bool #

(<=) :: V -> V -> Bool #

(>) :: V -> V -> Bool #

(>=) :: V -> V -> Bool #

max :: V -> V -> V #

min :: V -> V -> V #

Read V Source # 
Show V Source # 

Methods

showsPrec :: Int -> V -> ShowS #

show :: V -> String #

showList :: [V] -> ShowS #

IsString V Source # 

Methods

fromString :: String -> V #

Pretty V Source # 

Methods

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

pPrint :: V -> Doc #

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

IsVariable V Source # 

Methods

variant :: V -> Set V -> V Source #

prefix :: String -> V -> V Source #

JustApply ApAtom Source # 
IsFirstOrder EqFormula Source # 
IsFirstOrder ApFormula Source # 
IsFirstOrder Formula Source # 
Monad m => Unify m (SkAtom, SkAtom) Source # 

Associated Types

type UTermOf (SkAtom, SkAtom) :: * Source #

type UTermOf (SkAtom, SkAtom) Source # 

Functions

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

type Arity = Int 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.

Minimal complete definition

vt, fApp, foldTerm

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 :: (TVarOf term -> r) -> (FunOf term -> [term] -> r) -> term -> r Source #

A fold over instances of IsTerm.

Instances

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

Associated Types

type TVarOf (Term function v) :: * Source #

type FunOf (Term function v) :: * Source #

Methods

vt :: TVarOf (Term function v) -> Term function v Source #

fApp :: FunOf (Term function v) -> [Term function v] -> Term function v Source #

foldTerm :: (TVarOf (Term function v) -> r) -> (FunOf (Term function v) -> [Term function v] -> r) -> Term function v -> r 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 # 
Monad m => Unify m (SkAtom, SkAtom) Source # 

Associated Types

type UTermOf (SkAtom, SkAtom) :: * Source #

(Eq function, Eq v) => Eq (Term function v) Source # 

Methods

(==) :: Term function v -> Term function v -> Bool #

(/=) :: Term function v -> Term function v -> Bool #

(Data function, Data v) => Data (Term function v) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Term function v -> c (Term function v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Term function v) #

toConstr :: Term function v -> Constr #

dataTypeOf :: Term function v -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Term function v)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Term function v)) #

gmapT :: (forall b. Data b => b -> b) -> Term function v -> Term function v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Term function v -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Term function v -> r #

gmapQ :: (forall d. Data d => d -> u) -> Term function v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Term function v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Term function v -> m (Term function v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Term function v -> m (Term function v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Term function v -> m (Term function v) #

(Ord function, Ord v) => Ord (Term function v) Source # 

Methods

compare :: Term function v -> Term function v -> Ordering #

(<) :: Term function v -> Term function v -> Bool #

(<=) :: Term function v -> Term function v -> Bool #

(>) :: Term function v -> Term function v -> Bool #

(>=) :: Term function v -> Term function v -> Bool #

max :: Term function v -> Term function v -> Term function v #

min :: Term function v -> Term function v -> Term function v #

(Read function, Read v) => Read (Term function v) Source # 

Methods

readsPrec :: Int -> ReadS (Term function v) #

readList :: ReadS [Term function v] #

readPrec :: ReadPrec (Term function v) #

readListPrec :: ReadPrec [Term function v] #

(IsVariable v, IsFunction function) => Show (Term function v) Source # 

Methods

showsPrec :: Int -> Term function v -> ShowS #

show :: Term function v -> String #

showList :: [Term function v] -> ShowS #

(IsVariable v, IsFunction function) => IsString (Term function v) Source # 

Methods

fromString :: String -> Term function v #

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

Methods

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

pPrint :: Term function v -> Doc #

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

(IsFunction function, IsVariable v) => HasFixity (Term function v) Source # 

Methods

precedence :: Term function v -> Precedence Source #

associativity :: Term function v -> Associativity Source #

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

Associated Types

type TVarOf (Term function v) :: * Source #

type FunOf (Term function v) :: * Source #

Methods

vt :: TVarOf (Term function v) -> Term function v Source #

fApp :: FunOf (Term function v) -> [Term function v] -> Term function v Source #

foldTerm :: (TVarOf (Term function v) -> r) -> (FunOf (Term function v) -> [Term function v] -> r) -> Term function v -> r Source #

type TVarOf (Term function v) Source # 
type TVarOf (Term function v) = v
type FunOf (Term function v) Source # 
type FunOf (Term function v) = function
type UTermOf (SkAtom, SkAtom) Source # 

type FTerm = Term FName V Source #

A term type with no Skolem functions