Yogurt-0.2: A MUD client librarySource codeContentsIndex
Network.Yogurt.Mud
Contents
Types
Hooks
Hook record fields
Match information
Variables
Timers
Timer record fields
Triggering hooks
IO
Description
The core of Yogurt, consisting of the Mud monad and all functions manipulating this monad.
Synopsis
type Mud = State MudState
data MudState
emptyMud :: MudState
data Hook
data Destination
= Local
| Remote
type Pattern = String
data Timer
type Interval = Int
data Result
= Send Destination String
| forall a . RunIO (IO a) (a -> Mud ())
| NewTimer Timer
mkHook :: Destination -> Pattern -> Mud a -> Mud Hook
mkPrioHook :: Int -> Destination -> Pattern -> Mud a -> Mud Hook
setHook :: Hook -> Mud ()
rmHook :: Hook -> Mud ()
allHooks :: Mud [Hook]
hPriority :: Hook -> Int
hDestination :: Hook -> Destination
hPattern :: Hook -> Pattern
hAction :: Hook -> Mud ()
triggeredHook :: Mud Hook
matchedLine :: Mud String
before :: Mud String
group :: Int -> Mud String
after :: Mud String
mkVar :: a -> Mud (Var a)
setVar :: Var a -> a -> Mud ()
readVar :: Var a -> Mud a
modifyVar :: Var a -> (a -> a) -> Mud ()
mkTimer :: Interval -> Mud a -> Mud Timer
rmTimer :: Timer -> Mud ()
existsTimer :: Timer -> Mud Bool
allTimers :: Mud [Timer]
tAction :: Timer -> Mud ()
tInterval :: Timer -> Interval
trigger :: Destination -> String -> Mud ()
triggerJust :: (Hook -> Bool) -> Destination -> String -> Mud ()
io :: Destination -> String -> Mud ()
flushResults :: Mud [Result]
withIO :: IO a -> (a -> Mud ()) -> Mud ()
runIO :: IO a -> Mud ()
Types
type Mud = State MudStateSource
The Mud monad is a simple state monad.
data MudState Source
State internal to the Mud monad.
emptyMud :: MudStateSource
The initial state of the Mud monad.
data Hook Source
The abstract Hook type. Two hooks are considered equal if they were created (using mkHook) at the same time. Hook h1 < hook h2 if h1 will match earlier than h2.
show/hide Instances
data Destination Source
Used to distinguish between messages going in different directions.
Constructors
LocalThe message is headed towards the user's terminal.
RemoteThe message is headed towards the remote MUD server.
show/hide Instances
type Pattern = StringSource
A Pattern is a regular expression.
data Timer Source
The abstract Timer type.
type Interval = IntSource
Interval in milliseconds.
data Result Source
A Result is a consequence of executing a Mud program.
Constructors
Send Destination String
forall a . RunIO (IO a) (a -> Mud ())
NewTimer Timer
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 should 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.
Timers
mkTimer :: Interval -> Mud a -> Mud TimerSource
mkTimer interval prog creates a timer that executes prog every interval milliseconds.
rmTimer :: Timer -> Mud ()Source
Disables the timer.
existsTimer :: Timer -> Mud BoolSource
Checks whether a timer is active.
allTimers :: Mud [Timer]Source
Yields all currently active timers.
Timer record fields
tAction :: Timer -> Mud ()Source
Yields the timer's action.
tInterval :: Timer -> IntervalSource
Yields the timer's interval.
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.
flushResults :: Mud [Result]Source
Yields all accumulated results and removes them from the state. Used by Network.Yogurt.Engine in runMud.
IO
withIO :: IO a -> (a -> Mud ()) -> Mud ()Source
Executes the IO action soon. The computation's result is passed to the function, and the resulting Mud computation is executed.
runIO :: IO a -> Mud ()Source
Invokes withIO, discarding the IO's result.
Produced by Haddock version 2.3.0