tpdb-1.1.1: Data Type for Rewriting Systems

Safe HaskellSafe-Inferred
LanguageHaskell98

TPDB.Data.Term

Synopsis

Documentation

data Term v s Source

Constructors

Var v 
Node s [Term v s] 

Instances

Functor (Term v) 
(HTypeable (Rule (Term v c)), XmlContent (Term v c)) => XmlContent (Rule (Term v c)) 
HTypeable (Rule (Term v c)) 
(Eq v, Eq s) => Eq (Term v s) 
(Ord v, Ord s) => Ord (Term v s) 
(Show v, Show s) => Show (Term v s) 
(Typeable * (Term v c), XmlContent v, XmlContent c) => XmlContent (Term v c) 
XmlContent (TRS Identifier Symbol) 
(Pretty v, Pretty s) => Pretty (Term v s) 
(Pretty v, Pretty s) => PrettyTerm (Term v s) 
Reader v => Reader (Term v Identifier) 
Reader (TRS Identifier Identifier) 
Typeable (* -> * -> *) Term 

vmap :: (v -> u) -> Term v s -> Term u s Source

positions :: Term v c -> [(Position, Term v c)] Source

pos :: Term v c -> [Position] Source

all positions

sympos :: Term v c -> [Position] Source

non-variable positions

varpos :: Term v c -> [Position] Source

variable positions

leafpos :: Term v c -> [Position] Source

leaf positions (= nullary symbols)

subterms :: Term v c -> [Term v c] Source

isSubtermOf :: (Eq v, Eq c) => Term v c -> Term v c -> Bool Source

isStrictSubtermOf :: (Eq v, Eq c) => Term v c -> Term v c -> Bool Source

pmap :: (Position -> c -> d) -> Term v c -> Term v d Source

compute new symbol at position, giving the position

rpmap :: (Position -> c -> d) -> Term v c -> Term v d Source

compute new symbol from *reverse* position and previous symbol this is more efficient (no reverse needed)

peek :: Term v c -> Position -> Term v c Source

poke_symbol :: Term v c -> (Position, c) -> Term v c Source

warning: don't check arity

poke :: Term v c -> (Position, Term v c) -> Term v c Source

pokes :: Term v c -> [(Position, Term v c)] -> Term v c Source

symsl :: Term v c -> [c] Source

in preorder

syms :: Ord c => Term v c -> Set c Source

lsyms :: Ord c => Term v c -> [c] Source

vars :: Ord v => Term v c -> Set v Source

isvar :: Term v c -> Bool Source

lvars :: Ord v => Term v c -> [v] Source

list of variables (each occurs once, unspecified ordering)

voccs :: Term v c -> [v] Source

list of variables (in pre-order, with duplicates)