MonadCompose-0.8.0.0: Methods for composing monads.

Safe HaskellNone
LanguageHaskell98

Control.Linear

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

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

data Freeable Source

Pointers can be freeable or foreign. Freeable pointers are created with new. Linearity is enforced for them, so I can do strong update, but the need to keep track of all pointers means that split cannot be supported. Foreign pointers on the other hand can be copied indefinitely since the garbage collector is keeping track of them.

Freeable pointers can be turned into foreign pointers permanently using newForeign, or temporarily by focusing.

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 

data Placeholder Source

Constructors

Placeholder 

data Pointer p s t 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

run :: A a St St -> IO a Source

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

frst :: (Storable a, Storable b) => Ptr (Pair a b) -> Ptr a Source

secnd :: forall a b. (Storable a, Storable b) => Ptr (Pair a b) -> Ptr b Source

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

get :: Nonlinear t => ForeignPtr t -> A () Blank (Pointer p Foreign t) Source

contraction :: A () (Pointer p Foreign t) (Pair (Pointer p Foreign t) (Pointer p Foreign t)) Source

Contraction and weakening are available for pointers created from ForeignPtrs (and pointers I am focusing on).

focus :: (forall p. A a (Pair (Pointer p Foreign 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.

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

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

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

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

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