distributed-closure-0.1.0.0: Serializable closures for distributed programming.

Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Closure

Contents

Description

Serializable closures for distributed programming.

Synopsis

Documentation

type Serializable a = (Binary a, Typeable a) Source #

Values that can be sent across the network.

Closures

data Closure a Source #

Type of serializable closures. Abstractly speaking, a closure is a code reference paired together with an environment. A serializable closure includes a shareable code reference (i.e. a StaticPtr). Closures can be serialized only if all expressions captured in the environment are serializable.

Instances

Typeable * a => Binary (Closure a) Source # 

Methods

put :: Closure a -> Put #

get :: Get (Closure a) #

putList :: [Closure a] -> Put #

closure :: StaticPtr a -> Closure a Source #

Lift a Static pointer to a closure with an empty environment.

unclosure :: Closure a -> a Source #

Resolve a Closure to the value that it represents. Calling unclosure multiple times on the same closure is efficient: for most argument values the result is memoized.

cpure :: Closure (Dict (Serializable a)) -> a -> Closure a Source #

A closure can be created from any serializable value. cpure corresponds to Control.Applicative's pure, but restricted to lifting serializable values only.

cap :: Typeable a => Closure (a -> b) -> Closure a -> Closure b Source #

Closure application. Note that Closure is not a functor, let alone an applicative functor, even if it too has a meaningful notion of application.

cmap :: Typeable a => StaticPtr (a -> b) -> Closure a -> Closure b Source #

Closure is not a Functor, in that we cannot map arbitrary functions over it. That is, we cannot define fmap. However, we can map a static pointer to a function over a Closure.

Closure dictionaries

A Dict reifies a constraint in the form of a first class value. The Dict type is not serializable: how do you serialize the constraint that values of this type carry? However, for any constraint c, a value of type Closure (Dict c) can be serialized and sent over the wire, just like any Closure. A serializable dictionary for some constraint c is a value of type Closure (Dict c).

data Dict a :: Constraint -> * where #

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq 'Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: Dict a 

Instances

a :=> (Read (Dict a)) 

Methods

ins :: a :- Read (Dict a) #

a :=> (Monoid (Dict a)) 

Methods

ins :: a :- Monoid (Dict a) #

a :=> (Enum (Dict a)) 

Methods

ins :: a :- Enum (Dict a) #

a :=> (Bounded (Dict a)) 

Methods

ins :: a :- Bounded (Dict a) #

() :=> (Eq (Dict a)) 

Methods

ins :: () :- Eq (Dict a) #

() :=> (Ord (Dict a)) 

Methods

ins :: () :- Ord (Dict a) #

() :=> (Show (Dict a)) 

Methods

ins :: () :- Show (Dict a) #

a => Bounded (Dict a) 

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

Eq (Dict a) 

Methods

(==) :: Dict a -> Dict a -> Bool #

(/=) :: Dict a -> Dict a -> Bool #

(Typeable Constraint p, p) => Data (Dict p) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) #

toConstr :: Dict p -> Constr #

dataTypeOf :: Dict p -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) #

gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

Ord (Dict a) 

Methods

compare :: Dict a -> Dict a -> Ordering #

(<) :: Dict a -> Dict a -> Bool #

(<=) :: Dict a -> Dict a -> Bool #

(>) :: Dict a -> Dict a -> Bool #

(>=) :: Dict a -> Dict a -> Bool #

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

a => Read (Dict a) 
Show (Dict a) 

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

a => Monoid (Dict a) 

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #