MonadCompose-0.8.1.0: Methods for composing monads.

Safe HaskellNone
LanguageHaskell98

Control.Linear

Contents

Description

A linear type-based I/O system a la Clean.

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) 
Default a => Arrow (A a) 
Default a => ArrowChoice (A a) 

data Blank Source

Instances

data Pair t u Source

Instances

(Storable a, Storable b) => Storable (Pair a b) 

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

(>>==) :: A t2 t t3 -> (t2 -> A t1 t3 v) -> A t1 t 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 a1)) (Either (Pair t a) (Pair t a1)) Source

void' :: A t1 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

Safe pointer facilities

data Pointer p s t Source

data Freeable Source

Pointers can be freeable, foreign, or focused. There are the following tradeoffs:

  • Freeable pointers support strong update, but can only be split under focusing.
  • Foreign 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

Freeable 

data Foreign Source

Constructors

Foreign 

Instances

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

class Weakening t where Source

Methods

weakening :: A () t Blank Source

contraction :: Copyable s => A () (Pointer p s t) (Pair (Pointer p s t) (Pointer p s t)) Source

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

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

free :: A () (Pointer p2 Placeholder t) Blank 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, Copyable 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) (Pair v St)) -> A a (Pair (Pointer p2 s t) u) (Pair (Pair (Pointer p2 s t) v) St) Source

Focusing on a pointer.

Temporarily turns a freeable pointer into a focused pointer. I get the freeable 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 Freeable 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 Freeable 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

newForeign :: Storable t => t -> A () Blank (Pointer p Foreign t) Source

Allocate a Foreign pointer.

peek1 :: (Storable t, Copyable s) => A t (Pair (Pointer p s t) St) (Pair (Pointer p s t) St) Source

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