| Copyright | © 2021 Evan Relf |
|---|---|
| License | BSD-3-Clause |
| Maintainer | evan@evanrelf.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Drama
Description
Simple actor library for Haskell
Example
Fizz buzz, using three actors: main, logger, and fizzBuzz:
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NumericUnderscores #-}
module Main (main) where
import Control.Concurrent (threadDelay)
import Control.Monad (forever)
import Control.Monad.IO.Class (MonadIO (..))
import Drama
import Prelude hiding (log)
main :: IO ()
main = run do
loggerAddress <- spawn logger
_ <- spawn (fizzBuzz loggerAddress)
wait
logger :: Actor String ()
logger = forever do
string <- receive
liftIO $ putStrLn string
fizzBuzz :: Address String -> Actor () ()
fizzBuzz loggerAddress = do
let log = send loggerAddress
loop (0 :: Int) \n -> do
if | n `mod` 15 == 0 -> log "FizzBuzz"
| n `mod` 3 == 0 -> log "Fizz"
| n `mod` 5 == 0 -> log "Buzz"
| otherwise -> log (show n)
liftIO $ threadDelay 500_000
continue (n + 1)Output:
λ> main 1 2 Fizz 4 Buzz Fizz 7 8 Fizz Buzz 11 Fizz 13 14 FizzBuzz ...
Synopsis
- data Actor msg a
- spawn :: Actor childMsg () -> Actor msg (Address childMsg)
- wait :: Actor msg ()
- data Address msg
- here :: Actor msg (Address msg)
- send :: Address recipientMsg -> recipientMsg -> Actor msg ()
- receive :: Actor msg msg
- tryReceive :: Actor msg (Maybe msg)
- loop :: s -> (s -> Actor msg (Either s a)) -> Actor msg a
- continue :: s -> Actor msg (Either s a)
- exit :: a -> Actor msg (Either s a)
- run :: MonadIO m => Actor msg a -> m a
Documentation
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 # | |
Spawning actors
spawn :: Actor childMsg () -> Actor msg (Address childMsg) Source #
Spawn a new actor. Returns the spawned actor's address.
Example:
printerAddress <- spawn printer
Since: 0.1.0.0
Wait for all actors spawned by the current actor to terminate.
Example:
fooAddress <- spawn foo barAddress <- spawn bar wait
Since: 0.1.0.0
Messages
Addresses
here :: Actor msg (Address msg) Source #
Return the current actor's own address. Useful for sending your address to other actors, or for sending yourself a message.
Since: 0.1.0.0
Sending messages
send :: Address recipientMsg -> recipientMsg -> Actor msg () Source #
Given an actor's address, send it a message.
Example:
send printerAddress "Hello, world!"
Since: 0.1.0.0
Receiving messages
receive :: Actor msg msg Source #
Receive a message sent to the actor's mailbox. This function blocks until a message is received.
Example:
printer :: Actor String () printer = forever do string <- receive liftIO $ putStrLn string
Since: 0.1.0.0
tryReceive :: Actor msg (Maybe msg) Source #
Receive a message sent to the actor's mailbox. This function blocks until a message is received.
Example:
printer :: Actor String ()
printer = forever do
tryReceive >>= \case
Just string -> liftIO $ putStrLn string
Nothing -> ...Since: 0.1.0.0
Managing state
Arguments
| :: s | Initial state |
| -> (s -> Actor msg (Either s a)) | Action to perform, either returning a new state to continue looping, or a final value to stop looping. |
| -> Actor msg a |
Loop indefinitely with state. Use forever for stateless
infinite loops.
Example:
counter :: Actor () Int
counter = loop 10 \count -> do
liftIO $ print count
if count > 0
then continue (count - 1)
else exit countSince: 0.1.0.0
continue :: s -> Actor msg (Either s a) Source #
Continue looping with state.
continue s = pure (Left s)
Since: 0.1.0.0
exit :: a -> Actor msg (Either s a) Source #
Exit loop with value.
exit x = pure (Right x)
Since: 0.1.0.0