| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
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 {}
- ignoredOrigin :: Origin
- data Tool = Tool {}
- data CertificationProblemInput
- data Proof
- data DPS = forall s . (XmlContent s, Typeable s, Eq s) => DPS [Rule (Term Identifier s)]
- data ComplexityProof = ComplexityProofFIXME ()
- data ComplexityMeasure
- data ComplexityClass = ComplexityClassPolynomial {}
- data TrsNonterminationProof = TrsNonterminationProofFIXME ()
- data TrsTerminationProof
- = RIsEmpty
- | RuleRemoval { }
- | DpTrans { }
- | Semlab { }
- | Unlab { }
- | StringReversal { }
- data Model = FiniteModel Int [Interpret]
- data DpProof
- = PIsEmpty
- | RedPairProc { }
- | DepGraphProc [DepGraphComponent]
- | SemLabProc { }
- | UnlabProc { }
- data DepGraphComponent = DepGraphComponent {
- dgcRealScc :: Bool
- dgcDps :: DPS
- dgcDpProof :: DpProof
- data OrderingConstraintProof = OCPRedPair RedPair
- data RedPair
- data Interpretation = Interpretation {}
- data Interpretation_Type = Matrix_Interpretation {}
- data Domain
- data Interpret = Interpret {}
- data Value
- data Polynomial
- data ArithFunction
- data Symbol
- data Label
- data Coefficient
- = Vector [Coefficient]
- | Matrix [Coefficient]
- | forall a . (Eq a, XmlContent a) => Coefficient_Coefficient a
- data Exotic
- class ToExotic a where
- data PathOrder = PathOrder [PrecedenceEntry] [ArgumentFilterEntry]
- data PrecedenceEntry = PrecedenceEntry {}
- data ArgumentFilterEntry = ArgumentFilterEntry {}
- data Identifier
- type TES = TRS Identifier Identifier
Documentation
data CertificationProblem Source
Constructors
| CertificationProblem | |
Fields
| |
Constructors
| ProofOrigin | |
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 | |
| ComplexityInput | |
Constructors
| forall s . (XmlContent s, Typeable s, Eq s) => DPS [Rule (Term Identifier s)] |
data ComplexityClass Source
Constructors
| ComplexityClassPolynomial | it seems the degree must always be given in CPF, although the category spec also allows POLY http://cl-informatik.uibk.ac.at/users/georg/cbr/competition/rules.php |
Instances
data TrsTerminationProof Source
Constructors
| RIsEmpty | |
| RuleRemoval | |
| DpTrans | |
Fields
| |
| Semlab | |
Fields | |
| Unlab | |
Fields | |
| StringReversal | |
Fields | |
Constructors
| FiniteModel Int [Interpret] |
Constructors
| PIsEmpty | |
| RedPairProc | |
Fields | |
| DepGraphProc [DepGraphComponent] | |
| SemLabProc | |
| UnlabProc | |
data DepGraphComponent Source
Constructors
| DepGraphComponent | |
Fields
| |
data OrderingConstraintProof Source
Constructors
| OCPRedPair RedPair |
Constructors
| RPInterpretation Interpretation | |
| RPPathOrder PathOrder |
data Interpretation_Type Source
Constructors
| Matrix_Interpretation | |
Constructors
| Polynomial Polynomial | |
| ArithFunction ArithFunction |
data Polynomial Source
Constructors
| Sum [Polynomial] | |
| Product [Polynomial] | |
| Polynomial_Coefficient Coefficient | |
| Polynomial_Variable String |
Instances
data ArithFunction Source
Constructors
| AFNatural Integer | |
| AFVariable Integer | |
| AFSum [ArithFunction] | |
| AFProduct [ArithFunction] | |
| AFMin [ArithFunction] | |
| AFMax [ArithFunction] | |
| AFIfEqual ArithFunction ArithFunction ArithFunction ArithFunction |
Instances
Instances
data Coefficient Source
Constructors
| Vector [Coefficient] | |
| Matrix [Coefficient] | |
| forall a . (Eq a, XmlContent a) => Coefficient_Coefficient a |
Instances
Constructors
| Minus_Infinite | |
| E_Integer Integer | |
| E_Rational Rational | |
| Plus_Infinite |
Constructors
| PathOrder [PrecedenceEntry] [ArgumentFilterEntry] |
data PrecedenceEntry Source
Constructors
| PrecedenceEntry | |
data ArgumentFilterEntry Source
Constructors
| ArgumentFilterEntry | |
data Identifier Source
Instances
| Eq Identifier | |
| Ord Identifier | |
| Show Identifier | |
| XmlContent Identifier | FIXME: move to separate module |
| Hashable Identifier | |
| Pretty Identifier | |
| Reader Identifier | |
| Typeable * Identifier | |
| Reader (SRS Identifier) | |
| XmlContent (TRS Identifier Symbol) | |
| Reader v => Reader (Term v Identifier) | |
| Reader (TRS Identifier Identifier) |
type TES = TRS Identifier Identifier Source
legaca stuff (used in matchbox)