th-context-0.24: Test instance context

Safe HaskellNone
LanguageHaskell2010

Data.Logic.ATP.TH

Contents

Description

ATP instances for the template haskell type Type, and the conjunction of such types, [Type]. In these instances, almost every role is played by Type. It might a case where the tagged package could be used to advantage. A list represents conjunction, but there is no disjunction operation, nor any derived from it like implication or equivalence.

Synopsis

Documentation

unfoldApply :: Type -> [Type] -> (Type, [Type]) Source #

Helper function to interpret a type application: unfoldApply (AppT (AppT (AppT (VarT (mkName "a")) StarT) ListT) ArrowT) -> (VarT (mkName "a"), [StarT, ListT, ArrowT]) The inverse is uncurry . foldl AppT.

Orphan instances

IsString Type Source # 

Methods

fromString :: String -> Type #

HasEquate Type Source # 

Methods

equate :: TermOf Type -> TermOf Type -> Type #

foldEquate :: (TermOf Type -> TermOf Type -> r) -> (PredOf Type -> [TermOf Type] -> r) -> Type -> r #

IsPredicate Type Source # 
HasApply Type Source # 

Associated Types

type PredOf Type :: * #

type TermOf Type :: * #

Methods

applyPredicate :: PredOf Type -> [TermOf Type] -> Type #

foldApply' :: (Type -> r) -> (PredOf Type -> [TermOf Type] -> r) -> Type -> r #

overterms :: (TermOf Type -> r -> r) -> r -> Type -> r #

onterms :: (TermOf Type -> TermOf Type) -> Type -> Type #

IsVariable Type Source # 

Methods

variant :: Type -> Set Type -> Type #

prefix :: String -> Type -> Type #

IsFunction Type Source # 
IsTerm Type Source # 

Associated Types

type TVarOf Type :: * #

type FunOf Type :: * #

Methods

vt :: TVarOf Type -> Type #

fApp :: FunOf Type -> [Type] -> Type #

foldTerm :: (TVarOf Type -> r) -> (FunOf Type -> [Type] -> r) -> Type -> r #

IsLiteral Type Source # 

Methods

naiveNegate :: Type -> Type #

foldNegation :: (Type -> r) -> (Type -> r) -> Type -> r #

foldLiteral' :: (Type -> r) -> (Type -> r) -> (Bool -> r) -> (AtomOf Type -> r) -> Type -> r #

JustLiteral Type Source # 
IsAtom Type Source # 
IsFormula Type Source # 

Associated Types

type AtomOf Type :: * #

Methods

true :: Type #

false :: Type #

asBool :: Type -> Maybe Bool #

atomic :: AtomOf Type -> Type #

overatoms :: (AtomOf Type -> r -> r) -> Type -> r -> r #

onatoms :: (AtomOf Type -> AtomOf Type) -> Type -> Type #

HasFixity Type Source # 
Pretty Type Source # 
Monad m => Unify m Type Source # 

Associated Types

type UTermOf Type :: * #

Methods

unify' :: Type -> StateT (Map (TVarOf (UTermOf Type)) (UTermOf Type)) m () #

Monad m => Unify m [Type] Source # 

Associated Types

type UTermOf [Type] :: * #

Methods

unify' :: [Type] -> StateT (Map (TVarOf (UTermOf [Type])) (UTermOf [Type])) m () #