distributed-closure-0.5.0.0: Serializable closures for distributed programming.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Distributed.Closure

Description

Serializable closures for distributed programming. This package builds a "remotable closure" abstraction on top of static pointers. See this blog post for a longer introduction.

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 Closure). Closures can be serialized only if all expressions captured in the environment are serializable.

Instances

Instances details
IsStatic Closure Source # 
Instance details

Defined in Control.Distributed.Closure.Internal

Methods

fromStaticPtr :: StaticPtr a -> Closure a #

StaticApplicative Closure Source # 
Instance details

Defined in Control.Applicative.Static

Methods

staticPure :: Typeable a => Closure a -> Closure a Source #

StaticApply Closure Source # 
Instance details

Defined in Control.Applicative.Static

Methods

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

StaticComonad Closure Source # 
Instance details

Defined in Control.Comonad.Static

Methods

staticExtract :: Typeable a => Closure a -> a Source #

StaticExtend Closure Source # 
Instance details

Defined in Control.Comonad.Static

StaticBind Closure Source # 
Instance details

Defined in Control.Monad.Static

StaticFunctor Closure Source # 
Instance details

Defined in Data.Functor.Static

Methods

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

Typeable a => Binary (Closure a) Source # 
Instance details

Defined in Control.Distributed.Closure.Internal

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 #

Deprecated: Use staticMap instead.

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.

cduplicate :: Closure a -> Closure (Closure a) Source #

Turn a closure into a closure of a closure.

Special closures

newtype WrappedArrowClosure a b Source #

A newtype-wrapper useful for defining instances of classes indexed by higher-kinded types.

Constructors

WrapArrowClosure 

Fields

Instances

Instances details
StaticChoice WrappedArrowClosure Source # 
Instance details

Defined in Data.Profunctor.Choice.Static

StaticProfunctor WrappedArrowClosure Source # 
Instance details

Defined in Data.Profunctor.Static

StaticStrong WrappedArrowClosure Source # 
Instance details

Defined in Data.Profunctor.Strong.Static

(Typeable a, Typeable b) => Binary (WrappedArrowClosure a b) Source # 
Instance details

Defined in Control.Distributed.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? Whereas, for any constraint c, a value of type Closure (Dict c) can be serialized and sent over the wire, just like any Closure. A static dictionary for some constraint c is a value of type Closure (Dict c).

data Dict a 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 :: forall a. a => Dict a 

Instances

Instances details
() :=> (Semigroup (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

a :=> (Monoid (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Bounded (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Enum (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Read (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

HasDict a (Dict a) 
Instance details

Defined in Data.Constraint

Methods

evidence :: Dict a -> Dict a #

(Typeable p, p) => Data (Dict p) 
Instance details

Defined in Data.Constraint

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 :: forall r r'. (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) #

a => Monoid (Dict a) 
Instance details

Defined in Data.Constraint

Methods

mempty :: Dict a #

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

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

Semigroup (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Bounded (Dict a) 
Instance details

Defined in Data.Constraint

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 
Instance details

Defined in Data.Constraint

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] #

a => Read (Dict a) 
Instance details

Defined in Data.Constraint

Show (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

c => Boring (Dict c) 
Instance details

Defined in Data.Constraint

Methods

boring :: Dict c #

NFData (Dict c) 
Instance details

Defined in Data.Constraint

Methods

rnf :: Dict c -> () #

Eq (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

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

Ord (Dict a) 
Instance details

Defined in Data.Constraint

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 #

class c => Static c where Source #

It's often useful to create a static dictionary on-the-fly given any constraint. Morally, all type class constraints have associated static dictionaries, since these are either global values or simple combinations thereof. But GHC doesn't yet know how to invent a static dictionary on-demand yet given any type class constraint, so we'll have to do it manually for the time being. By defining instances of this type class manually, or via withStatic if it becomes too tedious.

Instances

Instances details
(Static c1, Static c2, Typeable c1, Typeable c2, (c1, c2)) => Static (c1, c2) Source # 
Instance details

Defined in Control.Distributed.Closure

Methods

closureDict :: Closure (Dict (c1, c2)) Source #

(Static c1, Static c2, Static c3, Typeable c1, Typeable c2, Typeable c3, (c1, c2, c3)) => Static (c1, c2, c3) Source # 
Instance details

Defined in Control.Distributed.Closure

Methods

closureDict :: Closure (Dict (c1, c2, c3)) Source #

(Static c1, Static c2, Static c3, Static c4, Typeable c1, Typeable c2, Typeable c3, Typeable c4, (c1, c2, c3, c4)) => Static (c1, c2, c3, c4) Source # 
Instance details

Defined in Control.Distributed.Closure

Methods

closureDict :: Closure (Dict (c1, c2, c3, c4)) Source #

(Static c1, Static c2, Static c3, Static c4, Static c5, Typeable c1, Typeable c2, Typeable c3, Typeable c4, Typeable c5, (c1, c2, c3, c4, c5)) => Static (c1, c2, c3, c4, c5) Source # 
Instance details

Defined in Control.Distributed.Closure

Methods

closureDict :: Closure (Dict (c1, c2, c3, c4, c5)) Source #

(Static c1, Static c2, Static c3, Static c4, Static c5, Static c6, Typeable c1, Typeable c2, Typeable c3, Typeable c4, Typeable c5, Typeable c6, (c1, c2, c3, c4, c5, c6)) => Static (c1, c2, c3, c4, c5, c6) Source # 
Instance details

Defined in Control.Distributed.Closure

Methods

closureDict :: Closure (Dict (c1, c2, c3, c4, c5, c6)) Source #