Hi,
I have this little program that works 'sometimes'. It is supposed to connect to a server via telnet and print the incoming text to a wx textwidget. Usually I get an error message: ChessGui: <socket: 22>: hGetBufSome: illegal operation (handle is closed), but I acutally saw it working a few times...
The whole thing is a bit out of my Haskell-league, so I´m a bit lost now. Any help is very appreciated!
Best regards,
Tilmann
module Main where
import Control.Concurrent (forkIO, killThread)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Resource
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import qualified Data.ByteString.Char8 as BS
import Network (connectTo, PortID (..))
import System.IO
import Graphics.UI.WX
import Graphics.UI.WX.Types
import Graphics.UI.WXCore.WxcDefs
main = start gui
gui = do
f <- frame []
t <- textCtrlEx f (wxTE_MULTILINE .+. wxTE_RICH2) [font := fontFixed]
e <- entry f []
set f [layout := boxed "console" (grid 5 5 [[floatLeft $ expand $ hstretch $ widget t]
,[expand $ hstretch $ widget e]])]
telnet "freechess.org" 5000 t
telnet :: String -> Int -> TextCtrl() -> IO ()
telnet host port t = runResourceT $ do
(releaseSock, hsock) <- allocate (connectTo host $ PortNumber $ fromIntegral port) hClose
liftIO $ mapM_ (`hSetBuffering` LineBuffering) [ hsock ]
liftIO $ forkIO $ CB.sourceHandle hsock $$ (sink' t)
return ()
sink' :: TextCtrl () -> Sink BS.ByteString IO ()
sink' textCtrl = do
mstr <- await
case mstr of
Nothing -> return ()
Just str -> do
text' <- liftIO $ (get textCtrl text)
liftIO $ set textCtrl [text := text' ++ BS.unpack str ]
sink' textCtrl
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe