Say, I was wondering if someone on this list would be willing to help
me track down a space leak in a program I wrote. I don't really have
enough insight into the workings of things to figure out what's causing
it, but people here have seemed helpful in the past. The space leak
occurs under GHC 4.0x; I haven't really tried it under another Haskell
system, given that I use GHC extensions. Any help would be appreciated.
Attached is the source of the program, a rudimentary chatserver that
does nothing more than relay text from one socket to all others connected.
Four-space tabstops are recommended for viewing and editing.

Thanks,
Bill
\begin{code}
module Main where
import List
import IO
import System
import Select
import SocketPrim(socketToHandle)
import Socket

main = do
        n <- getArgs
        sock <- listenOn ((PortNumber . mkPortNumber)
                                                (case n of [] -> 1666 ; (h:t) -> read 
h))
        loop sock []

loop sock ys'' =
        do
                h <- socketToHandle sock ReadWriteMode
                (xs', ys', zs') <- hSelect (h : ys'') [] [] (Just 10)
                s <- (mapM hGetLine (xs' \\ [h])) `catch` (\_ -> return [])
                t <- mapM hIsEOF (xs' \\ [h])
                let ys = ys'' \\ [x | (x,y) <- zip xs' t, y ]
                        in
                                do
                                        putStr (unlines s)
                                        mapM (\msg -> mapM ((flip hPutStrLn) msg) (ys 
\\ [h])) s
                                                `catch` (\_-> return [[()]])
                                        if h `elem` xs'
                                                then
                                                        do
                                                                (h',host) <- accept 
sock
                                                                putStrLn ("accepted a 
socket "
                                                                                       
 ++ "connection from " ++ host)
                                                                loop sock (h':ys)
                                                else
                                                        loop sock ys

\end{code}

Reply via email to