drama-0.1.0.3: Simple actor library for Haskell
Copyright© 2021 Evan Relf
LicenseBSD-3-Clause
Maintainerevan@evanrelf.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Drama

Description

Simple actor library for Haskell

Example

Expand

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

Documentation

data Actor msg a Source #

The Actor monad, where you can spawn other actors, and send and receive messages.

Since: 0.1.0.0

Instances

Instances details
Monad (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

(>>=) :: Actor msg a -> (a -> Actor msg b) -> Actor msg b #

(>>) :: Actor msg a -> Actor msg b -> Actor msg b #

return :: a -> Actor msg a #

Functor (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

fmap :: (a -> b) -> Actor msg a -> Actor msg b #

(<$) :: a -> Actor msg b -> Actor msg a #

MonadFix (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

mfix :: (a -> Actor msg a) -> Actor msg a #

MonadFail (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

fail :: String -> Actor msg a #

Applicative (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

pure :: a -> Actor msg a #

(<*>) :: Actor msg (a -> b) -> Actor msg a -> Actor msg b #

liftA2 :: (a -> b -> c) -> Actor msg a -> Actor msg b -> Actor msg c #

(*>) :: Actor msg a -> Actor msg b -> Actor msg b #

(<*) :: Actor msg a -> Actor msg b -> Actor msg a #

MonadIO (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

liftIO :: IO a -> Actor msg a #

Alternative (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

empty :: Actor msg a #

(<|>) :: Actor msg a -> Actor msg a -> Actor msg a #

some :: Actor msg a -> Actor msg [a] #

many :: Actor msg a -> Actor msg [a] #

MonadPlus (Actor msg) Source # 
Instance details

Defined in Drama.Internal

Methods

mzero :: Actor msg a #

mplus :: Actor msg a -> Actor msg a -> Actor msg a #

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 :: Actor msg () Source #

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

data Address msg Source #

The address for an actor. Returned after spawning an actor or asking for the current actor's address with here. Used to send messages to specific actors.

Since: 0.1.0.0

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

loop Source #

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 count

Since: 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

Running your program

run :: MonadIO m => Actor msg a -> m a Source #

Run a top-level actor. Intended to be used at the entry point of your program.

Since: 0.1.0.0