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

2010-03-11 Thread Philip Beadling
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 ("", "marbleWidget")
ui_button <- findChild ui ("", "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 ()


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-10 Thread Alp Mestanogullari
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.beadl...@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 ("", "MarbleWidget")
>sc <- qObjectProperty ui_map "showCompass"
>
>qshow ui ()
>ok <- qApplicationExec ()
>return ()
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Alp Mestanogullari
http://alpmestan.wordpress.com/
http://alp.developpez.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-09 Thread Philip Beadling
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 ("", "MarbleWidget")  
sc <- qObjectProperty ui_map "showCompass"

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



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe