Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | None |
Language | Haskell98 |
A rule is just a transformation with some meta-information, such as a name (which should be unique) and properties such as "buggy" or "minor". Rules can be lifted with a view using the LiftView type class.
- data Rule a
- transformation :: Rule a -> Transformation a
- recognizer :: Recognizable f => f a -> Recognizer a
- checkReferences :: Rule a -> Environment -> Maybe String
- makeRule :: (IsId n, MakeTrans f) => n -> (a -> f a) -> Rule a
- ruleMaybe :: IsId n => n -> (a -> Maybe a) -> Rule a
- ruleList :: IsId n => n -> (a -> [a]) -> Rule a
- ruleTrans :: IsId n => n -> Transformation a -> Rule a
- ruleRewrite :: RewriteRule a -> Rule a
- buggyRule :: (IsId n, MakeTrans f) => n -> (a -> f a) -> Rule a
- minorRule :: (IsId n, MakeTrans f) => n -> (a -> f a) -> Rule a
- rewriteRule :: (IsId n, RuleBuilder f a) => n -> f -> Rule a
- rewriteRules :: (IsId n, RuleBuilder f a) => n -> [f] -> Rule a
- idRule :: IsId n => n -> Rule a
- checkRule :: IsId n => n -> (a -> Bool) -> Rule a
- emptyRule :: IsId n => n -> Rule a
- ruleSiblings :: Rule a -> [Id]
- siblingOf :: HasId b => b -> Rule a -> Rule a
- isRewriteRule :: Rule a -> Bool
- isRecognizer :: Rule a -> Bool
- doAfter :: (a -> a) -> Rule a -> Rule a
- addRecognizer :: Recognizer a -> Rule a -> Rule a
- addRecognizerBool :: (a -> a -> Bool) -> Rule a -> Rule a
- addTransRecognizer :: (a -> a -> Bool) -> Rule a -> Rule a
- addRecognizerEnvMonad :: (a -> a -> EnvMonad ()) -> Rule a -> Rule a
Rule data type and accessors
Abstract data type for representing rules
transformation :: Rule a -> Transformation a Source
recognizer :: Recognizable f => f a -> Recognizer a Source
checkReferences :: Rule a -> Environment -> Maybe String Source
Constructor functions
ruleTrans :: IsId n => n -> Transformation a -> Rule a Source
ruleRewrite :: RewriteRule a -> Rule a Source
rewriteRule :: (IsId n, RuleBuilder f a) => n -> f -> Rule a Source
rewriteRules :: (IsId n, RuleBuilder f a) => n -> [f] -> Rule a Source
Special minor rules
checkRule :: IsId n => n -> (a -> Bool) -> Rule a Source
A special (minor) rule that checks a predicate (and returns the identity if the predicate holds)
emptyRule :: IsId n => n -> Rule a Source
A special (minor) rule that is never applicable (i.e., this rule always fails)
Rule properties
ruleSiblings :: Rule a -> [Id] Source
isRewriteRule :: Rule a -> Bool Source
isRecognizer :: Rule a -> Bool Source
Recognizer
addRecognizer :: Recognizer a -> Rule a -> Rule a Source
addRecognizerBool :: (a -> a -> Bool) -> Rule a -> Rule a Source
addTransRecognizer :: (a -> a -> Bool) -> Rule a -> Rule a Source
addRecognizerEnvMonad :: (a -> a -> EnvMonad ()) -> Rule a -> Rule a Source