MonadCompose-0.8.4.2: Methods for composing monads.

Safe HaskellTrustworthy
LanguageHaskell98

Control.Linear

Contents

Description

A linear type-based I/O system a la Clean - including a "safe C" (like Cyclone).

This is an alternative to composing monads - one can decompose them into their corresponding comonads, with linear operations for manipulating them. (See Kieburtz, http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.46.5169&rep=rep1&type=pdf)

Synopsis

Documentation

data St Source

Values representing the real world.

data A t u v Source

Linear computations are arrows over linear data, but monads over nonlinear data.

Instances

Default a => Category * (A a) Source 
Default a => Arrow (A a) Source 
Default a => ArrowChoice (A a) Source 

data Pair t u Source

Instances

type Fn t u = A () (Pair t St) (Pair u St) Source

(>>==) :: A t t1 t3 -> (t -> A t2 t3 v) -> A t2 t1 v infixl 1 Source

Monadic bind (for nonlinear data).

rtn :: t -> A t v v Source

Monadic return

Algebraic operations

bimap :: A t3 t t2 -> A t4 t1 u -> A (t3, t4) (Pair t t1) (Pair t2 u) Source

assoc1 :: A () (Pair (Pair t t1) u) (Pair t (Pair t1 u)) Source

assoc2 :: A () (Pair t (Pair u1 u)) (Pair (Pair t u1) u) Source

drop1 :: A () (Pair Blank v) v Source

drop2 :: A () (Pair v Blank) v Source

undrop1 :: A () u (Pair Blank u) Source

undrop2 :: A () t (Pair t Blank) Source

swap :: A () (Pair u t) (Pair t u) Source

apply :: A t (Pair (A t t1 v) t1) v Source

curry :: A t (Pair t1 u) v -> A () t1 (A t u v) Source

distr :: A () (Pair t (Either a b)) (Either (Pair t a) (Pair t b)) Source

assoc3 :: ((t, t1), t2) -> (t, (t1, t2)) Source

assoc4 :: (t1, (t2, t)) -> ((t1, t2), t) Source

void' :: A b t v -> A () t v Source

bimap' :: A () t u -> A () v w -> A () (Pair t v) (Pair u w) Source

Basic I/O system

data Open p Source

Instances

data Placeholder Source

Constructors

Placeholder 

fileSize :: Openhandle h => A Integer (Pair h St) (Pair h St) Source

setFileSize :: Openhandle t => Integer -> A () (Pair t St) (Pair t St) Source

eof :: Openhandle h => A Bool (Pair h St) (Pair h St) Source

seek :: Openhandle t => SeekMode -> Integer -> A () (Pair t St) (Pair t St) Source

tell :: Openhandle h => A Integer (Pair h St) (Pair h St) Source

char :: Openhandle h => A Char (Pair h St) (Pair h St) Source

line :: Openhandle h => A String (Pair h St) (Pair h St) Source

lookahead :: Openhandle h => A Char (Pair h St) (Pair h St) Source

putC :: Openhandle t => Char -> A () (Pair t St) (Pair t St) Source

putS :: Openhandle t => String -> A () (Pair t St) (Pair t St) Source

random :: Random t => (t, t) -> A t Blank Blank Source

Safe pointer facilities

data Linear Source

Pointers can be linear, nonlinear, or focused. There are the following tradeoffs:

  • Linear pointers support strong update, but can only be split under focusing.
  • Nonlinear pointers can be split, but do not support strong update.

Placeholders classify pointers that either point to junk or to data that is not allowed to be used (to maintain linearity).

Constructors

Linear 

data Nonlinear Source

Constructors

Nonlinear 

data Focused Source

Constructors

Focused 

Instances

data Fix f Source

With the Fix constructor, I can build data structures of linear data.

Constructors

In (f (Fix f)) 

fixInj1 :: Pointer p s (Fix f) -> Pointer p s (f (Fix f)) Source

fixInj2 :: Pointer p s (f (Fix f)) -> Pointer p s (Fix f) Source

new :: Storable t => A () St (Pair (Pointer p Placeholder t) St) Source

Allocate a new linear block (containing junk), Use poke' to initialize it.

free :: A () (Pair (Pointer p2 Placeholder t) St) St Source

Use peek' to take ownership of the contents of a block before freeing it.

split :: forall t u p s. (Storable t, Storable u, Splittable s) => A () (Pointer p s (Pair t u)) (Pair (Pointer p s t) (Pointer p s u)) Source

Split a pointer to a pair, into a pair of pointers.

ptrSwap :: Storable t => Fn (Pair (Pointer p s t) t) (Pair (Pointer p s t) t) Source

Focusing

focus :: (forall p. A a (Pair (Pointer p Focused t) u) v) -> A a (Pair (Pointer p s t) u) (Pair (Pointer p s t) v) Source

Focusing on a pointer.

Temporarily turns a linear pointer into a focused pointer. I get the linear pointer back after all copies have been surrendered (with weakening).

focusHdl :: (forall p. A a (Pair (Open p) t) u) -> A a (Pair Exclusive t) (Pair Exclusive u) Source

Focusing on a handle.

Strong update

peek' :: Storable t => Fn (Pointer p Linear t) (Pair (Pointer p Placeholder t) t) Source

Take the data out of a block, making it a placeholder.

poke' :: Storable t => Fn (Pair (Pointer p Placeholder t) t) (Pointer p Linear t) Source

The reverse operation.

changeType :: forall t u p. (Storable t, Storable u) => A () (Pointer p Placeholder t) (Pointer p Placeholder u) Source

A placeholder block can change its type.

Operations on nonlinear data / Weak update

newNonlinear :: Storable t => t -> A () Blank (Pointer p Nonlinear t) Source

Allocate a nonlinear pointer.

poke1 :: Storable t => t -> Fn (Pointer p s t) (Pointer p s t) Source

Multithreading

fork :: A () St (Pair St St) Source

Duplicate the world state. This is interpreted as creating a thread.

join' :: A () (Pair St St) St Source

Sync together two world states.

Example programs