Yogurt-0.4.1: A MUD client library

Network.Yogurt.Mud

Contents

Description

The core of Yogurt, consisting of the Mud monad and all functions manipulating this monad.

Synopsis

Types

type Mud = StateT MudState IOSource

The Mud monad is a state monad over IO.

data MudState Source

State internal to the Mud monad.

type RunMud = forall a. Mud a -> IO aSource

Run a Mud computation in IO. A common implementation of this function is runMud vState.

type Output = Destination -> String -> IO ()Source

Provides a way to output messages.

data Hook Source

The abstract Hook type. For every pair of hooks (h1, h2):

  • h1 == h2 iff they were created by the same call to mkHook.
  • h1 < h2 iff h1 will match earlier than h2.

Instances

data Destination Source

The direction in which a message is going.

Constructors

Local

The message is headed towards the user's terminal.

Remote

The message is headed towards the remote MUD server.

type Pattern = StringSource

A Pattern is a regular expression.

data Var a Source

Variables hold updatable, typed data.

Running Mud computations

emptyMud :: RunMud -> Output -> MudStateSource

The initial state of the Mud monad. The RunMud argument is stored in the state to make forkWithCallback possible; the Output argument is used by Mud computations for messages leaving the engine.

runMud :: MVar MudState -> RunMudSource

Runs a Mud computation, executes the results (such as sending messages to the screen or the MUD) and returns the computation's result. The MVar is updated.

Hooks

A hook watches a channel for messages matching a specific regular expression. When a hook fires, the triggering message is consumed and the hook's action is executed. When a message doesn't trigger any hooks, it is sent on to its destination. A hook's action may query for match-specific data; see section Match information. At most one hook fires for each message, unless the hook's action explicitly sends the message through trigger again. If several hooks match, only the hook with the highest priority fires. If there is still a tie, the hook that was defined last (using mkHook) fires.

mkHook :: Destination -> Pattern -> Mud a -> Mud HookSource

Calls mkPrioHook with priority 0.

mkPrioHook :: Int -> Destination -> Pattern -> Mud a -> Mud HookSource

Creates and installs a hook that watches messages headed to the specified destination and match the specified pattern.

setHook :: Hook -> Mud ()Source

Saves a changed hook, or reactivates it.

rmHook :: Hook -> Mud ()Source

Disables a hook.

allHooks :: Mud [Hook]Source

Yields all current hooks in preferred firing order.

Hook record fields

Use these in combination with setHook to update hooks.

hPriority :: Hook -> IntSource

Yields the hook's priority.

hDestination :: Hook -> DestinationSource

Yields the destination this hook watches.

hPattern :: Hook -> PatternSource

Yields the pattern messages must have for this hook to fire.

hAction :: Hook -> Mud ()Source

Yields the Mud program to execute when the hook fires.

Match information

Functions for querying the currently firing hook. These functions can only be called from within a hook's body.

triggeredHook :: Mud HookSource

Yields the hook that is currently firing.

matchedLine :: Mud StringSource

Yields the message that triggered the currently firing hook.

before :: Mud StringSource

Yields the part of the triggering message that comes before the matched pattern.

group :: Int -> Mud StringSource

Yields the regex group from the matched pattern. group 0 yields the complete match; higher indices correspond to the parenthesized groups.

after :: Mud StringSource

Yields the part of the triggering message that comes after the matched pattern.

Variables

mkVar :: a -> Mud (Var a)Source

Creates a variable with an initial value.

setVar :: Var a -> a -> Mud ()Source

Updates a variable to a new value.

readVar :: Var a -> Mud aSource

Yields the variable's current value.

modifyVar :: Var a -> (a -> a) -> Mud ()Source

Updates the variable using the update function.

Triggering hooks

trigger :: Destination -> String -> Mud ()Source

Short for triggerJust (const True).

triggerJust :: (Hook -> Bool) -> Destination -> String -> Mud ()Source

If the message triggers a hook that passes the specified test, it is fired. Otherwise, the message is passed on to the destination using io.

io :: Destination -> String -> Mud ()Source

Immediately write a message to a destination, without triggering hooks.

Multi-threading

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

forkWithCallback :: (RunMud -> IO ()) -> Mud ThreadIdSource

Used when you want a forked thread to be able to call back into the Mud monad. Note that when using the RunMud argument, the forked thread will have to contend with the threads for the user input and MUD input, because only one Mud computation can run at any given time. The id of the forked thread is returned.