objective-0.6.3: Extensible objects

Copyright(c) Fumiaki Kinoshita 2014
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Object

Contents

Description

Stateful effect transducer: The Mealy machine for effects.

Synopsis

Construction

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 5 Source

An alias for runObject.

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

Lift a natural transformation into an object.

echo :: Functor f => Object f f Source

The identity object

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

Build an object using continuation passing style.

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@

variable :: s -> Variable s Source

A mutable variable.

type Variable s = forall m. Monad m => Object (StateT s m) m Source

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

foldP :: Applicative f => (a -> r -> f r) -> r -> Object (PushPull a r) f Source

foldP' :: Applicative f => (a -> r -> r) -> r -> Object (PushPull a r) f Source

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

Build a stateful object, sharing out the state.

animate :: (Applicative m, Num t) => (t -> m a) -> Object (Request t a) m Source

transit :: (Alternative m, Fractional t, Ord t) => t -> (t -> m a) -> Object (Request t a) m Source

Composition

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

Object-object composition

(@>>^) :: 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

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

loner :: Functor f => Object Nil f Source

An object that won't accept any messages.

(@|>@) :: Functor g => Object f g -> Object (Union s) g -> Object (f |> Union s) g infixr 3 Source

Extend an object by adding another independent object.

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 the messages coming into the object.

Stream

($$) :: (Monad m, Adjunction f g) => Object g m -> Object f m -> m x infix 0 Source

For every adjunction f ⊣ g, we can "connect" Object g m and Object f m permanently.

($$!) :: (Monad m, Adjunction f g) => Object g m -> Mortal f m a -> m (Object g m, a) infix 0 Source

Like $$, but kept until the right Mortal dies.

(!$$) :: (Monad m, Adjunction f g) => Mortal g m a -> Object f m -> m (a, Object f m) infix 0 Source

Like $$, but kept until the left Mortal dies.

(!$$!) :: (Monad m, Adjunction f g) => Mortal g m a -> Mortal f m b -> m (Either (a, Mortal f m b) (Mortal g m a, b)) infix 0 Source

Connect two Mortals.

Monads

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

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

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

Let object handle sequential methods.

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

Let object handle sequential methods.

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

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

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

Patterns

flyweight :: (Monad m, Ord k) => (k -> m a) -> Object (Request k a) m Source

The flyweight pattern.

flyweight' :: (Monad m, Eq k, Hashable k) => (k -> m a) -> Object (Request k a) m Source

Like flyweight, but it uses Strict internally.

announce :: (Traversable t, Monad m, Elevate (State (t (Object f g))) m, Elevate g m) => f a -> m [a] Source

announceMaybe :: (Witherable t, Monad m, Elevate (State (t (Object f Maybe))) m) => f a -> m [a] Source

announceMaybeT :: (Witherable t, Monad m, State (t (Object f (MaybeT g))) Floors1 m, g Floors1 m, Tower m) => f a -> m [a] Source

newtype Process m a b Source

An object which is specialized to be a Mealy machine

Constructors

Process 

Fields

unProcess :: Object (Request a b) m
 

Instances

Monad m => Category * (Process m) 
Monad m => Arrow (Process m) 
Monad m => ArrowChoice (Process m) 
Monad m => Strong (Process m) 
Monad m => Choice (Process m) 
Monad m => Profunctor (Process m) 
Functor f => Functor (Process f a) 
Applicative f => Applicative (Process f a) 
(Applicative m, Fractional o) => Fractional (Process m i o) 
(Applicative m, Num o) => Num (Process m i o) 
(Applicative f, Monoid b) => Monoid (Process f a b) 

_Process :: (Profunctor p, Functor f) => p (Process m a b) (f (Process m a b)) -> p (Object (Request a b) m) (f (Object (Request a b) m)) Source

_Process :: Iso' (Object (Request a b) m) (Process m a b)

newtype Mortal f g a Source

Object with a final result.

Object f g ≡ Mortal f g Void

Constructors

Mortal 

Fields

unMortal :: Object f (EitherT a g)
 

Instances

Monad m => Monad (Mortal f m) 
(Functor m, Monad m) => Functor (Mortal f m) 
(Functor m, Monad m) => Applicative (Mortal f m) 

runMortal :: Monad m => Mortal f m a -> f x -> m (Either a (x, Mortal f m a)) Source