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

Philip Beadling phil.beadling at googlemail.com
Thu Mar 11 20:13:07 EST 2010


On Wed, 2010-03-10 at 11:22 +0100, Alp Mestanogullari wrote:
> This something you are afaik able to do. 
> 
> 
> I'm cc'ing David (qthaskell's author).
> 

Thanks for the reply.  I've worked it out.

The below code demonstrates getting and setting a property from a marble
widget.

I'm a little surprised it worked.  If my C++ is right what I've done
here is dynamically cast the Marble widget as it's Qt parent.

This of course is fine, but given that longitude() is not a virtual
function on the parent, I'd to have to cast as the child to access this
function - my code shouldn't have scope of Marble specific functions.

This doesn't follow C++ (or I need to brush up on my OO programming!).

I can live with this, after all I'm not writing a C++ program, but if
anyone can explain this I'd be interested to understand why.

One other peculiarity I noticed was that the qVariant "constructor" will
only take Double or Integer types if they are nested in a tuple.  Again,
this is fine, but at odds with the documentation which implies
constructors can take:

() | p1 | (p1) | (p1,p2,...pn)


So I'm over the first hurdle; it is possible, now to think of something
interesting to do with it :-)



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 ("<QWidget*>", "marbleWidget")
    ui_button <- findChild ui ("<QPushButton*>", "pushButton")  
    
    sc <- qObjectProperty ui_map "longitude"
    bt <- qObjectProperty ui_button "text"

    long <- qVariantValue_Double sc

    print long

    x <- qVariant (-1::Double)
    blah <- qObjectSetProperty ui_map "longitude" x
  

    qshow ui ()
    ok <- qApplicationExec ()
    return ()




More information about the Haskell-Cafe mailing list