[Haskell-beginners] recursively retrieving widgets handlers in wxhaskell

Stephen Tetley stephen.tetley at gmail.com
Mon Apr 5 09:11:00 EDT 2010


Hi Didier

I think I've simplified what you are saying to remove the dependency
on wxHaskell. Recursing a widget hierarchy to all get a list of all
widgets seems a bit strange, though demo1 does this.

Generally I'd expect you would want to recursively process the widget
hierarchy collecting some attribute of each widget - demo2 does this.

I've put the recursive functions into the IO monad to model wxHaskell
where widgets are in some monad.

code follows...


-- Model widgets as a simple binary tree - labels and interior
-- nodes both have names.
-- 
data Tree = Leaf String
          | Node Tree String Tree
  deriving (Show)

-- simulate the 'get children' on a widget -
-- the function is in the IO monad as an analogy
-- to wxHaskell being in some monad.
--
children :: Tree -> IO [Tree]
children (Leaf _)     = return []
children (Node l _ r) = return [l,r]


-- allTrees returns a list of trees -
-- the current tree (t) plus trees of all children (kids_deep)
-- Again in the IO monad to simulate wxHaskell being in some
-- monad.
--
allTrees :: Tree -> IO [Tree]
allTrees t = do
  kids      <- children t               --  [Tree]
  kids_deep <- mapM allTrees kids       -- [[Tree]]
  return (t : concat kids_deep)

tree1 = Node (Leaf "a") "top" (Node (Leaf "c") "node_b" (Leaf "d"))


demo1 = allTrees tree1


-- Simpler idiom just collecting an 'attribute' at each level
-- of the tree - here the name.
--
allNames :: Tree -> IO [String]
allNames t = case t of
  Leaf s     -> return [s]
  Node l s r -> do { ls <- allNames l
                   ; rs <- allNames r
                   ; return (s:ls ++ rs)
                   }

demo2 = allNames tree1


More information about the Beginners mailing list