[Haskell] Announcement: Yogurt, a MUD client library

Martijn van Steenbergen martijn at van.steenbergen.nl
Thu May 29 10:56:20 EDT 2008


Hello all,

The past weeks I've been working on Yogurt, which as far as I know is 
the first MUD client for Haskell. It's terminal-based and relies on your 
terminal for input, output and stuff like ANSI colors. It allows you to 
set up hooks that listen for specific messages, either from local to 
remote or vice versa (a generalization of aliases and triggers). 
Together with variables and timers, this should satisfy the basic 
scripting needs. It's up for download on hackage:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Yogurt

If you play any MUDs, go give Yogurt a try! I'd love to hear your 
comments, suggestions and experiences. Below is a small program which 
connects to a MUD and demonstrates some examples. Run it with runhaskell.

Kind regards,

Martijn van Steenbergen.


---


{-# OPTIONS_GHC -fglasgow-exts #-}

module Main where

import Network.Yogurt
import Network.Yogurt.Utils
import Data.Char

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.
   -- Most MUDs don't appreciate this. :-)
   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)

   -- Use semicolons to split commands:
   mkPrioHook 10 Remote ";" $ do
     before >>= matchMoreOn  . (++ "\n")
     after  >>= matchMoreOn'

   -- 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)
     sequence $ replicate (read n) (sendln dir)

   return ()


More information about the Haskell mailing list