objective-0.4: Extensible objects

Safe HaskellNone
LanguageHaskell2010

Control.Object

Contents

Synopsis

Construction

newtype Object e m Source

The type 'Object e m' represents objects which can handle messages e, perform actions in the environment m. It can be thought of as an automaton that converts effects. Objects can be composed just like functions using .>>.; the identity element is echo.

Constructors

Object 

Fields

runObject :: forall x. e x -> m (x, Object e m)
 

Instances

Typeable ((* -> *) -> (* -> *) -> *) Object 

liftO :: Functor f => (forall x. e x -> f x) -> Object e f Source

Lift a natural transformation into an object.

echo :: Functor e => Object e e Source

Parrots messages given.

oneshot :: (Functor e, Monad m) => (forall a. e (m a) -> m a) -> Object e m Source

Build an object using continuation passing style.

stateful :: Monad m => (forall a. e a -> StateT s m a) -> s -> Object e m Source

Build a stateful object.

variable :: Applicative f => s -> Object (State s) f Source

A mutable variable.

Composition

(.>>.) :: Functor n => Object e m -> Object m n -> Object e n infixr 4 Source

Compose two objects (aka Dependency Injection).

transObject :: Functor g => (forall x. f x -> g x) -> Object e f -> Object e g Source

Change the workspace of the object.

adaptObject :: Functor m => (forall x. e x -> f x) -> Object f m -> Object e m Source

Apply a function to the messages coming into the object.

sequential :: Monad m => Object e m -> Object (Free e) m Source

Convert a method sequence into a sequential method execution.

Extensible objects

loner :: Functor m => Object Nil m Source

An object that won't accept any messages.

(.|>.) :: Functor m => Object f m -> Object (Union s) m -> Object (f |> Union s) m Source

Extend an object by adding another independent object.

sharing :: Monad m => (forall a. e a -> StateT s m a) -> s -> Object (State s |> (e |> Nil)) m Source

Build a stateful object, sharing out the state.

Utilitites

data Request a b r Source

Constructors

Request a (b -> r) 

Instances

Lift (Request a b) (Request a b) 

request :: Lift (Request a b) f => a -> f b Source

accept :: Functor f => (a -> f b) -> Request a b r -> f r Source

acceptM :: Monad m => (a -> m b) -> Request a b r -> m r Source

class Lift f g | g -> f where Source

Methods

lift_ :: f a -> g a Source

Instances

(∈) (* -> *) f u => Lift f (Union u) 
Lift (StateT s m) (StateT s m) 
Lift (Request a b) (Request a b) 

get_ :: (Monad m, Lift (StateT s m) f) => f s Source

modify_ :: (Monad m, Lift (StateT s m) f) => (s -> s) -> f () Source

put_ :: (Monad m, Lift (StateT s m) f) => s -> f () Source