Safe Haskell | None |
---|
TPDB.CPF.Proof.Type
Description
internal representation of CPF termination proofs, see http://cl-informatik.uibk.ac.at/software/cpf/
- data CertificationProblem = CertificationProblem {}
- data Origin = ProofOrigin Tool
- data Tool = Tool {}
- data CertificationProblemInput = TrsInput {}
- data Proof = TrsTerminationProof TrsTerminationProof
- data Sharp i
- data DPS = forall s . (XmlContent s, Typeable s) => DPS [Rule (Term Identifier s)]
- data TrsTerminationProof
- = RIsEmpty
- | RuleRemoval { }
- | DpTrans { }
- | Semlab { }
- | Unlab { }
- | StringReversal { }
- data Model = FiniteModel {
- carrierSize :: Int
- data DpProof
- data OrderingConstraintProof = RedPair {}
- data Interpretation = Interpretation {}
- data Interpretation_Type = Matrix_Interpretation {}
- data Domain
- data Interpret = forall s . XmlContent s => Interpret {}
- data Value = Polynomial Polynomial
- data Polynomial
- data Coefficient
- = Vector [Coefficient]
- | Matrix [Coefficient]
- | forall a . XmlContent a => Coefficient_Coefficient a
- data Exotic
- class ToExotic a where
- data Identifier
- type TES = TRS Identifier Identifier
Documentation
data CertificationProblem Source
Constructors
CertificationProblem | |
Fields
|
Instances
data CertificationProblemInput Source
Constructors
TrsInput | this is actually not true, since instead of copying from XTC, CPF format repeats the definition of TRS, and it's a different one (relative rules are extra) |
Fields |
Constructors
TrsTerminationProof TrsTerminationProof |
Instances
Constructors
forall s . (XmlContent s, Typeable s) => DPS [Rule (Term Identifier s)] |
Instances
data TrsTerminationProof Source
Constructors
RIsEmpty | |
RuleRemoval | |
DpTrans | |
Fields
| |
Semlab | |
Fields | |
Unlab | |
Fields | |
StringReversal | |
Fields |
Constructors
PIsEmpty | |
RedPairProc | |
Instances
data OrderingConstraintProof Source
Constructors
RedPair | |
Fields |
data Interpretation_Type Source
Constructors
Matrix_Interpretation | |
Instances
Instances
data Polynomial Source
Constructors
Sum [Polynomial] | |
Product [Polynomial] | |
Polynomial_Coefficient Coefficient | |
Polynomial_Variable String |
Instances
data Coefficient Source
Constructors
Vector [Coefficient] | |
Matrix [Coefficient] | |
forall a . XmlContent a => Coefficient_Coefficient a |
Instances
Constructors
Minus_Infinite | |
E_Integer Integer | |
E_Rational Rational | |
Plus_Infinite |
Instances
data Identifier Source
Instances
Eq Identifier | |
Ord Identifier | |
Show Identifier | |
Typeable Identifier | |
XmlContent Identifier | FIXME: move to separate module |
Hashable Identifier | |
Pretty Identifier | |
XRead Identifier | |
Reader Identifier | |
Reader (SRS Identifier) | |
Reader v => Reader (Term v Identifier) | |
Reader (TRS Identifier Identifier) |
type TES = TRS Identifier IdentifierSource
legaca stuff (used in matchbox)