ideas-1.5: Feedback services for intelligent tutoring systems

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

Ideas.Common.Strategy.Abstract

Contents

Description

Abstract data type for a Strategy and a LabeledStrategy.

Synopsis

Strategy data type

Labeled strategies

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).

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

Methods

toStrategy :: f a -> Strategy a Source

liftS :: IsStrategy f => (Strategy a -> Strategy a) -> f a -> Strategy a Source

liftS2 :: (IsStrategy f, IsStrategy g) => (Strategy a -> Strategy a -> Strategy a) -> f a -> g a -> Strategy a Source

liftSn :: IsStrategy f => ([Strategy a] -> Strategy a) -> [f 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 b) -> LabeledStrategy a -> LabeledStrategy b Source

Apply a function to all the rules that make up a labeled strategy

mapRulesS :: (Rule a -> Rule b) -> Strategy a -> Strategy b Source

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

Strategy declarations

useDecl :: Arity f => Decl f -> f (Strategy a) Source

decl2 :: (IsStrategy f, IsStrategy g) => Decl Binary -> f a -> g a -> Strategy a Source

declN :: IsStrategy f => Decl Nary -> [f a] -> Strategy a Source