ideas-1.6: Feedback services for intelligent tutoring systems

Maintainerbastiaan.heeren@ou.nl
Stabilityprovisional
Portabilityportable (depends on ghc)
Safe HaskellNone
LanguageHaskell98

Ideas.Common.Rewriting.Term

Contents

Description

A simple data type for term rewriting

Synopsis

Symbols

Terms

data Term Source #

Instances

Eq Term Source # 

Methods

(==) :: Term -> Term -> Bool #

(/=) :: Term -> Term -> Bool #

Ord Term Source # 

Methods

compare :: Term -> Term -> Ordering #

(<) :: Term -> Term -> Bool #

(<=) :: Term -> Term -> Bool #

(>) :: Term -> Term -> Bool #

(>=) :: Term -> Term -> Bool #

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

Read Term Source # 
Show Term Source # 

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Arbitrary Term Source # 

Methods

arbitrary :: Gen Term #

shrink :: Term -> [Term] #

Uniplate Term Source # 

Methods

uniplate :: Term -> (Str Term, Str Term -> Term) #

descend :: (Term -> Term) -> Term -> Term #

descendM :: Monad m => (Term -> m Term) -> Term -> m Term #

WithMetaVars Term Source # 

Methods

metaVar :: Int -> Term Source #

getMetaVar :: Monad m => Term -> m Int Source #

WithVars Term Source # 
WithFunctions Term Source # 
IsTerm Term Source # 
Reference Term Source # 

Methods

makeRef :: IsId n => n -> Ref Term Source #

makeRefList :: IsId n => n -> Ref [Term] Source #

Different Term Source # 

Methods

different :: (Term, Term) Source #

class IsTerm a where Source #

Minimal complete definition

toTerm, fromTerm

Methods

toTerm :: a -> Term Source #

toTermList :: [a] -> Term Source #

fromTerm :: MonadPlus m => Term -> m a Source #

fromTermList :: MonadPlus m => Term -> m [a] Source #

Instances

IsTerm Bool Source # 
IsTerm Char Source # 
IsTerm Double Source # 
IsTerm Int Source # 
IsTerm Integer Source # 
IsTerm ShowString Source # 
IsTerm Term Source # 
IsTerm a => IsTerm [a] Source # 

Methods

toTerm :: [a] -> Term Source #

toTermList :: [[a]] -> Term Source #

fromTerm :: MonadPlus m => Term -> m [a] Source #

fromTermList :: MonadPlus m => Term -> m [[a]] Source #

IsTerm a => IsTerm (Maybe a) Source # 
(IsTerm a, Ord a) => IsTerm (Set a) Source # 

Methods

toTerm :: Set a -> Term Source #

toTermList :: [Set a] -> Term Source #

fromTerm :: MonadPlus m => Term -> m (Set a) Source #

fromTermList :: MonadPlus m => Term -> m [Set a] Source #

(IsTerm a, IsTerm b) => IsTerm (Either a b) Source # 

Methods

toTerm :: Either a b -> Term Source #

toTermList :: [Either a b] -> Term Source #

fromTerm :: MonadPlus m => Term -> m (Either a b) Source #

fromTermList :: MonadPlus m => Term -> m [Either a b] Source #

(IsTerm a, IsTerm b) => IsTerm (a, b) Source # 

Methods

toTerm :: (a, b) -> Term Source #

toTermList :: [(a, b)] -> Term Source #

fromTerm :: MonadPlus m => Term -> m (a, b) Source #

fromTermList :: MonadPlus m => Term -> m [(a, b)] Source #

(IsTerm a, IsTerm b, Ord a) => IsTerm (Map a b) Source # 

Methods

toTerm :: Map a b -> Term Source #

toTermList :: [Map a b] -> Term Source #

fromTerm :: MonadPlus m => Term -> m (Map a b) Source #

fromTermList :: MonadPlus m => Term -> m [Map a b] Source #

fromTermM :: (Monad m, IsTerm a) => Term -> m a Source #

fromTermWith :: (Monad m, IsTerm a) => (Symbol -> [a] -> m a) -> Term -> m a Source #

Functions and symbols

class WithFunctions a where Source #

Minimal complete definition

function, getFunction

Methods

symbol :: Symbol -> a Source #

function :: Symbol -> [a] -> a Source #

getSymbol :: Monad m => a -> m Symbol Source #

getFunction :: Monad m => a -> m (Symbol, [a]) Source #

isFunction :: (WithFunctions a, Monad m) => Symbol -> a -> m [a] Source #

unary :: WithFunctions a => Symbol -> a -> a Source #

binary :: WithFunctions a => Symbol -> a -> a -> a Source #

ternary :: WithFunctions a => Symbol -> a -> a -> a -> a Source #

isUnary :: (WithFunctions a, Monad m) => Symbol -> a -> m a Source #

isBinary :: (WithFunctions a, Monad m) => Symbol -> a -> m (a, a) Source #

Variables

class WithVars a where Source #

Minimal complete definition

variable, getVariable

Methods

variable :: String -> a Source #

getVariable :: Monad m => a -> m String Source #

vars :: (Uniplate a, WithVars a) => a -> [String] Source #

hasVar :: (Uniplate a, WithVars a) => String -> a -> Bool Source #

Meta variables

class WithMetaVars a where Source #

Minimal complete definition

metaVar, getMetaVar

Methods

metaVar :: Int -> a Source #

getMetaVar :: Monad m => a -> m Int Source #

Instances