[Haskell-cafe] 3rd party widgets with qtHaskell (Marble)

Alp Mestanogullari alp at mestan.fr
Wed Mar 10 05:22:28 EST 2010


This something you are afaik able to do.

I'm cc'ing David (qthaskell's author).

On Wed, Mar 10, 2010 at 1:59 AM, Philip Beadling <
phil.beadling at googlemail.com> wrote:

> Hi,
>
> I know this isn't a qtHaskell list, but I don't think there is one.
>
> Was wondering if anyone has any ideas on the below.
>
> Basically I'm trying to control a Marble (Map software) Qt widget from
> qtHaskell.
>
> So I've mocked up a very simple user interface in Qt Designer (1 form, 1
> Marble widget).
>
> I can load this up and display it fine in Haskell, but as soon as I try
> to interrogate the widget I get a seg fault (eg qObjectProperty)
>
> My guess is that the call to findChild, although it executes OK it is
> not producing a valid QObject - probably casting to
> Marble::MarbleWidget* it crux of the problem.
>
> I can get this working using standard Qt Widgets (just like the examples
> show from qtHaskell), so I know the method is sound - although calling
> 3rd party widgets like this may be ambitious or impossible.
>
> I recognise this is a fairly broad query!  Has anyone tried anything
> similar?  Is it even possible to do this in qtHaskell as I'm proposing?
>
> I'm a Qt novice, so it may well be that I've misunderstood qtHaskell.
>
>
> Cheers,
>
> Phil.
>
>
> Using:
> GHC 6.12.1 / QT4.5 / Marble 0.8 / Ubuntu 9.04
>
>
>
> module Main where
>
> import Qtc
>
> main :: IO ()
> main
>  = do
>    app <- qApplication  ()
>    rok <- registerResource "marble.rcc"
>    loader <- qUiLoader ()
>    uiFile <- qFile ":/marble.ui"
>    open uiFile fReadOnly
>    ui <- load loader uiFile
>    close uiFile ()
>
>    ui_map <- findChild ui ("<Marble::MarbleWidget*>", "MarbleWidget")
>    sc <- qObjectProperty ui_map "showCompass"
>
>    qshow ui ()
>    ok <- qApplicationExec ()
>    return ()
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Alp Mestanogullari
http://alpmestan.wordpress.com/
http://alp.developpez.com/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100310/717d522b/attachment.html


More information about the Haskell-Cafe mailing list