objective-0.6.5.1: Extensible objects

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Object.Object

Synopsis

Documentation

newtype Object f g Source

The type Object f g represents objects which can handle messages f, perform actions in the environment g. It can be thought of as an automaton that converts effects. Objects can be composed just like functions using @>>@; the identity element is echo. Objects are morphisms of the category of functors

Constructors

Object 

Fields

runObject :: forall x. f x -> g (x, Object f g)
 

Instances

Typeable ((* -> *) -> (* -> *) -> *) Object 
type InstOf IO (Object f g) = Inst IO f g 
type InstOf (ST s) (Object f g) = Inst (ST s) f g 

(@-) :: Object f g -> f x -> g (x, Object f g) infixr 3 Source

An alias for runObject.

echo :: Functor f => Object f f Source

The identity object

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

Lift a natural transformation into an object.

unfoldO :: Functor g => (forall a. r -> f a -> g (a, r)) -> r -> Object f g Source

The unwrapped analog of stateful unfoldO runObject = id unfoldO runSequential = sequential unfoldO iterObject = iterable

unfoldOM :: Monad m => (forall a. r -> f a -> m (a, r)) -> r -> Object f m Source

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

Build a stateful object.

stateful t s = t ^>> variable s@

(@>>@) :: Functor h => Object f g -> Object g h -> Object f h infixr 1 Source

Object-object composition

(@<<@) :: Functor h => Object g h -> Object f g -> Object f h infixl 1 Source

Reversed '(>>)'

(@>>^) :: Functor h => Object f g -> (forall x. g x -> h x) -> Object f h infixr 1 Source

Object-function composition

(^>>@) :: Functor h => (forall x. f x -> g x) -> Object g h -> Object f h infixr 1 Source

Function-object composition

(@**@) :: Applicative m => Object f m -> Object g m -> Object (Day f g) m infixr 3 Source

Parallel composition

(@||@) :: Functor m => Object f m -> Object g m -> Object (Coproduct f g) m infixr 2 Source

Objective fanin

sharing :: Monad m => (forall a. f a -> StateT s m a) -> s -> Object (Union `[State s, f]`) m Source

Build a stateful object, sharing out the state.

(@!) :: Monad m => Object e m -> ReifiedProgram e a -> m (a, Object e m) infixr 3 Source

(@!!) :: Monad m => Object e m -> ReifiedProgramT e m a -> m (a, Object e m) infixr 3 Source

iterObject :: Monad m => Object f m -> Free f a -> m (a, Object f m) Source

iterTObject :: Monad m => Object f m -> FreeT f m a -> m (a, Object f m) Source

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

Let object handle ReifiedProgram.

sequentialT :: Monad m => Object e m -> Object (ReifiedProgramT e m) m Source

Let object handle ReifiedProgramT.

iterative :: Monad m => Object f m -> Object (Free f) m Source

iterativeT :: Monad m => Object f m -> Object (FreeT f m) m Source

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. g x -> f x) -> Object f m -> Object g m Source

Apply a function to methods coming into an object.