[Haskell-cafe] anyone using wxHaskell

Zoran BoĆĄnjak zoran.bosnjak at via.si
Mon Oct 14 16:30:45 UTC 2024


Dear haskell cafe,
I have a problem with scrolledWindow inside notebook, when running with 
the latest version of wxHaskell. See the minimal example below, where 
the scrollbar is not shown (the same sample is OK on the wxHaskell 
version from few years ago).

I would appreciate a suggestion how to make the scrollbar work again (a 
workaround if possible). I have also filed the issue on the wxHaskell 
project page. But the project does not look like being super actively 
maintained.

https://codeberg.org/wxHaskell/wxHaskell/issues/48

Minimal example:

module Main where
import Graphics.UI.WXCore
import Graphics.UI.WX

gui :: IO ()
gui = do
     f <- frame [text := "Frame"]
     p <- panel f []
     nb <- notebook p []
     p1 <- scrolledWindow nb
         [ scrollRate := sz 20 20
         ]
     texts <- mapM (\n -> staticText p1 [text := ("test" <> show n) ]) 
[1::Int ..20]
     set f
         [ layout := fill $ widget p
         , clientSize := sz 400 200
         ]
     set p
         [ layout := fill $ tabs nb
           [ tab "tab1" $ container p1 $ column 5 (fmap widget texts)
           ]
         ]

main :: IO ()
main = start gui

regards,
Zoran


More information about the Haskell-Cafe mailing list