| Copyright | (c) Fumiaki Kinoshita 2015 |
|---|---|
| License | BSD3 |
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
| Stability | provisional |
| Portability | GADTs, Rank2Types |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Control.Object.Object
Description
- newtype Object f g = Object {}
- echo :: Functor f => Object f f
- (@>>@) :: Functor h => Object f g -> Object g h -> Object f h
- (@<<@) :: Functor h => Object g h -> Object f g -> Object f h
- liftO :: Functor g => (forall x. f x -> g x) -> Object f g
- (^>>@) :: Functor h => (forall x. f x -> g x) -> Object g h -> Object f h
- (@>>^) :: Functor h => Object f g -> (forall x. g x -> h x) -> Object f h
- (@||@) :: Functor h => Object f h -> Object g h -> Object (f `Sum` g) h
- unfoldO :: Functor g => (forall a. r -> f a -> g (a, r)) -> r -> Object f g
- unfoldOM :: Monad m => (forall a. r -> f a -> m (a, r)) -> r -> Object f m
- stateful :: Monad m => (forall a. t a -> StateT s m a) -> s -> Object t m
- (@~) :: Monad m => s -> (forall a. t a -> StateT s m a) -> Object t m
- variable :: Monad m => s -> Object (StateT s m) m
- (@-) :: Object f g -> f x -> g (x, Object f g)
- iterObject :: Monad m => Object f m -> Free f a -> m (a, Object f m)
- iterative :: Monad m => Object f m -> Object (Free f) m
- cascadeObject :: Monad m => Object t m -> Skeleton t a -> m (a, Object t m)
- cascading :: Monad m => Object t m -> Object (Skeleton t) m
- data Fallible t a where
- filteredO :: Monad m => (forall x. t x -> Bool) -> Object t m -> Object (Fallible t) m
- filterO :: (forall x. t x -> Bool) -> Object (Fallible t) (Skeleton t)
- invokesOf :: Monad m => ((Object t m -> WriterT r m (Object t m)) -> s -> WriterT r m s) -> t a -> (a -> r) -> StateT s m r
- invokes :: (Traversable t, Monad m, Monoid r) => f a -> (a -> r) -> StateT (t (Object f m)) m r
- (@!=) :: Monad m => ((Object t m -> WriterT a m (Object t m)) -> s -> WriterT a m s) -> t a -> StateT s m a
- announce :: (Traversable t, Monad m) => f a -> StateT (t (Object f m)) m [a]
- withBuilder :: Functor f => ((a -> Endo [a]) -> f (Endo [a])) -> f [a]
Documentation
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 transforms effects.
Objects can be composed just like functions using @>>@; the identity element is echo.
Objects are morphisms of the category of actions.
- Naturality
runObject obj . fmap f ≡ fmap f . runObject obj
(@>>@) :: Functor h => Object f g -> Object g h -> Object f h infixr 1 Source
The categorical composition of objects.
liftO :: Functor g => (forall x. f x -> g x) -> Object f g Source
Lift a natural transformation into an object.
(@||@) :: Functor h => Object f h -> Object g h -> Object (f `Sum` g) h Source
Combine objects so as to handle a Sum of interfaces.
Stateful construction
unfoldO :: Functor g => (forall a. r -> f a -> g (a, r)) -> r -> Object f g Source
An unwrapped analog of stateful
id = unfoldO runObject
iterative = unfoldO iterObjectcascading = unfoldO cascadeObject
stateful :: Monad m => (forall a. t a -> StateT s m a) -> s -> Object t m Source
Build a stateful object.
stateful t s = t ^>>@ variable s
(@~) :: Monad m => s -> (forall a. t a -> StateT s m a) -> Object t m infix 1 Source
Flipped stateful.
it is super convenient to use with the LambdaCase extension.
Method cascading
iterative :: Monad m => Object f m -> Object (Free f) m Source
Objects can consume free monads. cascading is more preferred.
cascadeObject :: Monad m => Object t m -> Skeleton t a -> m (a, Object t m) Source
Pass zero or more messages to an object.
cascading :: Monad m => Object t m -> Object (Skeleton t) m Source
Add capability to handle multiple messages at once.
Filtering
Manipulation on StateT
invokesOf :: Monad m => ((Object t m -> WriterT r m (Object t m)) -> s -> WriterT r m s) -> t a -> (a -> r) -> StateT s m r Source
Send a message to an object through a lens.
invokes :: (Traversable t, Monad m, Monoid r) => f a -> (a -> r) -> StateT (t (Object f m)) m r Source
(@!=) :: Monad m => ((Object t m -> WriterT a m (Object t m)) -> s -> WriterT a m s) -> t a -> StateT s m a Source
A method invocation operator on StateT.
announce :: (Traversable t, Monad m) => f a -> StateT (t (Object f m)) m [a] Source
Send a message to objects in a traversable container.
announce = withBuilder . invokesOf traverse
withBuilder :: Functor f => ((a -> Endo [a]) -> f (Endo [a])) -> f [a] Source