[Haskell-cafe] Cleaner way to write code and handle errors?

John Ky newhoggy at gmail.com
Tue Jun 28 10:08:44 CEST 2011


Hi all,

I'm practising my Haskell by writing a simple TCP echo server and finding
that getting my program control to be succinct is rather tricky.  In
particular, I have return () everywhere, my error handling is verbose and
I'm not entirely sure my recursion is the cleanest way syntactically to get
my loops going and terminating.

I must be doing something obviously un-Haskell-like.

Any suggestions on how I can improve my code?  Code below.

Cheers,

-John

import Control.Concurrent
import Control.Exception
import Control.Monad
import Network
import System.IO
import System.IO.Error (isEOFError)

main = withSocketsDo $ do
  sListen <- listenOn (PortNumber 8000)
  putStrLn "Listening on Port 8000"
  forkIO $ forever $ do
    (sSession, hostname, port) <- accept sListen
    putStrLn ("Connected to " ++ hostname ++ ":" ++ (show port))
    let processLine = forkIO $ do
        lineResult <- try (hGetLine sSession)
        case lineResult of
          Right line -> do
            putStrLn line
            processLine
            return ()
          Left e ->
            if isEOFError e
                then putStrLn (show e)
                else do
                  ioError e
                  return ()
        return ()
    processLine
    return()
  line <- getLine
  return ()
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110628/4dc03d26/attachment.htm>


More information about the Haskell-Cafe mailing list