tpdb-2.2.0: Data Type for Rewriting Systems

Safe HaskellSafe
LanguageHaskell98

TPDB.Data

Description

Data types for rewrite systems and termination problems. A "bare" term rewrite system (list of rules and relative rules) is TRS v s. A termination problem is Problem v s. This contains a rewrite system plus extra information (strategy, theory, etc.)

Synopsis

Documentation

type TES = TRS Identifier Identifier Source #

legacy stuff (used in matchbox)

data Startterm Source #

Instances
Show Startterm Source # 
Instance details

Defined in TPDB.Data

data Theory Source #

Constructors

A 
C 
AC 
Instances
Eq Theory Source # 
Instance details

Defined in TPDB.Data

Methods

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

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

Ord Theory Source # 
Instance details

Defined in TPDB.Data

Read Theory Source # 
Instance details

Defined in TPDB.Data

Show Theory Source # 
Instance details

Defined in TPDB.Data

data Theorydecl v s Source #

Constructors

Property Theory [s]

example: "(AC plus)"

Equations [Rule (Term v s)] 

data Strategy Source #

Constructors

Full 
Innermost 
Outermost 
Instances
Show Strategy Source # 
Instance details

Defined in TPDB.Data

data Type Source #

Constructors

Termination 
Complexity 
Instances
Show Type Source # 
Instance details

Defined in TPDB.Data

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

data Problem v s Source #

Instances
(Pretty s, Pretty r, Variables (Term s r)) => Pretty (Problem s r) Source # 
Instance details

Defined in TPDB.Plain.Write

Methods

pretty :: Problem s r -> Doc ann #

prettyList :: [Problem s r] -> Doc ann #

type SRS s = RS s [s] Source #

type TRS v s = RS s (Term v s) Source #

data RS s r Source #

Constructors

RS 

Fields

Instances
Functor (RS s) Source # 
Instance details

Defined in TPDB.Data

Methods

fmap :: (a -> b) -> RS s a -> RS s b #

(<$) :: a -> RS s b -> RS s a #

Variables (SRS s) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (SRS s) :: Type Source #

Methods

variables :: SRS s -> Set (Var (SRS s)) Source #

Reader (SRS Identifier) Source # 
Instance details

Defined in TPDB.Plain.Read

Eq r => Eq (RS s r) Source # 
Instance details

Defined in TPDB.Data

Methods

(==) :: RS s r -> RS s r -> Bool #

(/=) :: RS s r -> RS s r -> Bool #

(Pretty s, PrettyTerm r, Variables (RS s r), Pretty (Var (RS s r))) => Pretty (RS s r) Source # 
Instance details

Defined in TPDB.Plain.Write

Methods

pretty :: RS s r -> Doc ann #

prettyList :: [RS s r] -> Doc ann #

Ord v => Variables (TRS v s) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (TRS v s) :: Type Source #

Methods

variables :: TRS v s -> Set (Var (TRS v s)) Source #

Reader (TRS Identifier Identifier) Source # 
Instance details

Defined in TPDB.Plain.Read

XmlContent (TRS Identifier Symbol) Source # 
Instance details

Defined in TPDB.CPF.Proof.Write

type Var (SRS s) Source # 
Instance details

Defined in TPDB.Data

type Var (SRS s) = Void
type Var (TRS v s) Source # 
Instance details

Defined in TPDB.Data

type Var (TRS v s) = v

data Replacementmap Source #

Constructors

Replacementmap [Int] 
Instances
Show Replacementmap Source # 
Instance details

Defined in TPDB.Data

data Signature Source #

Instances
Show Signature Source # 
Instance details

Defined in TPDB.Data

data Funcsym Source #

according to XTC spec

Instances
Show Funcsym Source # 
Instance details

Defined in TPDB.Data

class Ord (Var t) => Variables t where Source #

Associated Types

type Var t Source #

Methods

variables :: t -> Set (Var t) Source #

Instances
Variables [c] Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var [c] :: Type Source #

Methods

variables :: [c] -> Set (Var [c]) Source #

Variables r => Variables (Rule r) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (Rule r) :: Type Source #

Methods

variables :: Rule r -> Set (Var (Rule r)) Source #

Variables (SRS s) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (SRS s) :: Type Source #

Methods

variables :: SRS s -> Set (Var (SRS s)) Source #

Ord v => Variables (Term v c) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (Term v c) :: Type Source #

Methods

variables :: Term v c -> Set (Var (Term v c)) Source #

Ord v => Variables (TRS v s) Source # 
Instance details

Defined in TPDB.Data

Associated Types

type Var (TRS v s) :: Type Source #

Methods

variables :: TRS v s -> Set (Var (TRS v s)) Source #

data Identifier Source #

Constructors

Identifier 

Fields

Instances
Eq Identifier Source # 
Instance details

Defined in TPDB.Data

Ord Identifier Source # 
Instance details

Defined in TPDB.Data

Show Identifier Source # 
Instance details

Defined in TPDB.Data

Hashable Identifier Source # 
Instance details

Defined in TPDB.Data

Pretty Identifier Source # 
Instance details

Defined in TPDB.Plain.Write

Methods

pretty :: Identifier -> Doc ann #

prettyList :: [Identifier] -> Doc ann #

Reader Identifier Source # 
Instance details

Defined in TPDB.Plain.Read

XmlContent Identifier Source #

FIXME: move to separate module

Instance details

Defined in TPDB.Data.Xml

Reader (SRS Identifier) Source # 
Instance details

Defined in TPDB.Plain.Read

Reader v => Reader (Term v Identifier) Source # 
Instance details

Defined in TPDB.Plain.Read

Reader (TRS Identifier Identifier) Source # 
Instance details

Defined in TPDB.Plain.Read

XmlContent (TRS Identifier Symbol) Source # 
Instance details

Defined in TPDB.CPF.Proof.Write

strict_rules :: RS s b -> [(b, b)] Source #

weak_rules :: RS s b -> [(b, b)] Source #

equal_rules :: RS s b -> [(b, b)] Source #

from_strict_rules :: Bool -> [(t, t)] -> RS i t Source #

with_rules :: RS s r1 -> [Rule r2] -> RS s r2 Source #