My Haskell/GTK4 experiments have reached ‘printing’. I have a run time problem which may be a GTK4 bug, but I am seeking to rule out the Haskell dimension first. I have a simple application which compiles with GHC 9.6.6:
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
module Main
( main
) where
import Control.Monad ( void )
import Data.GI.Base ( AttrOp (..), new, on )
import qualified GI.Gtk as Gtk
main :: IO ()
main = do
app <- new Gtk.Application
[ #applicationId := "com.pilgrem.gtk-print"
, On #activate (activate ?self)
]
void $ app.run Nothing
activate :: Gtk.Application -> IO ()
activate app = do
window <- new Gtk.ApplicationWindow
[ #application := app
, #title := "GTK4 printer example"
, #resizable := False
]
pageSetupButton <- new Gtk.Button
[ #label := "Page setup" ]
let onClickPageSetup :: IO ()
onClickPageSetup = do
printSettings <- Gtk.printSettingsNew
void $ Gtk.printRunPageSetupDialog
(Just window)
(Nothing :: Maybe Gtk.PageSetup)
printSettings
void $ on pageSetupButton #clicked onClickPageSetup
#setChild window (Just pageSetupButton)
window.show
The stack.yaml
is:
snapshot: lts-22.43 # GHC 9.6.6
extra-deps:
- gi-gdk-4.0.9
- gi-gsk-4.0.8
- gi-gtk-4.0.9
The package.yaml
is:
spec-version: 0.36.0
name: gtk-print
version: 0.1.0.0
dependencies:
- base >= 4.7 && < 5
- gi-gtk >= 4.0
- haskell-gi-base
executables:
gtk-print:
main: Main.hs
source-dirs: app
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
When the compiled executable is run, it first produces (as expected):
This is the problem, when the ‘Page setup’ button is then clicked, the application aborts with:
(gtk-print.EXE:3184): GLib-CRITICAL **: 18:07:02.332: g_utf8_to_utf16: assertion 'str != NULL' failed
Access violation in generated code when reading 0x0
Attempting to reconstruct a stack trace...
Frame Code address
* 0x9906f49f00 0x7ffd2cf29aba D:\sr\programs\x86_64-windows\msys2-20240727\mingw64\bin\libgtk-4-1.dll+0x2a9aba
* 0x9906f49f90 0x7ffd2cf2bcba D:\sr\programs\x86_64-windows\msys2-20240727\mingw64\bin\libgtk-4-1.dll+0x2abcba
* 0x9906f49f98 0x7ff7520a446d D:\Users\mike\Code\GitHub\gtk-print\.stack-work\install\170cbe04\bin\gtk-print.EXE+0x2446d
If anybody can show me a similar example which ‘works’ (on any operating system), that might help me narrow what I am experiencing.