ideas-1.7: Feedback services for intelligent tutoring systems

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

Ideas.Common.DerivationTree

Contents

Description

Datatype for representing derivations as a tree. The datatype stores all intermediate results as well as annotations for the steps.

Synopsis

Data types

data DerivationTree s a Source #

Instances

BiFunctor DerivationTree Source # 

Methods

biMap :: (a -> c) -> (b -> d) -> DerivationTree a b -> DerivationTree c d Source #

mapFirst :: (a -> b) -> DerivationTree a c -> DerivationTree b c Source #

mapSecond :: (b -> c) -> DerivationTree a b -> DerivationTree a c Source #

Functor (DerivationTree s) Source # 

Methods

fmap :: (a -> b) -> DerivationTree s a -> DerivationTree s b #

(<$) :: a -> DerivationTree s b -> DerivationTree s a #

(Show s, Show a) => Show (DerivationTree s a) Source # 

Constructors

singleNode :: a -> Bool -> DerivationTree s a Source #

Constructs a node without branches; the boolean indicates whether the node is an endpoint or not

addBranches :: [(s, DerivationTree s a)] -> DerivationTree s a -> DerivationTree s a Source #

Branches are attached after the existing ones (order matters)

makeTree :: (a -> (Bool, [(s, a)])) -> a -> DerivationTree s a Source #

Query

root :: DerivationTree s a -> a Source #

The root of the tree

endpoint :: DerivationTree s a -> Bool Source #

Is this node an endpoint?

branches :: DerivationTree s a -> [(s, DerivationTree s a)] Source #

All branches

subtrees :: DerivationTree s a -> [DerivationTree s a] Source #

Returns all subtrees at a given node

leafs :: DerivationTree s a -> [a] Source #

Returns all leafs, i.e., final results in derivation. Be careful: the returned list may be very long

lengthMax :: Int -> DerivationTree s a -> Maybe Int Source #

The argument supplied is the maximum number of steps; if more steps are needed, Nothing is returned

Adapters

restrictHeight :: Int -> DerivationTree s a -> DerivationTree s a Source #

Restrict the height of the tree (by cutting off branches at a certain depth). Nodes at this particular depth are turned into endpoints

restrictWidth :: Int -> DerivationTree s a -> DerivationTree s a Source #

Restrict the width of the tree (by cutting off branches).

updateAnnotations :: (a -> s -> a -> t) -> DerivationTree s a -> DerivationTree t a Source #

sortTree :: (l -> l -> Ordering) -> DerivationTree l a -> DerivationTree l a Source #

Conversions

derivation :: DerivationTree s a -> Maybe (Derivation s a) Source #

The first derivation (if any)

randomDerivation :: RandomGen g => g -> DerivationTree s a -> Maybe (Derivation s a) Source #

Return a random derivation (if any exists at all)

derivations :: DerivationTree s a -> [Derivation s a] Source #

All possible derivations (returned in a list)