i encounter a problem possibly related to a problem reported earlier by Mads 
in 2007 (segmentation fault):
when i change the list box items within the event handler, the event handler 
is called immediately (i.e. inside itself, recursively). it seems that the 
event is still active in the queue at this moment; i think it should be 
cleared upon entry (not on exit) of the event handler.

any comments? 
what is the best work-around?

andrew


the following program demonstrates the error:
    

module Main where   -- OnCommandTest where

{- test for on command jumping too often
-}

import Graphics.UI.WX


main = start $ 
    do
        w <- frame [text := 
                "test on command event processing"]
        f <- panel w [] 
        listVar <- varCreate (["aa"]:: [String])
        
        doButton <- button f [text :=  "do"]
        quitButton <- button f [text := "Quit",
                                on command := close w]
        aEn <- textEntry f [text := "aEn"]
        bEn <- singleListBox f [items := ["123456789012345678901234567890"] ]   
     

        set aEn [on enterKey := dox bEn listVar]
        set bEn [on select ::= dox2 bEn] 

        set doButton [on command := dox bEn listVar]
 
        let lay = fill $
                   column 5  
                            [ row 5 [label "buttons" 
                                    , widget doButton
                                    , widget quitButton
                                    ]
                            , row 5 [label "text entry", hfill $ widget aEn]
                            , hfill $ widget bEn
                            ]
              
        set w [ layout :=  minsize (sz 300 300) $ 
                            container f lay
              ]              
        return ()
        
dox bEn listVar = do
    putStrLn "dox start"
    l <- varGet listVar
    let l2 = l ++ ["bb"]
    set bEn [items := l2]
    varSet listVar l2
    repaint bEn
    putStrLn "dox end"

dox2 bEn w = do
    putStrLn "dox2 start"
    i <- get w selection
    set bEn [items := ["xx"]]
    putStrLn $ "selection " ++ show i
    putStrLn "dox2 end"


------------------------------------------------------------------------------
Crystal Reports - New Free Runtime and 30 Day Trial
Check out the new simplified licensing option that enables unlimited
royalty-free distribution of the report engine for externally facing 
server and web deployment.
http://p.sf.net/sfu/businessobjects
_______________________________________________
wxhaskell-users mailing list
wxhaskell-users@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/wxhaskell-users

Reply via email to