[Haskell-beginners] wxHaskell: add an external event from another thread
Tilmann
t_gass at gmx.de
Fri Jan 8 16:20:23 UTC 2016
Hi,
this post might be helpful.
http://snipplr.com/view/17538/wxhaskell-multithread--custom-event-example/
I needed something similar and came up with this. As far as I know there
is now wxhaskell internal way of doing this.
import Graphics.UI.WX
import Graphics.UI.WXCore
import Control.Concurrent
eventId :: Int
eventId = wxID_HIGHEST + 2
main :: IO ()
main = do
chan <- newChan
forkIO $ externalEventLoop chan
start $ gui chan
externalEventLoop :: Chan String -> IO ()
externalEventLoop chan = do
writeChan chan "foobar"
threadDelay $ 10 ^ 6
externalEventLoop chan
gui :: Chan String -> IO ()
gui chan = do
vCmd <- newEmptyMVar
f <- frame []
st <- textCtrl f []
forkIO $ eventLoop eventId chan vCmd f
evtHandlerOnMenuCommand f eventId $ takeMVar vCmd >>= \text ->
appendText st $ text ++ "\n"
set f [layout := fill $ minsize (Size 100 100) $ widget st]
eventLoop :: Int -> Chan String -> MVar String -> Frame () -> IO ()
eventLoop eventId chan vCmd f = do
content <- readChan chan
putMVar vCmd content
e <- commandEventCreate wxEVT_COMMAND_MENU_SELECTED eventId
evtHandlerAddPendingEvent f e
eventLoop eventId chan vCmd f
Am 07.01.16 um 22:27 schrieb Puck:
> Hello all,
>
> how is it possible to process external events, for example a
> succeeded getLine or a takeMVar with its values in the wxHaskell
> framework?
>
> The reason is, that I want to connect a erlang node to wxHaskell.
>
> I have found the functions
> Graphics.UI.WX.Events.newEvent :: String -> (w -> IO a) -> (w -> a ->
> IO ()) -> Event w a
> "Create a new event from a get and set function."
>
> Beside from, that I don't know what the get and set function shall do, I
> don't know, how I can add the new event to the event-loop of wx, and
> when it "fires".
>
> Do you know any possibilities?
>
> Thank you in advance
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
More information about the Beginners
mailing list