My piece of an IRC bot

Today I started on a simple IRC bot framework thingy. I decided to post the source code here so people can look at it and tell me what the heck I did wrong :-P
module IRC where
import Control.Monad.State import System.IO import Network
{----------------------}{------------------------------------------------------}
data IRCMessage = IRCMessage (Maybe String) String [String]
type IRCBot a = IRCMessage -> State a [IRCMessage] type IRCConnection a = IRCBot a -> IO ()
ircConnect :: String -> Integer -> a -> IRCConnection a
ircConnect server port state bot = withSocketsDo (do connection <- connectTo server (PortNumber (fromInteger port)) ircLoop connection state bot)
ircLoop connection state bot = do eof <- hIsEOF connection if eof then hWaitForInput connection 500 >> return () else do message <- hGetLine connection hPutStr connection (fst (runState (bot (ircParseMessage message)) state) >>= decodeMessage) ircLoop connection (snd (runState (bot (ircParseMessage message)) state)) bot
-- Oh noes. Let's hope we'll never, ever have to read that ;-)
{-End I/O capable code-}{------------------------------------------------------}
ircParseMessage x = let rx = filter (/='\r') x (p:u:us) = words rx in if (head p) == ':' then IRCMessage (Just p) u (ircParseParams us) else IRCMessage Nothing p (ircParseParams (u:us))
ircParseParams (x:xs) = if head x == ':' then [unwords (x:xs)] else x : ircParseParams xs
decodeMessage (IRCMessage Nothing command params)= (command ++ ' ' : unwords (init params) ++ ' ' : (':' : last params))
decodeMessage (IRCMessage (Just prefix) command params)= ((':' : prefix) ++ ' ' : command ++ ' ' : unwords (init params) ++ (':' : last params))
{-Thus ends the IRCbot-}{------------------------------------------------------}
The very simple bot I've been trying to run with it:
module Main where
import IRC import Control.Monad.State
{----------------------}{------------------------------------------------------}
main = ircConnect "brown.freenode.net" 6667 False bot
bot _ = State (\x -> if x then ([],True) else ( [IRCMessage Nothing "NICK" ["EagleBot"], IRCMessage Nothing "USER" ["EagleBot", "Null", "Null", "EagleBot"], IRCMessage Nothing "PRIVMSG" ["NickServ", "IDENTIFY censored"], IRCMessage Nothing "JOIN" ["#esoteric"]],True))
participants (1)
-
ihope