| Maintainer | bastiaan.heeren@ou.nl |
|---|---|
| Stability | provisional |
| Portability | portable (depends on ghc) |
| Safe Haskell | None |
| Language | Haskell98 |
Ideas.Common.Strategy.Abstract
Contents
Description
Abstract data type for a Strategy and a LabeledStrategy.
Synopsis
- data Strategy a
- data LabeledStrategy a
- label :: (IsId l, IsStrategy f) => l -> f a -> LabeledStrategy a
- unlabel :: LabeledStrategy a -> Strategy a
- class IsStrategy f where
- liftS :: IsStrategy f => (Strategy a -> Strategy a) -> f a -> Strategy a
- liftS2 :: (IsStrategy f, IsStrategy g) => (Strategy a -> Strategy a -> Strategy a) -> f a -> g a -> Strategy a
- liftSn :: IsStrategy f => ([Strategy a] -> Strategy a) -> [f a] -> Strategy a
- emptyPrefix :: IsStrategy f => f a -> a -> Prefix a
- replayPath :: IsStrategy f => Path -> f a -> a -> ([Rule a], Prefix a)
- replayPaths :: IsStrategy f => [Path] -> f a -> a -> Prefix a
- replayStrategy :: (Monad m, IsStrategy f) => Path -> f a -> a -> m (a, Prefix a)
- rulesInStrategy :: IsStrategy f => f a -> [Rule a]
- mapRules :: (Rule a -> Rule a) -> LabeledStrategy a -> LabeledStrategy a
- mapRulesS :: (Rule a -> Rule a) -> Strategy a -> Strategy a
- cleanUpStrategy :: (a -> a) -> LabeledStrategy a -> LabeledStrategy a
- cleanUpStrategyAfter :: (a -> a) -> LabeledStrategy a -> LabeledStrategy a
- derivationList :: IsStrategy f => (Rule a -> Rule a -> Ordering) -> f a -> a -> [Derivation (Rule a, Environment) a]
- toStrategyTree :: IsStrategy f => f a -> StrategyTree a
- onStrategyTree :: IsStrategy f => (StrategyTree a -> StrategyTree a) -> f a -> Strategy a
- useDecl :: Arity f => Decl f -> f (Strategy a)
- decl0 :: Decl Nullary -> Strategy a
- decl1 :: IsStrategy f => Decl Unary -> f a -> Strategy a
- decl2 :: (IsStrategy f, IsStrategy g) => Decl Binary -> f a -> g a -> Strategy a
- declN :: IsStrategy f => Decl Nary -> [f a] -> Strategy a
Strategy data type
Abstract data type for strategies
Instances
| Apply Strategy Source # | |
Defined in Ideas.Common.Strategy.Abstract | |
| LiftView Strategy Source # | |
| IsStrategy Strategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: Strategy a -> Strategy a Source # | |
| Show (Strategy a) Source # | |
| Fix (Strategy a) Source # | |
| Choice (Strategy a) Source # | |
Defined in Ideas.Common.Strategy.Abstract | |
| Sequence (Strategy a) Source # | |
Defined in Ideas.Common.Strategy.Abstract | |
| type Sym (Strategy a) Source # | |
Defined in Ideas.Common.Strategy.Abstract | |
Labeled strategies
data LabeledStrategy a Source #
A strategy which is labeled with an identifier
Instances
| Apply LabeledStrategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods applyAll :: LabeledStrategy a -> a -> [a] Source # | |
| LiftView LabeledStrategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods liftView :: View a b -> LabeledStrategy b -> LabeledStrategy a Source # liftViewIn :: View a (b, c) -> LabeledStrategy b -> LabeledStrategy a Source # | |
| IsStrategy LabeledStrategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: LabeledStrategy a -> Strategy a Source # | |
| Show (LabeledStrategy a) Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods showsPrec :: Int -> LabeledStrategy a -> ShowS # show :: LabeledStrategy a -> String # showList :: [LabeledStrategy a] -> ShowS # | |
| HasId (LabeledStrategy a) Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods getId :: LabeledStrategy a -> Id Source # changeId :: (Id -> Id) -> LabeledStrategy a -> LabeledStrategy a Source # | |
label :: (IsId l, IsStrategy f) => l -> f a -> LabeledStrategy a Source #
unlabel :: LabeledStrategy a -> Strategy a Source #
Removes the label from a strategy
Lifting to strategies
class IsStrategy f where Source #
Type class to turn values into strategies
Minimal complete definition
Methods
toStrategy :: f a -> Strategy a Source #
Instances
| IsStrategy RewriteRule Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: RewriteRule a -> Strategy a Source # | |
| IsStrategy Rule Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: Rule a -> Strategy a Source # | |
| IsStrategy Dynamic Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: Dynamic a -> Strategy a Source # | |
| IsStrategy LabeledStrategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: LabeledStrategy a -> Strategy a Source # | |
| IsStrategy Strategy Source # | |
Defined in Ideas.Common.Strategy.Abstract Methods toStrategy :: Strategy a -> Strategy a Source # | |
liftS2 :: (IsStrategy f, IsStrategy g) => (Strategy a -> Strategy a -> Strategy a) -> f a -> g a -> Strategy a Source #
Prefixes
emptyPrefix :: IsStrategy f => f a -> a -> Prefix a Source #
Construct the empty prefix for a labeled strategy
replayPath :: IsStrategy f => Path -> f a -> a -> ([Rule a], Prefix a) Source #
Construct a prefix for a path and a labeled strategy. The third argument is the current term.
replayPaths :: IsStrategy f => [Path] -> f a -> a -> Prefix a Source #
Construct a prefix for a list of paths and a labeled strategy. The third argument is the current term.
replayStrategy :: (Monad m, IsStrategy f) => Path -> f a -> a -> m (a, Prefix a) Source #
Construct a prefix for a path and a labeled strategy. The third argument is the initial term.
Rules
rulesInStrategy :: IsStrategy f => f a -> [Rule a] Source #
Returns a list of all major rules that are part of a labeled strategy
mapRules :: (Rule a -> Rule a) -> LabeledStrategy a -> LabeledStrategy a Source #
Apply a function to all the rules that make up a labeled strategy
cleanUpStrategy :: (a -> a) -> LabeledStrategy a -> LabeledStrategy a Source #
Use a function as do-after hook for all rules in a labeled strategy, but also use the function beforehand
cleanUpStrategyAfter :: (a -> a) -> LabeledStrategy a -> LabeledStrategy a Source #
Use a function as do-after hook for all rules in a labeled strategy
derivationList :: IsStrategy f => (Rule a -> Rule a -> Ordering) -> f a -> a -> [Derivation (Rule a, Environment) a] Source #
Access to underlying representation
toStrategyTree :: IsStrategy f => f a -> StrategyTree a Source #
onStrategyTree :: IsStrategy f => (StrategyTree a -> StrategyTree a) -> f a -> Strategy a Source #
Strategy declarations
decl2 :: (IsStrategy f, IsStrategy g) => Decl Binary -> f a -> g a -> Strategy a Source #