ideas-1.8: Feedback services for intelligent tutoring systems

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

Ideas.Common.Strategy.StrategyTree

Contents

Description

Representation of a strategy as a cyclic tree with explicit fixed-points. The nodes in the tree are named strategy combinators. The leafs are rules.

Synopsis

StrategyTree type synonym

data Leaf a Source #

Constructors

LeafRule (Rule a) 
LeafDyn (Dynamic a) 
Instances
Apply Leaf Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

applyAll :: Leaf a -> a -> [a] Source #

LiftView Leaf Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

liftView :: View a b -> Leaf b -> Leaf a Source #

liftViewIn :: View a (b, c) -> Leaf b -> Leaf a Source #

Eq (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

(==) :: Leaf a -> Leaf a -> Bool #

(/=) :: Leaf a -> Leaf a -> Bool #

Show (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

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

show :: Leaf a -> String #

showList :: [Leaf a] -> ShowS #

Minor (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

minor :: Leaf a -> Leaf a Source #

setMinor :: Bool -> Leaf a -> Leaf a Source #

isMinor :: Leaf a -> Bool Source #

isMajor :: Leaf a -> Bool Source #

HasId (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Leaf a -> Id Source #

changeId :: (Id -> Id) -> Leaf a -> Leaf a Source #

LabelSymbol (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

isEnterSymbol :: Leaf a -> Bool Source #

AtomicSymbol (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Declarations (named combinators)

data Decl f Source #

Instances
Eq (Decl f) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

(==) :: Decl f -> Decl f -> Bool #

(/=) :: Decl f -> Decl f -> Bool #

Show (Decl f) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

showsPrec :: Int -> Decl f -> ShowS #

show :: Decl f -> String #

showList :: [Decl f] -> ShowS #

HasId (Decl f) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Decl f -> Id Source #

changeId :: (Id -> Id) -> Decl f -> Decl f Source #

type Combinator f = forall a. f (Process (Leaf a)) Source #

(.=.) :: IsId n => n -> Combinator f -> Decl f infix 1 Source #

Dynamic strategies

data Dynamic a Source #

Instances
Apply Dynamic Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

applyAll :: Dynamic a -> a -> [a] Source #

LiftView Dynamic Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

liftView :: View a b -> Dynamic b -> Dynamic a Source #

liftViewIn :: View a (b, c) -> Dynamic b -> Dynamic a Source #

IsStrategy Dynamic Source # 
Instance details

Defined in Ideas.Common.Strategy.Abstract

HasId (Dynamic a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Dynamic a -> Id Source #

changeId :: (Id -> Id) -> Dynamic a -> Dynamic a Source #

makeDynamic :: (IsId n, IsTerm a) => n -> (a -> StrategyTree a) -> Dynamic a Source #

Arities

class Arity f where Source #

Minimal complete definition

listify, toArity, liftIso

Methods

listify :: f a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> f a Source #

liftIso :: Isomorphism a b -> f a -> f b Source #

Instances
Arity Nary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Nary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Nary a Source #

liftIso :: Isomorphism a b -> Nary a -> Nary b Source #

Arity Binary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Binary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Binary a Source #

liftIso :: Isomorphism a b -> Binary a -> Binary b Source #

Arity Unary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Unary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Unary a Source #

liftIso :: Isomorphism a b -> Unary a -> Unary b Source #

Arity Nullary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Nullary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Nullary a Source #

liftIso :: Isomorphism a b -> Nullary a -> Nullary b Source #

newtype Nullary a Source #

Constructors

Nullary 

Fields

Instances
Arity Nullary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Nullary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Nullary a Source #

liftIso :: Isomorphism a b -> Nullary a -> Nullary b Source #

newtype Unary a Source #

Constructors

Unary 

Fields

Instances
Arity Unary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Unary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Unary a Source #

liftIso :: Isomorphism a b -> Unary a -> Unary b Source #

newtype Binary a Source #

Constructors

Binary 

Fields

Instances
Arity Binary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Binary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Binary a Source #

liftIso :: Isomorphism a b -> Binary a -> Binary b Source #

newtype Nary a Source #

Constructors

Nary 

Fields

Instances
Arity Nary Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

listify :: Nary a -> [a] -> Maybe a Source #

toArity :: ([a] -> a) -> Nary a Source #

liftIso :: Isomorphism a b -> Nary a -> Nary b Source #