Hi Zoran,

wxhaskell refuses to compile with GHC 8.6.5 (or a more modern version). I have not tried anything prior to 8.6.5.

The last update to https://hackage.haskell.org/package/wx was over 7 years ago. The version of wxc on hackage won't compile with Cabal >= 2.2 because of a change to the signature of rawSystemStdInOut, which is needed during the configure step for the package. That's as far as I went; there could be other issues.

If you are able to create a docker image that compiles everything inside and reproduces your error with the scrollbar, I can give it a try.

There appears to have been an attempt at reviving the project: https://sourceforge.net/p/wxhaskell/bugs/, and people at Zurihac were working on it. I don't know what happened.

Cheers,

Ivan

On Mon, 14 Oct 2024 at 09:31, Zoran Bošnjak <zoran.bosnjak@via.si> wrote:
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
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.