ideas-1.1: Feedback services for intelligent tutoring systems

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

Ideas.Common.Strategy

Contents

Description

A strategy is a context-free grammar with rules as symbols. Strategies can be labeled with strings. A type class is introduced to lift all the combinators that work on strategies, only to prevent that you have to insert these lifting functions yourself.

Synopsis

Data types and type classes

data Strategy a Source

Abstract data type for strategies

class IsStrategy f whereSource

Type class to turn values into strategies

Methods

toStrategy :: f a -> Strategy aSource

Running strategies

fullDerivationTree :: IsStrategy f => Bool -> f a -> a -> DerivationTree (Step LabelInfo a) aSource

Returns the derivation tree for a strategy and a term, including all minor rules

derivationTree :: IsStrategy f => Bool -> f a -> a -> DerivationTree (Rule a, Environment) aSource

Returns the derivation tree for a strategy and a term with only major rules

Strategy combinators

Basic combinators

(<*>) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy aSource

Put two strategies in sequence (first do this, then do that)

(<|>) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy aSource

Choose between the two strategies (either do this or do that)

(<%>) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy aSource

Interleave two strategies

succeed :: Strategy aSource

The strategy that always succeeds (without doing anything)

fail :: Strategy aSource

The strategy that always fails

atomic :: IsStrategy f => f a -> Strategy aSource

Makes a strategy atomic (w.r.t. parallel composition)

label :: (IsId l, IsStrategy f) => l -> f a -> LabeledStrategy aSource

Labels a strategy with a string

sequence :: IsStrategy f => [f a] -> Strategy aSource

Puts a list of strategies into a sequence

alternatives :: IsStrategy f => [f a] -> Strategy aSource

Combines a list of alternative strategies

interleave :: IsStrategy f => [f a] -> Strategy aSource

Merges a list of strategies (in parallel)

permute :: IsStrategy f => [f a] -> Strategy aSource

Allows all permutations of the list

fix :: (Strategy a -> Strategy a) -> Strategy aSource

A fix-point combinator on strategies (to model recursion). Powerful (but dangerous) combinator

EBNF combinators

many :: IsStrategy f => f a -> Strategy aSource

Repeat a strategy zero or more times (non-greedy)

many1 :: IsStrategy f => f a -> Strategy aSource

Apply a certain strategy at least once (non-greedy)

replicate :: IsStrategy f => Int -> f a -> Strategy aSource

Apply a strategy a certain number of times

option :: IsStrategy f => f a -> Strategy aSource

Apply a certain strategy or do nothing (non-greedy)

Negation and greedy combinators

check :: (a -> Bool) -> Strategy aSource

Checks whether a predicate holds for the current term. The check is considered to be a minor step.

not :: IsStrategy f => f a -> Strategy aSource

Check whether or not the argument strategy cannot be applied: the result strategy only succeeds if this is not the case (otherwise it fails).

repeat :: IsStrategy f => f a -> Strategy aSource

Repeat a strategy zero or more times (greedy version of many)

repeat1 :: IsStrategy f => f a -> Strategy aSource

Apply a certain strategy at least once (greedy version of many1)

try :: IsStrategy f => f a -> Strategy aSource

Apply a certain strategy if this is possible (greedy version of option)

(|>) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy aSource

Left-biased choice: if the left-operand strategy can be applied, do so. Otherwise, try the right-operand strategy

exhaustive :: IsStrategy f => [f a] -> Strategy aSource

Apply the strategies from the list exhaustively (until this is no longer possible)

while :: IsStrategy f => (a -> Bool) -> f a -> Strategy aSource

Repeat the strategy as long as the predicate holds

until :: IsStrategy f => (a -> Bool) -> f a -> Strategy aSource

Repeat the strategy until the predicate holds

multi :: (IsId l, IsStrategy f) => l -> f a -> LabeledStrategy aSource

Apply a strategy at least once, but collapse into a single step

Traversal combinators

Configuration combinators

Strategy locations

strategyLocations :: LabeledStrategy a -> [([Int], LabeledStrategy a)]Source

Returns a list of all strategy locations, paired with the labeled substrategy at that location

subStrategy :: Id -> LabeledStrategy a -> Maybe (LabeledStrategy a)Source

Returns the substrategy or rule at a strategy location. Nothing indicates that the location is invalid

Prefixes

data Prefix a Source

Abstract data type for a (labeled) strategy with a prefix (a sequence of executed rules). A prefix is still aware of the labels that appear in the strategy. A prefix is encoded as a list of integers (and can be reconstructed from such a list: see makePrefix). The list is stored in reversed order.

Instances

Eq (Prefix a) 
Show (Prefix a) 

emptyPrefix :: LabeledStrategy a -> Prefix aSource

Construct the empty prefix for a labeled strategy

makePrefix :: Monad m => [Int] -> LabeledStrategy a -> m (Prefix a)Source

Construct a prefix for a given list of integers and a labeled strategy.

prefixTree :: Bool -> Prefix a -> a -> DerivationTree (Prefix a) aSource

Create a derivation tree with a prefix as annotation.

data Step l a Source

Constructors

Enter l 
Exit l 
RuleStep Environment (Rule a) 

Instances

Apply (Step l) 
Eq l => Eq (Step l a) 
Show l => Show (Step l a) 
Minor (Step l a) 

stepsToRules :: [Step l a] -> [Rule a]Source

Retrieves the rules from a list of steps

lastStepInPrefix :: Prefix a -> Maybe (Step LabelInfo a)Source

Returns the last rule of a prefix (if such a rule exists)

Misc

cleanUpStrategy :: (a -> a) -> LabeledStrategy a -> LabeledStrategy aSource

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 aSource

Use a function as do-after hook for all rules in a labeled strategy

rulesInStrategy :: IsStrategy f => f a -> [Rule a]Source

Returns a list of all major rules that are part of a labeled strategy