Control-Monad-MultiPass-0.1.0.0: A Library for Writing Multi-Pass Algorithms.

Safe HaskellSafe

Control.Monad.MultiPass

Contents

Description

This module implements the core functions, datatypes, and classes of the MultiPass library. Its export list is divided into two halves. The first half contains the declarations which are relevant to anyone who wants to use the MultiPass library. The second contains which are only relevant to people who want to implement new instruments.

Synopsis

Users

data MultiPass r w tc a Source

This monad is used to implement the body of a multi-pass algorithm.

Instances

Monad (MultiPass r w tc) 
Functor (MultiPass r w tc) 

data MultiPassPrologue r w tc a Source

This monad is used to implement the prologue of a multi-pass algorithm.

Instances

data MultiPassEpilogue r w tc a Source

This monad is used to implement the epilogue of a multi-pass algorithm.

Instances

data MultiPassMain r w tc c Source

MultiPassMain is an abstract datatype containing the prologue, body, and epilogue of a multi-pass algorithm. Use mkMultiPassMain to construct an object of type MultiPassMain.

mkMultiPassMainSource

Arguments

:: MultiPassPrologue r w tc a

Prologue

-> (a -> MultiPass r w tc b)

Algorithm body

-> (b -> MultiPassEpilogue r w tc c)

Epilogue

-> MultiPassMain r w tc c 

Combine the prologue, body, and epilogue of a multi-pass algorithm to create the MultiPassMain object which is required by the run function.

newtype PassS cont m Source

This datatype is used in conjunction with PassZ to package the main function of the multi-pass algorithm. For an example of how they are used, see the implementation of repminMP or any of the other examples in the Example directory.

Constructors

PassS (forall p. Monad p => cont (m p)) 

newtype PassZ f Source

Used in conjunction with PassS to build a Peano number corresponding to the number of passes.

Constructors

PassZ (forall tc. f tc) 

class MultiPassAlgorithm a b | a -> b whereSource

The main function of a multi-pass algorithm needs to be wrapped in a newtype so that it can be packaged with PassS and PassZ. The newtype needs to be made an instance of MultiPassAlgorithm so that it can unwrapped by the implementation.

