[Haskell-cafe] Printing telnet stream to wx widget with conduit

Tilmann t_gass at gmx.de
Sun Oct 5 11:28:07 UTC 2014


Awesome!  It works. Thank you very much for looking into it!


Am 05.10.14 13:12, schrieb Michael Snoyman:
>
>
> On Sun, Oct 5, 2014 at 1:14 PM, Tilmann <t_gass at gmx.de 
> <mailto:t_gass at gmx.de>> wrote:
>
>     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 <http://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 ()
>
>
> I don't know anything about wxwidgets, but I *do* see a problem here. 
> You're using `allocate` to say "when this ResourceT block exits, call 
> hClose on the Socket". You then take the socket and pass it to a new 
> thread. That new thread tries to continue using that Socket, but the 
> first thread's ResourceT block exits immediately, closing the Socket. 
> You may want to instead try using resourceForkIO[1].
>
> On a separate note, your usage of mapM_ isn't necessary in this case. 
> You can make do with:
>
>     liftIO $ hSetBuffering hsock LineBuffering
>
> [1] 
> http://haddocks.fpcomplete.com/fp/7.8/20140916-162/resourcet/Control-Monad-Trans-Resource.html#v:resourceForkIO
>
>     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 at haskell.org <mailto:Haskell-Cafe at haskell.org>
>     http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141005/0f6a10da/attachment.html>


More information about the Haskell-Cafe mailing list