| Copyright | © 2022 Evan Relf |
|---|---|
| License | BSD-3-Clause |
| Maintainer | evan@evanrelf.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Drama
Description
Actor library for Haskell
Example
An actor which encapsulates a piece of mutable state. Its StateMsg type
specifies which messages it accepts, which messages return a response, and
what type that response is.
data StateMsg s res where
GetState :: StateMsg s s
GetsState :: (s -> a) -> StateMsg s a
PutState :: s -> StateMsg s ()
ModifyState :: (s -> s) -> StateMsg s ()
state :: s -> Actor (StateMsg s) ()
state s0 = do
stateIORef <- liftIO $ newIORef s0
forever $ receive \case
GetState ->
liftIO $ readIORef stateIORef
GetsState f -> do
s <- liftIO $ readIORef stateIORef
pure (f s)
PutState s ->
liftIO $ writeIORef stateIORef s
ModifyState f ->
liftIO $ modifyIORef stateIORef fSynopsis
- data Actor (msg :: Type -> Type) a
- spawn :: Actor msg () -> Actor _msg (Address msg)
- wait :: Actor msg ()
- data Address msg
- cast :: Address msg -> msg () -> Actor _msg ()
- call :: Address msg -> msg res -> Actor _msg res
- getSelf :: Actor msg (Address msg)
- receive :: (forall res. msg res -> Actor msg res) -> Actor msg ()
- tryReceive :: (forall res. msg res -> Actor msg res) -> Actor msg Bool
- runActor :: MonadIO m => Actor msg a -> m a
- type Actor_ = Actor NoMsg
- data NoMsg res
- spawn_ :: Actor_ () -> Actor msg ()
- runActor_ :: MonadIO m => Actor_ a -> m a
Documentation
data Actor (msg :: Type -> Type) a Source #
Monad supporting actor operations.
Since: 0.4.0.0
Instances
| Monad (Actor msg) Source # | |
| Functor (Actor msg) Source # | |
| MonadFix (Actor msg) Source # | |
Defined in Drama.Internal | |
| MonadFail (Actor msg) Source # | |
Defined in Drama.Internal | |
| Applicative (Actor msg) Source # | |
| MonadIO (Actor msg) Source # | |
Defined in Drama.Internal | |
| Alternative (Actor msg) Source # | |
| MonadPlus (Actor msg) Source # | |
| MonadUnliftIO (Actor msg) Source # | Since: 0.5.0.0 |
Defined in Drama.Internal | |
Spawning actors
Spawn a child actor and return its address.
Since: 0.4.0.0
Sending messages
Send a message to another actor, expecting no response. Returns immediately without blocking.
Since: 0.4.0.0
Send a message to another actor, and wait for a response.
Since: 0.4.0.0
Receiving messages
Arguments
| :: (forall res. msg res -> Actor msg res) | Callback function that responds to messages |
| -> Actor msg () |
Receive a message. When the mailbox is empty, blocks until a message arrives.
Since: 0.4.0.0
Arguments
| :: (forall res. msg res -> Actor msg res) | Callback function that responds to messages |
| -> Actor msg Bool |
Try to receive a message. When the mailbox is empty, returns immediately.
Since: 0.4.0.0
Running your program
runActor :: MonadIO m => Actor msg a -> m a Source #
Run a top-level actor. Intended to be used at the entry point of your program.
If your program is designed with actors in mind, you can use Actor as
your program's base monad:
main :: IO () main = runActor root root :: Actor RootMsg () root = do ...
Otherwise, use runActor like you would with run functions from libraries
like transformers or mtl.
Since: 0.4.0.0