stepwise-1.0.2

Control.Monad.Stepwise.Examples

Description

This module shows some example stepwise-computations, and focus on individual features provided by the library. We start with testing out some basic functionality, then switch to more interesting examples. In practice, you'll combine several of the features presented here.

Synopsis

Documentation

data I t Source

A type for the simplest form of progress report: just a message I that indicates that a bit of work has been done. It is indexed by the watcher type t, which in this case doesn't matter. Later examples show a more involving type of progress report that uses the watcher type.

Constructors

I 

Instances

Monoid (I t)

Monoid instance for use in combination with <|>. In practice, you'll not use <|>, but write more complicated merging strategies instead.

test1 :: Stepwise AnyFailure I any AnyWatcher IntSource

Test 1: verify that results are provided when available (online behavior). With lazyEval this means that the result should be delivered, independent of the failure. Failure is just considered to be a bottom-value: if it's never needed in the continuation, it is not triggered. This is different in comparison to strict evaluation.

A short remark about the type signature: the AnyFailure is the type of failures such a computation may emit during stepwise evaluation (during lazy evaluation, this is simply a bottom value). Both String and AnyFailure are typical examples. The I type is the type of the progress reports. The watcher type is given seperately. A computation may state how it is evaluated: either may use lazy evaluation (via the type Lazy) or use sequential evaluation (via the type Sequential). For most computations this is not an issue: either keep it polymorphic (like in this example via a universally quantified type variable), or use Lazy (the preferred default evaluation mode). We also do not care about the watcher type for progress reports of type I. Either keep the type polymorphic, or simply choose a type like AnyWatcher (or '()'). Finally, the last type of the value that evaluation of the computation results into. The first three parameters to Stepwise typically stay the same, the latter three may vary from one computation to another.

test2 :: Stepwise AnyFailure I any AnyWatcher IntSource

Test 2: verify that the selection process causes strict evaluation. Despite running lazyEval on test2, strict evaluation will be done on the alternatives until a choice is made. In this case, both alternatives fail, so the entire result fails. Note that the <|>-implementation takes the first child that succeeds, or the last child that fails (left-biased).

test3 :: Stepwise AnyFailure I Lazy AnyWatcher IntSource

Test 3: verify selection of alternatives. The non-failure alternative is selected in this case. The Lazy annotation here we can use because we can. A Lazy-annotation is in principle never required (you can in such cases keep it polymorphic), but if possible, it's a good idea to do so, to make clear which computations should preferably be evaluated lazily.

data J t Source

Test 7: collecting multiple results.

test7b generates paths: the left subpath is of length n-1 the right subpath is a lot shorter (n div 2) (just for fun). test7a succeeds only for those paths that satisfy a funny criteria via xor. Those it returns. When it succeeds, test7b emits a progress report collecting that value. merge tries out options in a breadth-first way, and concatenates the lists in the progress reports. test7c takes out the list of all succeeding paths.

We collect these multiple results in a more informative form of progress report J. The type of the watcher is important here. The test7a function does not make any assumptions about the watcher, however test7b does. When test7a succeeds, it collects that results in a Collect.

Constructors

Collect [t] 
J 

test7a :: [Bool] -> Stepwise AnyFailure J Lazy somewatcher [Bool]Source

We may not make an assumption about the watcher here, hence we keep the watcher type polymorphic.

test7c :: Stepwise AnyFailure J Lazy a [[Bool]]Source

Strips steps (thus evaluates sequentially), until it hits a Collect message, which is subsequently delivers.

type Lab a = RWST LabIn Instrs LabChn (Stepwise AnyFailure LabSteps Lazy AnyWatcher) aSource

Test 8: lookahead. Decisions taken in this example may depend on what happens in the continuation. We takes as example path-finding in a labyrinth. Taking a step that brings us back to a position where we've been before is an immediate failure. However, the possibilities that remain may hit a dead-end later.

data LabIn Source

Constructors

LI 

data LabChn Source

Constructors

LC 

Fields

chnPos :: !Pos
 
chnTrail :: !(Set Pos)
 

Instances

data LabSteps t Source

Constructors

Walked !(Set Pos) 

type Pos = (Int, Int)Source

newtype Instrs Source

Constructors

Instrs (Path -> Path) 

type Path = [Dir]Source

data Dir Source

Constructors

North 
East 
South 
West 

Instances

(<<|>) :: Lab a -> Lab a -> Lab aSource

best :: Lab' a -> Lab' a -> Lab' aSource

lab1 :: [Pos]Source

Example labyrinth

data Branch a Source

Container to keep the contained value lazy

Constructors

Branch 

Fields

pickBranch :: Lab' a
 

memoize :: MemoEnvRef AnyFailure LabSteps Lazy AnyWatcher -> Int -> Lab () -> Lab ()Source

Test 8b: Explicit sharing. This example builds on the previous one. Since we immediately fail when a step would take us back at a position that we've been before, the paths we traverse form a DAG. However, certain paths on this DAG we may traverse more than once. In this example, we ensure that we only traverse each path once.

Note, however, that it memoizes the outcome (i.e. the Lab' value), produced in a context potentially different from ours. The key loc in this case, however, identifies a unique context.

convergeKill :: Lab' a -> Lab' a -> Lab (Lab' a, Lab' a)Source

Test 8c: Ambiguity and online-ness improvement. If two parallel branches converge on a single path, kill one of the branches. A much more effective approach is to keep a shared trail via an IORef and kill any branch that makes a move to a square already visited. However, the current approach is more interesting: it takes a bit longer until common paths are found.

runAhead :: Int -> Lab' a -> Lab (Lab' a)Source

data BinTree Source

Repmin with alternatives! The tree may contain alternatives. The tree is returned such that it (1) consists of the shortest (left-biassed) alternatives (2) all leaves replaced with the minimal value occurring in the tree (for the selected alternatives) This tests the MonadFix feature.

Note: To show that online results are in general necessairy for cyclic computations, we should actually make the selection process dependent on the outcome of a previously but already resolved selection. For example, by keeping a local minimum (from the left), and taking the first alternative that goes under it. Perhaps a min/max game tree would be a good example for that.

Also, a lazy value depending on the outcome of two or more alternatives can only be produced if there is one alternative left. If all the alternatives would yield the same outermost constructor, still no value can be produced. This is in general no problem; the reason that you had alternatives there is likely because it returns different results.

Instances