Safe Haskell | Safe-Inferred |
---|
- data Identifier = Identifier {}
- mk :: Int -> String -> Identifier
- data Relation
- data Rule a = Rule {}
- strict :: Rule a -> Bool
- weak :: Rule a -> Bool
- equal :: Rule a -> Bool
- data RS s r = RS {}
- strict_rules :: RS s t -> [(t, t)]
- weak_rules :: RS s t -> [(t, t)]
- equal_rules :: RS s t -> [(t, t)]
- type TRS v s = RS s (Term v s)
- type SRS s = RS s [s]
- data Problem v s = Problem {}
- data Type
- data Strategy
- data Startterm
- type TES = TRS Identifier Identifier
- type SES = SRS Identifier
- mknullary :: String -> Identifier
- mkunary :: String -> Identifier
- from_strict_rules :: Bool -> [(t, t)] -> RS i t
- with_rules :: RS s t -> [Rule r] -> RS s r
- module TPDB.Data.Term
Documentation
data Identifier Source
Eq Identifier | |
Ord Identifier | |
Show Identifier | |
Typeable Identifier | |
XmlContent Identifier | FIXME: move to separate module |
Hashable Identifier | |
Pretty Identifier | |
Reader Identifier | |
Reader (SRS Identifier) | |
XmlContent (TRS Identifier Symbol) | |
Reader v => Reader (Term v Identifier) | |
Reader (TRS Identifier Identifier) |
mk :: Int -> String -> IdentifierSource
Typeable2 RS | |
Functor (RS s) | |
Reader (SRS Identifier) | |
Eq r => Eq (RS s r) | |
XmlContent (TRS Identifier Symbol) | |
(Pretty s, PrettyTerm r) => Pretty (RS s r) | |
Reader (TRS Identifier Identifier) |
strict_rules :: RS s t -> [(t, t)]Source
weak_rules :: RS s t -> [(t, t)]Source
equal_rules :: RS s t -> [(t, t)]Source
type TES = TRS Identifier IdentifierSource
legaca stuff (used in matchbox)
type SES = SRS IdentifierSource
mknullary :: String -> IdentifierSource
mkunary :: String -> IdentifierSource
from_strict_rules :: Bool -> [(t, t)] -> RS i tSource
with_rules :: RS s t -> [Rule r] -> RS s rSource
module TPDB.Data.Term