ideas-1.6: Feedback services for intelligent tutoring systems

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

Ideas.Common.Strategy

Contents

Description

A strategy is a context-free grammar with rules as symbols. Strategies can be labeled with strings. The type class IsStrategy is introduced to lift functions and combinators that work on strategies to also accept rules and labeled strategies. This module re-exports the most important functionality of the underlying modules.

Synopsis

Data types and type classes

data Strategy a Source #

Abstract data type for strategies

class IsStrategy f where Source #

Type class to turn values into strategies

Minimal complete definition

toStrategy

Methods

toStrategy :: f a -> Strategy a Source #

Running strategies

derivationList :: IsStrategy f => (Rule a -> Rule a -> Ordering) -> f a -> a -> [Derivation (Rule a, Environment) a] Source #

Strategy combinators

Basic combinators

(.*.) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 5 Source #

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

(.|.) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 3 Source #

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

(.%.) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 2 Source #

Interleave two strategies

(.@.) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 2 Source #

Alternate two strategies

(!~>) :: IsStrategy f => Rule a -> f a -> Strategy a infixr 5 Source #

Prefixing a basic rule to a strategy atomically

succeed :: Strategy a Source #

The strategy that always succeeds (without doing anything)

fail :: Strategy a Source #

The strategy that always fails

atomic :: IsStrategy f => f a -> Strategy a Source #

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

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

Labels a strategy with an identifier. Labels are used to identify substrategies and to specialize feedback messages. The first argument of label can be of type String, in which case the string is used as identifier (and not as description).

inits :: IsStrategy f => f a -> Strategy a Source #

Initial prefixes (allows the strategy to stop succesfully at any time)

sequence :: IsStrategy f => [f a] -> Strategy a Source #

Puts a list of strategies into a sequence

choice :: IsStrategy f => [f a] -> Strategy a Source #

Combines a list of alternative strategies

interleave :: IsStrategy f => [f a] -> Strategy a Source #

Merges a list of strategies (in parallel)

permute :: IsStrategy f => [f a] -> Strategy a Source #

Allows all permutations of the list

EBNF combinators

many :: IsStrategy f => f a -> Strategy a Source #

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

many1 :: IsStrategy f => f a -> Strategy a Source #

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

replicate :: IsStrategy f => Int -> f a -> Strategy a Source #

Apply a strategy a certain number of times

option :: IsStrategy f => f a -> Strategy a Source #

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

Negation and greedy combinators

check :: (a -> Bool) -> Strategy a Source #

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

not :: IsStrategy f => f a -> Strategy a Source #

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 a Source #

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

repeat1 :: IsStrategy f => f a -> Strategy a Source #

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

try :: IsStrategy f => f a -> Strategy a Source #

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

(|>) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 4 Source #

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

(./.) :: (IsStrategy f, IsStrategy g) => f a -> g a -> Strategy a infixr 4 Source #

Choose between the two strategies, with a preference for steps from the left hand-side strategy.

exhaustive :: IsStrategy f => [f a] -> Strategy a Source #

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

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

Repeat the strategy as long as the predicate holds

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

Repeat the strategy until the predicate holds

dynamic :: (IsId n, IsStrategy f, IsTerm a) => n -> (a -> f a) -> Strategy a Source #

The structure of a dynamic strategy depends on the current term

Graph

type DependencyGraph node key = [(node, key, [key])] Source #

dependencyGraph :: (IsStrategy f, Ord key) => DependencyGraph (f a) key -> Strategy a Source #

Create a strategy from a dependency graph with strategies as nodes Does not check for cycles

Traversal combinators

Configuration combinators

Strategy locations

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

Returns a list of all strategy locations, paired with the label

Prefixes

data Prefix a Source #

Instances

Show (Prefix a) Source # 

Methods

showsPrec :: Int -> Prefix a -> ShowS #

show :: Prefix a -> String #

showList :: [Prefix a] -> ShowS #

Monoid (Prefix a) Source # 

Methods

mempty :: Prefix a #

mappend :: Prefix a -> Prefix a -> Prefix a #

mconcat :: [Prefix a] -> Prefix a #

Firsts (Prefix a) Source # 

Associated Types

type Elem (Prefix a) :: * Source #

Methods

ready :: Prefix a -> Bool Source #

firsts :: Prefix a -> [(Elem (Prefix a), Prefix a)] Source #

type Elem (Prefix a) Source # 
type Elem (Prefix a) = (Rule a, a, Environment)

emptyPrefix :: IsStrategy f => f a -> a -> Prefix a Source #

Construct the empty prefix for a labeled strategy

noPrefix :: Prefix a Source #

The error prefix (i.e., without a location in the 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.

data Path Source #

A path encodes a location in a strategy. Paths are represented as a list of integers and terms (the latter act as input for the dynamic strategies).

Instances

Eq Path Source # 

Methods

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

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

Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

emptyPath :: Path Source #

The empty path.

prefixPaths :: Prefix a -> [Path] Source #

Returns the current Path.

majorPrefix :: Prefix a -> Prefix a Source #

Transforms the prefix such that only major steps are kept in the remaining strategy.

Misc

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

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

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