Yogurt

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Yogurt is a small MUD client library written in Haskell. It can be downloaded from hackage. Yogurt is a DSL embedded in Haskell. Unlike other MUD clients out there, it doesn't offer its own syntax; instead, it relies on Haskell and naturally offers all Haskell's features. This means full control over what messages are sent, variables with any valid Haskell type, no ambiguity about whether a variable is expanded at hook define time or hook trigger time, no clumsy syntax, et cetera. On the other hand, this means you do not get the ability to change the installed hooks at runtime for free.

Yogurt is best explained by an example:

{-# OPTIONS_GHC -fglasgow-exts #-}

module Main where

import Network.Yogurt
import Network.Yogurt.Utils
import Data.Char
import Control.Monad (replicateM)

main :: IO ()
main = connect "eclipse.cs.pdx.edu" 7680 newmoon

newmoon :: Mud ()
newmoon = do

  -- Automatically log in.
  mkTriggerOnce "^Enter your name:" $ do
    sendln "username"
    sendln "password"

  -- Sound bell everytime someone sends you a tell.
  mkTrigger "tells you: " (echo "\BEL")
  
  -- Send return every 5 minutes to keep connection alive.
  mkTimer 300000 (sendln "")
  
  -- Count the number of occurrences of the word "quiet".
  vQuiet <- mkVar 0
  mkTrigger "quiet" $ modifyVar vQuiet (+ 1)
  mkCommand "quiet" $ readVar vQuiet >>= echoln . show

  -- Show all currently installed hooks.
  mkCommand "lshooks" $ do
    allHooks >>= echoln . unlines . map show
  
  -- We can do fun stuff with recursive monads:
  mkCommand "go" $ mdo
    t <- mkTimerOnce 1000  (echoln "hello!" >> rmHook h)
    h <- mkCommand "stop"  (rmTimer t       >> rmHook h)

  -- Although we don't get any scripting for free, it's easy to build some.
  -- For example, use semicolons to split commands:
  mkPrioHook 10 Remote ";" $ do
    before >>= matchMoreOn  . (++ "\n")
    after  >>= matchMoreOn'

  -- Or allow runtime system commands:
  mkHook Remote "^system (.*)" (group 1 >>= system)

  -- Speedwalks: for example, 6n expands to n;n;n;n;n;n.
  mkHook Remote "^[0-9]+[neswud]$" $ do
    (n, dir) <- fmap (span isDigit) (group 0)
    replicateM (read n) (sendln dir)

  return ()