Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | None |
Language | Haskell98 |
A simple data type for term rewriting
- data Symbol
- newSymbol :: IsId a => a -> Symbol
- isAssociative :: Symbol -> Bool
- makeAssociative :: Symbol -> Symbol
- nothingSymbol :: Symbol
- trueSymbol :: Symbol
- falseSymbol :: Symbol
- data Term
- class IsTerm a where
- termView :: IsTerm a => View Term a
- fromTermM :: (Monad m, IsTerm a) => Term -> m a
- fromTermWith :: (Monad m, IsTerm a) => (Symbol -> [a] -> m a) -> Term -> m a
- class WithFunctions a where
- isSymbol :: WithFunctions a => Symbol -> a -> Bool
- isFunction :: (WithFunctions a, Monad m) => Symbol -> a -> m [a]
- unary :: WithFunctions a => Symbol -> a -> a
- binary :: WithFunctions a => Symbol -> a -> a -> a
- ternary :: WithFunctions a => Symbol -> a -> a -> a -> a
- isUnary :: (WithFunctions a, Monad m) => Symbol -> a -> m a
- isBinary :: (WithFunctions a, Monad m) => Symbol -> a -> m (a, a)
- class WithVars a where
- isVariable :: WithVars a => a -> Bool
- vars :: (Uniplate a, WithVars a) => a -> [String]
- varSet :: (Uniplate a, WithVars a) => a -> Set String
- hasVar :: (Uniplate a, WithVars a) => String -> a -> Bool
- withoutVar :: (Uniplate a, WithVars a) => String -> a -> Bool
- hasSomeVar :: (Uniplate a, WithVars a) => a -> Bool
- hasNoVar :: (Uniplate a, WithVars a) => a -> Bool
- variableView :: WithVars a => View a String
- class WithMetaVars a where
- isMetaVar :: WithMetaVars a => a -> Bool
- metaVars :: (Uniplate a, WithMetaVars a) => a -> [Int]
- metaVarSet :: (Uniplate a, WithMetaVars a) => a -> IntSet
- hasMetaVar :: (Uniplate a, WithMetaVars a) => Int -> a -> Bool
- nextMetaVar :: (Uniplate a, WithMetaVars a) => a -> Int
Symbols
isAssociative :: Symbol -> Bool Source #
makeAssociative :: Symbol -> Symbol Source #
trueSymbol :: Symbol Source #
falseSymbol :: Symbol Source #
Terms
toTermList :: [a] -> Term Source #
fromTerm :: MonadPlus m => Term -> m a Source #
fromTermList :: MonadPlus m => Term -> m [a] Source #
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 # | |
IsTerm a => IsTerm (Maybe a) Source # | |
(IsTerm a, Ord a) => IsTerm (Set a) Source # | |
(IsTerm a, IsTerm b) => IsTerm (Either a b) Source # | |
(IsTerm a, IsTerm b) => IsTerm (a, b) Source # | |
(IsTerm a, IsTerm b, Ord a) => IsTerm (Map a b) Source # | |
Functions and symbols
class WithFunctions a where 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 #
Variables
isVariable :: WithVars a => a -> Bool Source #
Meta variables
class WithMetaVars a where Source #
isMetaVar :: WithMetaVars a => a -> Bool Source #
metaVarSet :: (Uniplate a, WithMetaVars a) => a -> IntSet Source #
hasMetaVar :: (Uniplate a, WithMetaVars a) => Int -> a -> Bool Source #
nextMetaVar :: (Uniplate a, WithMetaVars a) => a -> Int Source #