drama-0.5.0.0: Actor library for Haskell
Copyright© 2022 Evan Relf
LicenseBSD-3-Clause
Maintainerevan@evanrelf.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Drama

Description

Actor library for Haskell

Example
Expand

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 f
Synopsis

Documentation

data Actor (msg :: Type -> Type) a Source #

Monad supporting actor operations.

Since: 0.4.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 #

MonadUnliftIO (Actor msg) Source #

Since: 0.5.0.0

Instance details

Defined in Drama.Internal

Methods

withRunInIO :: ((forall a. Actor msg a -> IO a) -> IO b) -> Actor msg b #

Spawning actors

spawn Source #

Arguments

:: Actor msg ()

Actor to spawn

-> Actor _msg (Address msg)

Spawned actor's address

Spawn a child actor and return its address.

Since: 0.4.0.0

wait :: Actor msg () Source #

Block until all child actors have terminated.

Since: 0.4.0.0

Sending messages

data Address msg Source #

Address for sending messages to an actor. Obtained by running spawn, getSelf, or receive (if another actor sends you an address).

Since: 0.4.0.0

cast Source #

Arguments

:: Address msg

Actor's address

-> msg ()

Message to send

-> Actor _msg () 

Send a message to another actor, expecting no response. Returns immediately without blocking.

Since: 0.4.0.0

call Source #

Arguments

:: Address msg

Actor's address

-> msg res

Message to send

-> Actor _msg res

Response

Send a message to another actor, and wait for a response.

Since: 0.4.0.0

getSelf :: Actor msg (Address msg) Source #

Return the current actor's address.

Since: 0.4.0.0

Receiving messages

receive Source #

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

tryReceive Source #

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

Not receiving messages

type Actor_ = Actor NoMsg Source #

Since: 0.4.0.0

data NoMsg res Source #

Message type used by actors which do not receive messages.

Since: 0.4.0.0

spawn_ :: Actor_ () -> Actor msg () Source #

More efficient version of spawn, for actors which receive no messages (msg ~ NoMsg). See docs for spawn for more information.

Since: 0.4.0.0

runActor_ :: MonadIO m => Actor_ a -> m a Source #

More efficient version of runActor, for actors which receive no messages (msg ~ NoMsg). See docs for runActor for more information.

Since: 0.4.0.0