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

Drama.Internal

Description

 
Synopsis

Documentation

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

Monad supporting actor operations.

Since: 0.4.0.0

Constructors

Actor (ReaderT (ActorEnv msg) IO a) 

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 #

data ActorEnv msg Source #

Ambient context provided by the Actor monad.

Values in ActorEnv are scoped to the current actor and cannot be safely shared. Functions like spawn, receive, and getSelf use these values as implicit parameters to avoid leaking internals (and for convenience).

Since: 0.4.0.0

Constructors

ActorEnv 

Fields

  • address :: Address msg

    Current actor's address.

  • mailbox :: Mailbox msg

    Current actor's mailbox.

  • scope :: Scope

    Current actor's token used for spawning threads. Delimits the lifetime of child actors (threads).

newtype 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

Constructors

Address (InChan (Envelope msg)) 

newtype Mailbox msg Source #

Mailbox where an actor receives messages. Cannot be shared with other actors; used implicitly by receive and tryReceive.

Since: 0.4.0.0

Constructors

Mailbox (OutChan (Envelope msg)) 

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

Wrapper around higher-kinded message types.

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

Since: 0.4.0.0

Constructors

Cast :: msg () -> Envelope msg 
Call :: MVar res -> msg res -> Envelope msg 

data NoMsg res Source #

Message type used by actors which do not receive messages.

Since: 0.4.0.0

type Actor_ = Actor NoMsg Source #

Since: 0.4.0.0

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

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

wait :: Actor msg () Source #

Block until all child actors have terminated.

Since: 0.4.0.0

getSelf :: Actor msg (Address msg) Source #

Return the current actor's 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

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

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

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