Safe Haskell | None |
---|---|
Language | Haskell2010 |
Jukebox.Form
Documentation
Instances
Show Term Source # | |
Eq Term Source # | |
Ord Term Source # | |
Symbolic Term Source # | |
Typed Term Source # | |
Unpack Term Source # | |
Named Term Source # | |
TermLike Term Source # | |
Pretty Term Source # | |
Defined in Jukebox.TPTP.Print Methods pPrintPrec :: PrettyLevel -> Rational -> Term -> Doc # pPrintList :: PrettyLevel -> [Term] -> Doc # |
Instances
Foldable Signed Source # | |
Defined in Jukebox.Form Methods fold :: Monoid m => Signed m -> m # foldMap :: Monoid m => (a -> m) -> Signed a -> m # foldMap' :: Monoid m => (a -> m) -> Signed a -> m # foldr :: (a -> b -> b) -> b -> Signed a -> b # foldr' :: (a -> b -> b) -> b -> Signed a -> b # foldl :: (b -> a -> b) -> b -> Signed a -> b # foldl' :: (b -> a -> b) -> b -> Signed a -> b # foldr1 :: (a -> a -> a) -> Signed a -> a # foldl1 :: (a -> a -> a) -> Signed a -> a # elem :: Eq a => a -> Signed a -> Bool # maximum :: Ord a => Signed a -> a # minimum :: Ord a => Signed a -> a # | |
Traversable Signed Source # | |
Functor Signed Source # | |
Show a => Show (Signed a) Source # | |
Eq a => Eq (Signed a) Source # | |
Ord a => Ord (Signed a) Source # | |
Defined in Jukebox.Form | |
Symbolic a => Symbolic (Signed a) Source # | |
Symbolic a => Unpack (Signed a) Source # | |
Constructors
Literal Literal | |
Not Form | |
And [Form] | |
Or [Form] | |
Equiv Form Form | |
ForAll !(Bind Form) | |
Exists !(Bind Form) | |
Connective Connective Form Form |
data Connective Source #
Instances
Show Connective Source # | |
Defined in Jukebox.TPTP.Print Methods showsPrec :: Int -> Connective -> ShowS # show :: Connective -> String # showList :: [Connective] -> ShowS # | |
Eq Connective Source # | |
Defined in Jukebox.Form | |
Ord Connective Source # | |
Defined in Jukebox.Form Methods compare :: Connective -> Connective -> Ordering # (<) :: Connective -> Connective -> Bool # (<=) :: Connective -> Connective -> Bool # (>) :: Connective -> Connective -> Bool # (>=) :: Connective -> Connective -> Bool # max :: Connective -> Connective -> Connective # min :: Connective -> Connective -> Connective # |
connective :: Connective -> Form -> Form -> Form Source #
notInwards :: Form -> Form Source #
Constructors
CNF | |
Fields
|
toLiterals :: Clause -> [Literal] Source #
Constructors
Axiom | |
Hypothesis | |
Definition | |
Assumption | |
Lemma | |
TheoremKind | |
NegatedConjecture |
Constructors
Conjecture | |
Question |
Constructors
Sat SatReason (Maybe Model) | |
Unsat UnsatReason (Maybe CNFRefutation) | |
NoAnswer NoAnswerReason |
data NoAnswerReason Source #
Instances
Show NoAnswerReason Source # | |
Defined in Jukebox.Form Methods showsPrec :: Int -> NoAnswerReason -> ShowS # show :: NoAnswerReason -> String # showList :: [NoAnswerReason] -> ShowS # | |
Eq NoAnswerReason Source # | |
Defined in Jukebox.Form Methods (==) :: NoAnswerReason -> NoAnswerReason -> Bool # (/=) :: NoAnswerReason -> NoAnswerReason -> Bool # | |
Ord NoAnswerReason Source # | |
Defined in Jukebox.Form Methods compare :: NoAnswerReason -> NoAnswerReason -> Ordering # (<) :: NoAnswerReason -> NoAnswerReason -> Bool # (<=) :: NoAnswerReason -> NoAnswerReason -> Bool # (>) :: NoAnswerReason -> NoAnswerReason -> Bool # (>=) :: NoAnswerReason -> NoAnswerReason -> Bool # max :: NoAnswerReason -> NoAnswerReason -> NoAnswerReason # min :: NoAnswerReason -> NoAnswerReason -> NoAnswerReason # |
Constructors
Satisfiable | |
CounterSatisfiable |
Instances
Show SatReason Source # | |
Eq SatReason Source # | |
Ord SatReason Source # | |
data UnsatReason Source #
Constructors
Unsatisfiable | |
Theorem |
Instances
Show UnsatReason Source # | |
Defined in Jukebox.Form Methods showsPrec :: Int -> UnsatReason -> ShowS # show :: UnsatReason -> String # showList :: [UnsatReason] -> ShowS # | |
Eq UnsatReason Source # | |
Defined in Jukebox.Form | |
Ord UnsatReason Source # | |
Defined in Jukebox.Form Methods compare :: UnsatReason -> UnsatReason -> Ordering # (<) :: UnsatReason -> UnsatReason -> Bool # (<=) :: UnsatReason -> UnsatReason -> Bool # (>) :: UnsatReason -> UnsatReason -> Bool # (>=) :: UnsatReason -> UnsatReason -> Bool # max :: UnsatReason -> UnsatReason -> UnsatReason # min :: UnsatReason -> UnsatReason -> UnsatReason # |
type CNFRefutation = [String] Source #
explainAnswer :: Answer -> String Source #
Instances
Foldable Input Source # | |
Defined in Jukebox.Form Methods fold :: Monoid m => Input m -> m # foldMap :: Monoid m => (a -> m) -> Input a -> m # foldMap' :: Monoid m => (a -> m) -> Input a -> m # foldr :: (a -> b -> b) -> b -> Input a -> b # foldr' :: (a -> b -> b) -> b -> Input a -> b # foldl :: (b -> a -> b) -> b -> Input a -> b # foldl' :: (b -> a -> b) -> b -> Input a -> b # foldr1 :: (a -> a -> a) -> Input a -> a # foldl1 :: (a -> a -> a) -> Input a -> a # elem :: Eq a => a -> Input a -> Bool # maximum :: Ord a => Input a -> a # minimum :: Ord a => Input a -> a # | |
Traversable Input Source # | |
Functor Input Source # | |
Pretty a => Show (Input a) Source # | |
Symbolic a => Symbolic (Input a) Source # | |
Symbolic a => Unpack (Input a) Source # | |
Pretty a => Pretty (Input a) Source # | |
Defined in Jukebox.TPTP.Print Methods pPrintPrec :: PrettyLevel -> Rational -> Input a -> Doc # pPrintList :: PrettyLevel -> [Input a] -> Doc # |
data InputSource Source #
Constructors
InputPlus | |
Fields
|
Constructors
Form :: TypeOf Form | |
Clause_ :: TypeOf Clause | |
Term :: TypeOf Term | |
Atomic :: TypeOf Atomic | |
Signed :: forall a1. (Symbolic a1, Symbolic (Signed a1)) => TypeOf (Signed a1) | |
Bind_ :: forall a1. (Symbolic a1, Symbolic (Bind a1)) => TypeOf (Bind a1) | |
List :: forall a1. (Symbolic a1, Symbolic [a1]) => TypeOf [a1] | |
Input_ :: forall a1. (Symbolic a1, Symbolic (Input a1)) => TypeOf (Input a1) | |
CNF_ :: TypeOf CNF |
class Symbolic a where Source #
Instances
Symbolic Atomic Source # | |
Symbolic CNF Source # | |
Symbolic Clause Source # | |
Symbolic Form Source # | |
Symbolic Term Source # | |
Symbolic a => Symbolic (Bind a) Source # | |
Symbolic a => Symbolic (Input a) Source # | |
Symbolic a => Symbolic (Signed a) Source # | |
Symbolic a => Symbolic [a] Source # | |
Defined in Jukebox.Form |
recursively :: Symbolic a => (forall a1. Symbolic a1 => a1 -> a1) -> a -> a Source #
recursivelyM :: (Monad m, Symbolic a) => (forall a1. Symbolic a1 => a1 -> m a1) -> a -> m a Source #
termsAndBinders :: Symbolic a => (Term -> DList b) -> (forall a1. Symbolic a1 => Bind a1 -> [b]) -> (forall a1. Symbolic a1 => Input a1 -> [b]) -> a -> [b] Source #
eraseTypes :: Symbolic a => a -> a Source #
uniqueNames :: Symbolic a => a -> NameM a Source #