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

Drama.Server

Description

Higher-level process operations, allowing responses to messages. Inspired by Elixir and Erlang's generic servers (GenServer / gen_server).

Example
Expand

A server 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 -> Server (StateMsg s) ()
state s0 = do
  stateIORef <- liftIO $ newIORef s0

  forever $ receive >>= handle \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

type Server msg a = Process (Envelope msg) a Source #

Since: 0.3.0.0

data Envelope (msg :: Type -> Type) Source #

Wrapper around higher-kinded message types, to make them compatible with the lower-level Process machinery.

Higher-kinded message types are defined as GADTs with a type parameter. This allows specifying the response type for messages.

Since: 0.3.0.0

Sending messages

cast Source #

Arguments

:: Address (Envelope msg)

Process' address

-> msg ()

Message to send

-> Process _msg () 

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

Since: 0.3.0.0

call Source #

Arguments

:: HasMsg res 
=> Address (Envelope msg)

Process' address

-> msg res

Message to send

-> Process _msg res

Response

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

Since: 0.3.0.0

Handling messages

handle Source #

Arguments

:: (forall res. msg res -> Process _msg res)

Callback function that responds to messages

-> Envelope msg

Message to handle

-> Process _msg () 

Handle messages which may require a response. This is the only way to consume an Envelope.

Since: 0.3.0.0