logic-classes-1.4.7: Framework for propositional and first order logic, theorem proving

Safe HaskellNone

Data.Logic.Classes.Apply

Description

The Apply class represents a type of atom the only supports predicate application.

Synopsis

Documentation

class Predicate p => Apply atom p term | atom -> p term whereSource

Methods

foldApply :: (p -> [term] -> r) -> (Bool -> r) -> atom -> rSource

apply' :: p -> [term] -> atomSource

Instances

Apply FOL String TermType 
Apply FOLEQ PredName TermType

Using PredName for the predicate type is not quite appropriate here, but we need to implement this instance so we can use it as a superclass of AtomEq below.

(Variable v, Predicate p, Function f v) => Apply (Sentence v p f) p (CTerm v f) 

class (Arity p, Constants p, Eq p, Ord p, Data p, Pretty p) => Predicate p Source

apply :: Apply atom p term => p -> [term] -> atomSource

apply' with an arity check - clients should always call this.

zipApplys :: Apply atom p term => (p -> [term] -> p -> [term] -> Maybe r) -> (Bool -> Bool -> Maybe r) -> atom -> atom -> Maybe rSource

apply0 :: Apply atom p term => p -> atomSource

apply1 :: Apply atom p term => p -> term -> atomSource

apply2 :: Apply atom p term => p -> term -> term -> atomSource

apply3 :: Apply atom p term => p -> term -> term -> term -> atomSource

apply4 :: Apply atom p term => p -> term -> term -> term -> term -> atomSource

apply5 :: Apply atom p term => p -> term -> term -> term -> term -> term -> atomSource

apply6 :: Apply atom p term => p -> term -> term -> term -> term -> term -> term -> atomSource

apply7 :: Apply atom p term => p -> term -> term -> term -> term -> term -> term -> term -> atomSource

showApply :: (Apply atom p term, Term term v f, Show v, Show p, Show f) => atom -> StringSource

prettyApply :: (Apply atom p term, Term term v f) => (v -> Doc) -> (p -> Doc) -> (f -> Doc) -> Int -> atom -> DocSource

varApply :: (Apply atom p term, Term term v f) => atom -> Set vSource

Return the variables that occur in an instance of Apply.

substApply :: (Apply atom p term, Constants atom, Term term v f) => Map v term -> atom -> atomSource