run :: forall r w f f' g tc gc out. (InstantiatePasses f f', MultiPassAlgorithm (f' tc) g, ApplyArgs r w g tc gc tc gc tc (MultiPassMain r w tc (Off out)), InitCtx tc, InitCtx gc, RunPasses r w f tc gc Off out) => f -> ST2 r w outSource

This function is used to run a multi-pass algorithm. Its complicated type is mostly an artifact of the internal implementation, which uses type classes to generate the code for each pass of the algorithm. Therefore, the recommended way to learn how to use run is to look at some of the examples in the Example sub-directory.

newtype NumThreads Source

NumThreads is used to specify the number of threads in parallelMP and parallelMP_.

Constructors

NumThreads Int 

parallelMPSource

Arguments

:: (Ix i, Num i) 
=> NumThreads

Number of threads to spawn

-> (i, i)

Element range

-> (i -> MultiPass r w tc a) 
-> MultiPass r w tc (ST2Array r w i a) 

Use m threads to run n instances of the function f. The results are returned in an array of length n.

parallelMP_Source

Arguments

:: (Ix i, Num i) 
=> NumThreads

Number of threads to spawn

-> (i, i)

Element range

-> (i -> MultiPass r w tc a) 
-> MultiPass r w tc () 

Modified version of parallelMP which discards the result of the function, rather than writing it to an array.

readOnlyST2ToMP :: (forall w. ST2 r w a) -> MultiPass r w' tc aSource

Read-only ST2 computations are allowed to be executed in the MultiPass monad.

Instrument Authors

newtype On a Source

Trivial monad, equivalent to Identity. Used to switch on a pass of a multi-pass algorithm.

Constructors

On a 

Instances

Monad On 
Functor On 
Instrument tc () () (Delay On On tc) 
Instrument tc () () (Delay On Off tc) 
Instrument tc () () (CreateST2Array r w On tc) 
Instrument tc () () (DelayedLift r w On tc) 
Monoid a => Instrument tc (MonoidTC a) () (Monoid2 a r w On Off tc) 
Num i => Instrument tc (CounterTC2 i r) () (Counter i r w On On tc) 
Num i => Instrument tc (CounterTC1 i r) () (Counter i r w On Off tc) 
Instrument tc (CounterTC1 Int r) () (Knot3 a r w On Off Off tc) 
Num i => Instrument tc (CounterTC1 i r) () (EmitST2Array i a r w On Off Off tc) 

data Off a Source

Trivial monad which computes absolutely nothing. It is used to switch off a pass of a multi-pass algorithm.

Constructors

Off 

Instances

Monad Off 
Functor Off 
Instrument tc () () (Delay On Off tc) 
Instrument tc () () (Delay Off Off tc) 
Instrument tc () () (CreateST2Array r w Off tc) 
Instrument tc () () (DelayedLift r w Off tc) 
Instrument tc () () (Counter i r w Off Off tc) 
Instrument tc () () (Monoid2 a r w Off Off tc) 
Instrument tc () () (OrdCons a r w Off Off tc) 
Instrument tc () () (TopKnot a r w Off Off tc) 
Instrument tc () () (Knot3 a r w Off Off Off tc) 
Instrument tc () () (EmitST2Array i a r w Off Off Off tc) 
Instrument tc () () (EmitST2ArrayFxp i a r w Off Off Off tc) 
Monoid a => Instrument tc (MonoidTC a) () (Monoid2 a r w On Off tc) 
Num i => Instrument tc (CounterTC1 i r) () (Counter i r w On Off tc) 
Instrument tc (CounterTC1 Int r) () (Knot3 a r w On Off Off tc) 
Num i => Instrument tc (CounterTC1 i r) () (EmitST2Array i a r w On Off Off tc) 

data MultiPassBase r w tc a Source

MultiPass, MultiPassPrologue, and MultiPassEpilogue are trivial newtype wrappers around this monad. Instruments can construct computations in the MultiPassBase monad, but then use mkMultiPass, mkMultiPassPrologue, and mkMultiPassEpilogue to restrict which of the three stages it is allowed to be used in.

Instances

mkMultiPass :: MultiPassBase r w tc a -> MultiPass r w tc aSource

Restrict a computation so that it can only be executed during the body of the algorithm (not the prologue or epilogue).

mkMultiPassPrologue :: MultiPassBase r w tc a -> MultiPassPrologue r w tc aSource

Restrict a computation so that it can only be executed during the prologue.

mkMultiPassEpilogue :: MultiPassBase r w tc a -> MultiPassEpilogue r w tc aSource

Restrict a computation so that it can only be executed during the epilogue.

data WrapInstrument instr Source

This abstract datatype is used as the result type of createInstrument. Instrument authors can create it using the wrapInstrument function, but cannot unwrap it. This ensures that instruments can only be constructed by the Control.Monad.MultiPass library.

wrapInstrument :: instr -> WrapInstrument instrSource

Create an object of type WrapInstrument. It is needed when defining a new instance of the Instrument class.

data PassNumber Source

This datatype is used by the back-tracking mechanism. Instruments can request that the evaluator back-tracks to a specific pass number. Instruments which use back-tracking store the relevant PassNumbers in their global context. The current PassNumber is the first argument of nextGlobalContext for this purpose. PassNumber is an abstract datatype. Instruments should never need to create a new PassNumber or modify an existing one, so no functions that operate on PassNumber are exported from this module.

data StepDirection Source

This datatype is used by the NextThreadContext and NextGlobalContext classes to specify whether the algorithm is progressing to the next pass or back-tracking to a previous pass. When back-tracking occurs, the current thread and global contexts are first passed the StepReset command. Then they are passed the StepBackward command N times, where N is the number of passes that need to be revisited. Note that N can be zero if only the current pass needs to be revisited, so the StepBackward command may not be used. This is the reason why the StepReset command is always issued first.

Instances

type ST2ToMP tc = forall r w a. ST2 r w a -> MultiPassBase r w tc aSource

The type of the first argument of createInstrument. It enables instruments to run ST2 in the MultiPassBase monad. (Clearly the st2ToMP argument needs to be used with care.)

type UpdateThreadContext tc tc' = forall r w. (tc' -> tc') -> MultiPassBase r w tc tc'Source

The type of the first argument of createInstrument. It used to read and write the thread context.

class Instrument rootTC tc gc instr | instr -> tc gc whereSource

Every instrument must define an instance of this class for each of its passes. For example, the Counter instrument defines the following instances:

 instance Instrument tc () () () (Counter i r w Off Off tc)

 instance Num i =>
          Instrument tc (CounterTC1 i r) () (Counter i r w On Off tc)

 instance Num i =>
          Instrument tc (CounterTC2 i r) () (Counter i r w On On tc)

The functional dependency from instr to tc and gc enables the run function to automatically deduce the type of the thread context and global context for each pass.

Methods

createInstrumentSource

Arguments

:: ST2ToMP rootTC 
-> UpdateThreadContext rootTC tc 
-> gc

Global context

-> WrapInstrument instr

Instrument

Instances

Instrument tc () () (Delay On On tc) 
Instrument tc () () (Delay On Off tc) 
Instrument tc () () (Delay Off Off tc) 
Instrument tc () () (CreateST2Array r w On tc) 
Instrument tc () () (CreateST2Array r w Off tc) 
Instrument tc () () (DelayedLift r w On tc) 
Instrument tc () () (DelayedLift r w Off tc) 
Instrument tc () () (Counter i r w Off Off tc) 
Instrument tc () () (Monoid2 a r w Off Off tc) 
Instrument tc () () (OrdCons a r w Off Off tc) 
Instrument tc () () (TopKnot a r w Off Off tc) 
Instrument tc () () (Knot3 a r w Off Off Off tc) 
Instrument tc () () (EmitST2Array i a r w Off Off Off tc) 
Instrument tc () () (EmitST2ArrayFxp i a r w Off Off Off tc) 
Monoid a => Instrument tc (MonoidTC a) () (Monoid2 a r w On Off tc) 
Num i => Instrument tc (CounterTC2 i r) () (Counter i r w On On tc) 
Num i => Instrument tc (CounterTC1 i r) () (Counter i r w On Off tc) 
Instrument tc (CounterTC1 Int r) () (Knot3 a r w On Off Off tc) 
Num i => Instrument tc (CounterTC1 i r) () (EmitST2Array i a r w On Off Off tc) 

class ThreadContext r w tc whereSource

This class is used when multiple threads are spawned. splitThreadContext is used to create a new thread context for each of the new threads and mergeThreadContext is used to merge them back together when the parallel region ends.

Methods

splitThreadContext :: Int -> Int -> tc -> ST2 r w tcSource

mergeThreadContext :: Int -> (Int -> ST2 r w tc) -> tc -> ST2 r w tcSource

Instances

ThreadContext r w () 
Monoid a => ThreadContext r w (MonoidTC a) 
(ThreadContext r w x, ThreadContext r w y) => ThreadContext r w (Either x y) 
(ThreadContext r w x, ThreadContext r w y) => ThreadContext r w (x, y) 
Num i => ThreadContext r w (CounterTC2 i r) 
Num i => ThreadContext r w (CounterTC1 i r) 
(ThreadContext r w x, ThreadContext r w y, ThreadContext r w z) => ThreadContext r w (x, y, z) 

class NextThreadContext r w tc gc tc' whereSource

This class is used to create the next thread context when the multi-pass algorithm proceeds to the next pass or back-tracks to the previous pass.

Methods

nextThreadContext :: PassNumber -> StepDirection -> tc -> gc -> ST2 r w tc'Source

Instances

NextThreadContext r w tc gc () 
Monoid a => NextThreadContext r w tc gc (MonoidTC a) 
(NextThreadContext r w () gc x, NextThreadContext r w () gc y) => NextThreadContext r w () gc (x, y) 
Num i => NextThreadContext r w () gc (CounterTC1 i r) 
(NextThreadContext r w () gc x, NextThreadContext r w () gc y, NextThreadContext r w () gc z) => NextThreadContext r w () gc (x, y, z) 
(NextThreadContext r w x gc x', NextThreadContext r w y gc y') => NextThreadContext r w (Either x y) gc (Either x' y') 
(NextThreadContext r w x gc x', NextThreadContext r w y gc y') => NextThreadContext r w (x, y) gc (x', y') 
Num i => NextThreadContext r w (CounterTC2 i r) gc (CounterTC2 i r) 
Num i => NextThreadContext r w (CounterTC2 i r) gc (CounterTC1 i r) 
Num i => NextThreadContext r w (CounterTC1 i r) gc (CounterTC2 i r) 
Num i => NextThreadContext r w (CounterTC1 i r) gc (CounterTC1 i r) 
(NextThreadContext r w x gc x', NextThreadContext r w y gc y', NextThreadContext r w z gc z') => NextThreadContext r w (x, y, z) gc (x', y', z') 

class NextGlobalContext r w tc gc gc' whereSource

This class is used to create the next global context when the multi-pass algorithm proceeds to the next pass or back-tracks to the previous pass.

Methods

nextGlobalContext :: PassNumber -> StepDirection -> tc -> gc -> ST2 r w gc'Source

Instances

NextGlobalContext r w tc gc () 
(NextGlobalContext r w tc x x', NextGlobalContext r w tc y y') => NextGlobalContext r w tc (Either x y) (Either x' y') 
(NextGlobalContext r w tc x x', NextGlobalContext r w tc y y') => NextGlobalContext r w tc (x, y) (x', y') 
(NextGlobalContext r w tc x x', NextGlobalContext r w tc y y', NextGlobalContext r w tc z z') => NextGlobalContext r w tc (x, y, z) (x', y', z') 

class BackTrack r w tc gc whereSource

Every instrument must define an instance of this class for each of its passes. It is used to tell the evaluator whether it needs to back-track. Instruments which do not back-track should use the default implementation of backtrack which returns Nothing (which means that no back-tracking is necessary.) If more than one instrument requests that the evaluator back-tracks then the evaluator will back-track to the earliest of the requested passes.

Methods

backtrack :: tc -> gc -> ST2 r w (Maybe PassNumber)Source

Instances

BackTrack r w tc ()