lvish-1.1.2: Parallel scheduler, LVar data structures, and infrastructure to build more.

Safe HaskellTrustworthy

Control.LVish.DeepFrz

Contents

Description

The DeepFrz module provides a way to return arbitrarily complex data structures containing LVars from Par computations.

The important thing to know is that to use runParThenFreeze to run a Par computation, you must make sure that all types you return from the Par computation have DeepFrz instances. This means that, if you wish to return a user-defined type, you will need to include a bit of boilerplate to give it a DeepFrz instance. Here is a complete example:

 
 import Control.LVish.DeepFrz
 
 data MyData = MyData Int deriving Show
 
 instance DeepFrz MyData where
   type FrzType MyData = MyData
 
 main = print (runParThenFreeze (return (MyData 3)))

Synopsis

The functions you'll want to use

runParThenFreeze :: DeepFrz a => Par Det NonFrzn a -> FrzType aSource

Under normal conditions, calling a freeze operation inside a Par computation makes the Par computation quasi-deterministic. However, if we freeze only after all LVar operations are completed (after the implicit global barrier of runPar), then we've avoided all data races, and freezing is therefore safe. Running a Par computation with runParThenFreeze accomplishes this, without our having to call freeze explicitly.

In order to use runParThenFreeze, the type returned from the Par computation must be a member of the DeepFrz class. All the Data.LVar.* libraries should provide instances of DeepFrz already. Further, you can create additional instances for custom, pure datatypes. The result of a runParThenFreeze depends on the type-level function FrzType, whose only purpose is to toggle the s parameters of all IVars to the Frzn state.

Significantly, the freeze at the end of runParThenFreeze has no runtime cost, in spite of the fact that it enables a deep (recursive) freeze of the value returned by the Par computation.

runParThenFreezeIO :: DeepFrz a => Par d NonFrzn a -> IO (FrzType a)Source

This version works for nondeterministic computations as well.

Of course, nondeterministic computations may also call freeze internally, but this function has an advantage to doing your own freeze at the end of a runParIO: there is an implicit barrier before the final freeze. Further, DeepFrz has no runtime overhead, whereas regular freezing has a cost.

Some supporting types

class DeepFrz a Source

DeepFreezing is a type-level (guaranteed O(1) time complexity) operation. It marks an LVar and its contents (recursively) as frozen. DeepFreezing is not an action that can be taken directly by the user, however. Rather, it is the final step in a runParThenFreeze invocation.

Associated Types

type FrzType a :: *Source

This type function is public. It maps pre-frozen types to frozen ones. It should be idempotent.

Instances

DeepFrz Bool 
DeepFrz Char 
DeepFrz Double 
DeepFrz Float 
DeepFrz Int 
DeepFrz Int8 
DeepFrz Int16 
DeepFrz Int32 
DeepFrz Int64 
DeepFrz Integer 
DeepFrz Ordering 
DeepFrz Word 
DeepFrz Word8 
DeepFrz Word16 
DeepFrz Word32 
DeepFrz Word64 
DeepFrz () 
DeepFrz a => DeepFrz [a] 
DeepFrz a => DeepFrz (Maybe a) 
(DeepFrz a, DeepFrz b) => DeepFrz (Either a b) 
(DeepFrz a, DeepFrz b) => DeepFrz (a, b) 
DeepFrz a => DeepFrz (IVar s a) 
DeepFrz a => DeepFrz (IStructure s a) 
DeepFrz a => DeepFrz (ISet s a) 
DeepFrz a => DeepFrz (ISet s a) 
DeepFrz a => DeepFrz (PureLVar s a) 
(DeepFrz a, DeepFrz b, DeepFrz c) => DeepFrz (a, b, c) 
DeepFrz a => DeepFrz (IMap k s a) 
DeepFrz a => DeepFrz (IMap k s a) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d) => DeepFrz (a, b, c, d) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d, DeepFrz e) => DeepFrz (a, b, c, d, e) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d, DeepFrz e, DeepFrz f) => DeepFrz (a, b, c, d, e, f) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d, DeepFrz e, DeepFrz f, DeepFrz g) => DeepFrz (a, b, c, d, e, f, g) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d, DeepFrz e, DeepFrz f, DeepFrz g, DeepFrz h) => DeepFrz (a, b, c, d, e, f, g, h) 
(DeepFrz a, DeepFrz b, DeepFrz c, DeepFrz d, DeepFrz e, DeepFrz f, DeepFrz g, DeepFrz h, DeepFrz i) => DeepFrz (a, b, c, d, e, f, g, h, i) 

data NonFrzn Source

This exists only for the purpose of being a type which is not equal to Frzn. One could just as well have used (), but this is more descriptive.

data Frzn Source

An uninhabited type that signals that an LVar has been frozen. LVars should use this in place of their s parameter.

Instances

Foldable (IStructure Frzn) 
Foldable (ISet Frzn) 
Foldable (ISet Frzn) 
Show a => Show (IVar Frzn a) 
Show a => Show (IStructure Frzn a) 
Show a => Show (ISet Frzn a) 
Show a => Show (ISet Frzn a) 
Show a => Show (PureLVar Frzn a) 
Foldable (IMap k Frzn) 
Foldable (IMap k Frzn) 
(Show k, Show a) => Show (IMap k Frzn a) 
(Show k, Show a) => Show (IMap k Frzn a) 

data Trvrsbl Source

An uninhabited type that signals that an LVar is not only frozen, but it may be traversed in whatever order its internal representation dictates.

Instances

Foldable (IVar Trvrsbl) 
Foldable (IStructure Trvrsbl) 
Foldable (ISet Trvrsbl) 
Foldable (ISet Trvrsbl) 
Show a => Show (IVar Trvrsbl a)

For convenience only; the user could define this.

Show a => Show (IStructure Trvrsbl a)

For convenience only; the user could define this.

Show a => Show (ISet Trvrsbl a)

For convenience; the user could define this.

Show a => Show (ISet Trvrsbl a)

For convenience only; the user could define this.

Foldable (IMap k Trvrsbl) 
Foldable (IMap k Trvrsbl) 
(Show k, Show a) => Show (IMap k Trvrsbl a)

For convenience only; the user could define this.

(Show k, Show a) => Show (IMap k Trvrsbl a)

For convenience only; the user could define this.