This tutorial is designed as a practical guide to writing real worldcode inHaskell and hopes to intuitively motivateand introduce some of the advanced features of Haskell to the noviceprogrammer. Our goal is to write a concise, robust and elegantIRC bot in Haskell.
A packaged-up version of the code isavailable on GitHub.
You'll need a reasonably recent version ofGHC. Our first step is to get on thenetwork. So let's start by importing modules from the standard library and thenetwork package, and defining a server to connect to.
-- File 1.hsimport System.IO -- baseimport qualified Network.Socket as N -- network-- Configuration optionsmyServer = "irc.libera.chat" :: StringmyPort = 6667 :: N.PortNumber-- Toplevel programmain :: IO ()main = do h <- connectTo myServer myPort t <- hGetContents h hSetBuffering stdout NoBuffering print t-- Connect to a server given its name and port numberconnectTo :: N.HostName -> N.PortNumber -> IO HandleconnectTo host port = do addr : _ <- N.getAddrInfo Nothing (Just host) (Just (show port)) sock <- N.socket (N.addrFamily addr) (N.addrSocketType addr) (N.addrProtocol addr) N.connect sock (N.addrAddress addr) N.socketToHandle sock ReadWriteMode
The key here is themain
function. This is the entry point to a Haskell program. We first connect to the server and get a socketh
(wrapped as aHandle
). We can then read and print any data we receive. We disable buffering (hSetBuffering
) on standard output, asprint
renders strings on a single line, with newline characters escaped.
Put this code in the module1.hs
and we can then run it. Use whichever system you like:
Using runhaskell:
$ runhaskell 1.hs "NOTICE AUTH :*** Looking up your hostname...\r\nNOTICE AUTH :*** Checking ident\r\nNOTICE AUTH :*** Found your hostname\r\n ...
Or we can just compile it to an executable with GHC:
$ ghc --make 1.hs -o tutbot Chasing modules from: 1.hs Compiling Main ( 1.hs, 1.o ) Linking ... $ ./tutbot "NOTICE AUTH :*** Looking up your hostname...\r\nNOTICE AUTH :*** Checking ident\r\nNOTICE AUTH :*** Found your hostname\r\n ...
Or using GHCi:
$ ghci 1.hs *Main> main "NOTICE AUTH :*** Looking up your hostname...\r\nNOTICE AUTH :*** Checking ident\r\nNOTICE AUTH :*** Found your hostname\r\n ...
Great! We're on the network.
Now we're listening to the server, we better start sending some information back. Three details are important: the nick, the user name, and a channel to join. So let's send those.
-- File 2.hsimport System.IO -- baseimport qualified Network.Socket as N -- network-- Configuration optionsmyServer = "irc.libera.chat" :: StringmyPort = 6667 :: N.PortNumbermyChan = "#tutbot-testing" :: StringmyNick = "tutbot" :: String-- Toplevel programmain :: IO ()main = do h <- connectTo myServer myPort write h "NICK" myNick write h "USER" (myNick ++ " 0 * :tutorial bot") write h "JOIN" myChan listen h-- Connect to a server given its name and port numberconnectTo :: N.HostName -> N.PortNumber -> IO HandleconnectTo host port = do addr : _ <- N.getAddrInfo Nothing (Just host) (Just (show port)) sock <- N.socket (N.addrFamily addr) (N.addrSocketType addr) (N.addrProtocol addr) N.connect sock (N.addrAddress addr) N.socketToHandle sock ReadWriteMode-- Send a message to a handlewrite :: Handle -> String -> String -> IO ()write h cmd args = do let msg = cmd ++ " " ++ args ++ "\r\n" hPutStr h msg -- Send message on the wire putStr ("> " ++ msg) -- Show sent message on the command line-- Process each line from the serverlisten :: Handle -> IO ()listen h = forever $ do line <- hGetLine h putStrLn line where forever :: IO () -> IO () forever a = do a; forever a
Now, we've done quite a few things here. Firstly, we set up a channel name and bot nickname. Themain
function has been extended to send messages back to the IRC server using awrite
function. Let's look at that a bit more closely:
-- Send a message to a handlewrite :: Handle -> String -> String -> IO ()write h cmd args = do let msg = cmd ++ " " ++ args ++ "\r\n" hPutStr h msg -- Send message on the wire putStr ("> " ++ msg) -- Show sent message on the command line
Thewrite
function takes 3 arguments; a handle (our socket), and then two strings representing an IRC protocol action, and any arguments it takes.write
then builds an IRC message by concatenating strings and write it over the wire to the server. For debugging purposes we also print to standard output the message we send.
Our second function,listen
, is as follows:
-- Process each line from the serverlisten :: Handle -> IO ()listen h = forever $ do line <- hGetLine h putStrLn line where forever :: IO () -> IO () forever a = do a; forever a
This function takes aHandle
argument, and sits in an infinite loop reading lines of text from the network and printing them. We take advantage of two powerful features; lazy evaluation and higher order functions to roll our own loop control structure,forever
, as a normal function!forever
takes a chunk of code as an argument, evaluates it and recurses - an infinite loop function. It is very common to roll our own control structures in Haskell this way, using higher order functions. No need to add new syntax to the language, lisp-like macros or meta programming - you just write a normal function to implement whatever control flow you wish. We can also avoiddo
-notation, and directly write:forever a = a >> forever a
. Note thatforever
can also be found in the standard librarybase, in the moduleControl.Monad
(with a more general type).
Let's run this thing:
$ runhaskell 2.hs> NICK tutbot> USER tutbot 0 * :tutorial bot> JOIN #tutbot-testingNOTICE AUTH :*** Looking up your hostname...NOTICE AUTH :*** Found your hostname, welcome backNOTICE AUTH :*** Checking identNOTICE AUTH :*** No identd (auth) response:copper.libera.chat NOTICE * :*** Checking Ident:copper.libera.chat NOTICE * :*** Looking up your hostname......:tutbot MODE tutbot :+iw:tutbot!~tutbot@aa.bb.cc.dd JOIN :#tutbot-testing:copper.libera.chat 353 tutbot @ #tutbot-testing :tutbot @dons:copper.libera.chat 366 tutbot #tutbot-testing :End of /NAMES list.
And we're in business! From an IRC client, we can watch the bot connect:
15:02 -- tutbot [n=tutbot@aa.bb.cc.dd] has joined #tutbot-testing 15:02 dons> hello
And the bot logs to standard output:
:dons!i=dons@my.net PRIVMSG #tutbot-testing :hello
We can now implement some commands.
Add these additional imports before changing thelisten
function.
import Data.Listimport System.Exit
-- Connect to a server given its name and port numberlisten :: Handle -> IO ()listen h = forever $ do line <- hGetLine h putStrLn line let s = init line if isPing s then pong s else eval h (clean s) where forever :: IO () -> IO () forever a = do a; forever a clean :: String -> String clean = drop 1 . dropWhile (/= ':') . drop 1 isPing :: String -> Bool isPing x = "PING :" `isPrefixOf` x pong :: String -> IO () pong x = write h "PONG" (':' : drop 6 x)
We add 3 features to the bot here by modifyinglisten
.Firstly, it responds toPING
messages:if ping s then pong s ...
.This is useful for servers that require pings to keep clients connected.Before we can process a command, remember the IRC protocol generatesinput lines of the form:
:dons!i=dons@my.net PRIVMSG #tutbot-testing :!id foo
so we need aclean
function to simply drop the leading ':' character, and then everything up to the next ':', leaving just the actual command content. We then pass this cleaned up string toeval
, which dispatches bot commands.
-- Dispatch a commandeval :: Handle -> String -> IO ()eval h "!quit" = write h "QUIT" ":Exiting" >> exitSuccesseval h x | "!id " `isPrefixOf` x = privmsg h (drop 4 x)eval _ _ = return () -- ignore everything else
So, if the single string"!quit"
is received, we inform the server and exit the program. If a string beginning with"!id "
appears, we echo any argument string back to the server (the command is named after the identity functionid
, which just returns its argument). Finally, if no other matches occur, we do nothing.
We add theprivmsg
function - a useful wrapper overwrite
for sendingPRIVMSG
lines to the server.
-- Send a privmsg to the channelprivmsg :: Handle -> String -> IO ()privmsg h s = write h "PRIVMSG" (chan ++ " :" ++ s)
Here's a transcript from our minimal bot running in channel:
15:12 -- tutbot [n=tutbot@aa.bb.cc.dd] has joined #tutbot-testing 15:13 dons> !id hello, world! 15:13 tutbot> hello, world! 15:13 dons> !id very pleased to meet you. 15:13 tutbot> very pleased to meet you. 15:13 dons> !quit 15:13 -- tutbot [n=tutbot@aa.bb.cc.dd] has quit [Client Quit]
Now, before we go further, let's refactor the code a bit.
A small annoyance so far has been that we've had to thread around our socket to every function that needs to talk to the network. The socket is essentiallyimmutable state, that could be treated as a global read only value in other languages. In Haskell, we can implement such a structure using areader monad. Monads are a very powerful abstraction, and we'll only touch on them here. The interested reader is referred toAll About Monads. We'll be using a custom monad specifically to implement a read-only global state for our bot.
The key requirement is that we wish to be able to perform IO actions, as well as thread a small state value transparently through the program. As this is Haskell, we can take the extra step of partitioning our stateful code from all other program code, using a new type.
So let's define a small reader monad:
-- The 'Net' monad, a wrapper over IO, carrying the bot's immutable state.data Bot = Bot { botSocket :: Handle }type Net = ReaderT Bot IO
Firstly, we define a data type for the global state. In this case, it is theBot
type, a simple struct storing our network socket. We then layer this data type over our existing IO code, with amonad transformer. This isn't as scary as it sounds and the effect is that we can treat the socket as a global read-only value anywhere we need it. We'll call this new IO + state structure theNet
monad.ReaderT
is atype constructor, essentially a type function, that takes 2 types as arguments, building a result type: theNet
monad type.
We can now throw out all that socket threading and grab the socket when we need it. The key steps are connecting to the server, followed by the initialisation of our new reader monad and then to run the main bot loop with that global value. We add a small function, which takes the intial bot state and evaluates the bot'srun
loop "in" the Net monad, using the Reader monad'srunReaderT
function:
loop st = runReaderT run st
whererun
is a small function to register the bot's nick, join a channel, and start listening for commands.
While we're here, we can tidy up the main function a little by usingControl.Exception.bracket
to explicitly delimit the connection, shutdown and main loop phases of the program - a useful technique.
-- Toplevel programmain :: IO ()main = bracket connect disconnect loop where disconnect = hClose . socket loop st = runReaderT run st
That is, the higher order functionbracket
takes 3 arguments: a function to connect to the server, a function to disconnect and a main loop to run in between. We can usebracket
whenever we wish to run some code before and after a particular action - likeforever
, this is another control structure implemented as a normal Haskell function.
Rather than threading the socket around, we can now simply ask for it when needed. Note that the type ofwrite
changes - it is in theNet
monad, which tells us that the bot must already by connected to a server (and thus it is ok to use the socket, as it is initialised).
-- Send a message out to the server we're currently connected towrite :: String -> String -> Net ()write cmd args = do h <- asks botSocket let msg = cmd ++ " " ++ args ++ "\r\n" liftIO $ hPutStr h msg -- Send message on the wire liftIO $ putStr ("> " ++ msg) -- Show sent message on the command line
In order to use both state and IO, we use theliftIO
function tolift an IO expression into theNet
monad making that IO function available to code in theNet
monad.
-- Imported from Control.Monad.IO.ClassliftIO :: IO a -> Net a
The monadic, stateful, exception-handling bot in all its glory:
-- File 4.hsimport Control.Exception -- baseimport Control.Monad.IO.Class --import Data.List --import System.Exit --import System.IO --import qualified Network.Socket as N -- networkimport Control.Monad.Trans.Reader -- transformers-- Configuration optionsmyServer = "irc.libera.chat" :: StringmyPort = 6667 :: N.PortNumbermyChan = "#tutbot-testing" :: StringmyNick = "tutbot" :: String-- Set up actions to run on start and end, and run the main loopmain :: IO ()main = bracket connect disconnect loop where disconnect = hClose . botSocket loop st = runReaderT run st-- The 'Net' monad, a wrapper over IO, carrying the bot's immutable state.data Bot = Bot { botSocket :: Handle }type Net = ReaderT Bot IO-- Connect to the server and return the initial bot stateconnect :: IO Botconnect = notify $ do h <- connectTo myServer myPort return (Bot h) where notify a = bracket_ (putStrLn ("Connecting to " ++ myServer ++ " ...") >> hFlush stdout) (putStrLn "done.") a-- Connect to the server and return a Handle (helper for connect)connectTo :: N.HostName -> N.PortNumber -> IO HandleconnectTo host port = do addr : _ <- N.getAddrInfo Nothing (Just host) (Just (show port)) sock <- N.socket (N.addrFamily addr) (N.addrSocketType addr) (N.addrProtocol addr) N.connect sock (N.addrAddress addr) N.socketToHandle sock ReadWriteMode-- We're in the Net monad now, so we've connected successfully-- Join a channel, and start processing commandsrun :: Net ()run = do write "NICK" myNick write "USER" (myNick ++ " 0 * :tutorial bot") write "JOIN" myChan listen-- Send a message to the server we're currently connected towrite :: String -> String -> Net ()write cmd args = do h <- asks botSocket let msg = cmd ++ " " ++ args ++ "\r\n" liftIO $ hPutStr h msg -- Send message on the wire liftIO $ putStr ("> " ++ msg) -- Show sent message on the command line-- Process each line from the serverlisten :: Net ()listen = forever $ do h <- asks botSocket line <- liftIO $ hGetLine h liftIO (putStrLn line) let s = init line if isPing s then pong s else eval (clean s) where forever :: Net () -> Net () forever a = do a; forever a clean :: String -> String clean = drop 1 . dropWhile (/= ':') . drop 1 isPing :: String -> Bool isPing x = "PING :" `isPrefixOf` x pong :: String -> Net () pong x = write "PONG" (':' : drop 6 x)-- Dispatch a commandeval :: String -> Net ()eval "!quit" = write "QUIT" ":Exiting" >> liftIO exitSuccesseval x | "!id " `isPrefixOf` x = privmsg (drop 4 x)eval _ = return () -- ignore everything else-- Send a privmsg to the current chan + serverprivmsg :: String -> Net ()privmsg msg = write "PRIVMSG" (myChan ++ " :" ++ msg)
Note that we threw in a new control structure,notify
, for fun. Now we're almost done! Let's run this bot. Using runhaskell:
$ runhaskell 4.hs
or using GHC:
$ ghc --make 4.hs -o tutbot Chasing modules from: 4.hs Compiling Main ( 4.hs, 4.o ) Linking ... $ ./tutbot
And from an IRC client we can watch it connect:
15:26 -- tutbot [n=tutbot@aa.bb.cc.dd] has joined #tutbot-testing 15:28 dons> !id all good? 15:28 tutbot> all good? 15:28 dons> !quit 15:28 -- tutbot [n=tutbot@aa.bb.cc.dd] has quit [Client Quit]
So we now have a bot with explicit read-only monadic state, error handling, and some basic IRC operations. If we wished to add read-write state, we need only change theReaderT
transformer toStateT
.
Let's implement a basic new command: uptime tracking. Conceptually, we need to remember the time the bot starts. Then, if a user requests, we work out the total running time and print it as a string. A nice way to do this is to extend the bot's state with a start time field:
import Data.Time
-- Updated Bot typedata Bot = Bot { botSocket :: Handle, startTime :: UTCTime }
We can then modify the initialconnect
function to also set the start time.
-- Connect to the server and return the initial bot stateconnect :: IO Botconnect = notify $ do t <- getCurrentTime h <- connectTo myServer myPort return (Bot h t)
We then add a new case to theeval
function, to handle uptime requests:
eval "!uptime" = uptime >>= privmsgeval ...
This will run theuptime
function and send it back to the server.uptime
itself is:
-- Get the current uptimeuptime :: Net Stringuptime = do now <- liftIO getCurrentTime zero <- asks startTime return (pretty (diffUTCTime now zero))
That is, in theNet
monad, find the current time and the start time, and then calculate the difference, returning that number as a string. Rather than use the normal representation for dates, we'll write our own custom formatter for dates:
-- Pretty print the date in '1d 9h 9m 17s' formatpretty :: NominalDiffTime -> Stringpretty diff = unwords . map (\(t, unit) -> show t ++ unit) $ if null diffs then [(0, "s")] else diffs where diffs :: [(Integer, String)] diffs = filter ((/= 0) . fst) $ decompose [(86400, "d"), (3600, "h"), (60, "m"), (1, "s")] (floor diff) decompose [] _ = [] decompose ((secs, unit) : metrics) t = let (n, t') = t `divMod` secs in (n, unit) : decompose metrics t'
And that's it. Running the bot with this new command:
16:03 -- tutbot [n=tutbot@aa.bb.cc.dd] has joined #tutbot-testing 16:03 dons> !uptime 16:03 tutbot> 51s 16:03 dons> !uptime 16:03 tutbot> 1m 1s 16:12 dons> !uptime 16:12 tutbot> 9m 46s
This is just a flavour of application programming in Haskell, and onlyhints at the power of Haskell's lazy evaluation, static typing, monadiceffects and higher order functions. There is much, much more to be saidon these topics. Some places to start:
Or take the bot home and hack! Some suggestions:
forkIO
to add a command line interface, and you've got yourself an irc client with 4 more lines of code.Author: Don Stewart