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 (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 ()


___
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 (Marble::MarbleWidget*, 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


[Haskell-cafe] Re: Parallel foldl doesn't work correctly

2009-12-14 Thread Philip Beadling

 If you still have trouble, then try using ThreadScope
 
   http://code.haskell.org/ThreadScope/
 
 with GHC 6.12.1.  You can use ThreadScope directly from the darcs 
 repository on code.haskell.org, and we hope to do a proper release soon.
 
 Cheers,
   Simon

Thanks for the advice, just downloaded ThreadScope and it's pretty
useful (before I was using Ubuntu's System Monitor which isn't ideal).

I've moved onto 6.12 and I now have my program working nicely over 2
cores - the problem was at least in part my own design - I was
generating large thunks in my parallel version which was killing
performance.  With this solved 2 cores gives me ~50% performance
increase.

What I'm doing now is taking a list I am going to fold over and
splitting it up so I have a list of lists, where each parent list
element representing work for 1 core.  I then fold lazily and only
parallelise on the final sum operation which (as far as I can see) sends
each chunk of folds to a different core and sums the results.

Can I confirm - what you are suggesting is that although I can't
parallelise fold itself, I could force evaluation on the list I am about
to fold in parallel and then merely accumulate the result at the end --
thus most the donkey work is done in parallel?  

If this is possible, it may be more flexible then my method.  I'm lucky
as each fold operation will take give-or-take the same amount of time so
I can just chunk up fold jobs for each core equally.  If this wasn't the
case (and it certainly won't always be!), parallelising on individual
items would be the way to go.

Thanks,

Phil.


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


Re: [Haskell-cafe] Re: Parallel foldl doesn't work correctly

2009-12-13 Thread Philip Beadling
On Sat, 2009-12-12 at 13:46 +, Ben Millwood wrote:
 On Sat, Dec 12, 2009 at 10:08 AM, Maciej Piechotka
 uzytkown...@gmail.com wrote:
  If operation is associative it can be done using divide et impera
  spliting list in half and operating on it pararerlly then split in half
  etc.
 

Thank you very much for the replies.

I've come to the conclusion that, yep, you can't (directly) parallelise
of fold operation, as fold guarantees order of processing.

With something like map the runtime is free to continue sparking
function application to each element without waiting for the result.
So we spark f x, force evaluation of the remainder of the xs and
recurse.
I'm *guessing* at a detailed level when we are creating the output list,
haskell can concat each result element before f x returns due to
laziness - that is, haskell doesn't need to wait for evaluation of f x,
before continuing?

With fold, and specifically with foldl (+), this isn't the case as (+)
is strict on both arguments and thus it cannot continue until each
sparked evaluation has completed and combined with the accumulator.  If
(+) was not strict on both arguments, I'm not sure if could solider
on... assuming I've understood map correctly!?


Writing it out long hand (sorry if this is tedious!), we have:

using :: a - Strategy a - a
using x s = s x `seq` x

rwhnf :: Strategy a 
rwhnf x = x `seq` ()  

parList :: Strategy a - Strategy [a]
parList strat [] = ()
parList strat (x:xs) = strat x `par` (parList strat xs)

parMap :: Strategy b - (a - b) - [a] - [b]
parMap strat f = (`using` parList strat) . map f 


'using' applies a strategy to an item, and then returns the item.
'parList' is a (combinator) strategy which applies an atomic strategy to
each element in the list *in parallel* (for example forcing each element
to WHNF).

So for parMap we have xs passed into 'map f' - the result is then passed
to 'using' which will force application of 'f' on each element in
parallel by way of 'parList'.  No forced evaluation is dependant on a
previous evaluation.

Now for parFoldl - a crude and wrong representation for my purposes
could be:

parFoldl :: Num b = Strategy b - (a - b) - [a] - b
parFoldl strat f = sum . (`using` parList strat) . map f

This isn't really a fold of course, but it is doing roughly the same
thing, it's summing the results of applying function 'f' to each element
in a list.

The problem here is that sum will only allow one spark at a time,
because

sum [] = 0
sum (x:xs) = x + sum xs

So we get something like:
0 + (x4 + (x3 + (x2 + (x1

For example the result for (x4 + previous) can only be evaluated after
x3, x2 and x1 have been evaluated.  This means it won't spark evaluation
on x4 until (x3 + ) has been evaluated, thus only one core is ever
used.

I believe fold is just the general case of sum and the same logic
applies.


I suppose my questions are:

Have I got this right, if not very succinct!?  

Is it purely the strictness of (+) that causes this situation?

Ignoring DPH, is it possible to write a parallel fold avoiding something
like the technique below?


Anyhow, a workaround similar to those suggested I came up with is to
divide the folds up across the cores and then sum the sub-folds - this
produces approximately double the performance across two cores:

import Control.Parallel.Strategies (parMap,rwhnf)
import Data.List (foldl')
import Data.List.Split (chunk)
import GHC.Conc (numCapabilities)


-- Prepare to share work to be 
-- done across available cores
chunkOnCpu :: [a] - [[a]]
chunkOnCpu xs = chunk (length xs `div` numCapabilities) xs
 
-- Spark a fold of each chunk and
-- sum the results. Only works because
-- for associative folds.
foldChunks :: ([a] - a) - (a - b - a) - a - [[b]] - a
foldChunks combineFunc foldFunc acc = 
  combineFunc . (parMap rwhnf $ foldl' foldFunc acc)

-- Some pointless work to keep thread busy
workFunc :: Int - Int
workFunc 1 = 1
workFunc x = workFunc $ x - 1

-- Do some work on element x and append
foldFunc :: Int - Int - Int
foldFunc acc x = acc + workFunc x 

testList = repeat 10
answer =  foldChunks sum foldFunc 0 $ chunkOnCpu (take 50 testList)

main :: IO()
main = print answer













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


Re: [Haskell-cafe] Re: Parallel foldl doesn't work correctly

2009-12-13 Thread Philip Beadling
 -- Prepare to share work to be 
 -- done across available cores
 chunkOnCpu :: [a] - [[a]]
 chunkOnCpu xs = chunk (length xs `div` numCapabilities) xs
  
 -- Spark a fold of each chunk and
 -- sum the results. Only works because
 -- for associative folds.
 foldChunks :: ([a] - a) - (a - b - a) - a - [[b]] - a
 foldChunks combineFunc foldFunc acc = 
   combineFunc . (parMap rwhnf $ foldl' foldFunc acc)


I should probably point out that use of chunk above isn't a good idea in
anything beyond a toy example.  If you have used a list comprehension to
create your input then splitting it like the above results in thunks
that grow with list size as chunk forces generation of the list.  This
rapidly negates any advantage gained from processing across 1 core!
This is easily solved - just alter the generating function to create a
*list* of list comprehensions equal in length to the number of cores you
wish to process across, rather than create one list that is split across
the cores later.



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


[Haskell-cafe] Parallel foldl doesn't work correctly

2009-12-11 Thread Philip Beadling
Hi,

Can anyone put me right here.  I am trying to use a setup similar to
parMap to spark each valuation in a list in parallel, where the
resulting (evaluated) list is folded to produce a final single result.

Having done the obligatory google, I modified a few common examples to
give:

pfoldl f acc xs =  foldl' f acc (xs `using` parList rwhnf)


This compiles and if I monitor my CPUs it starts to use both cores, but
after approx 10 seconds, one core drops to low rate (I'm using a 2 core
machine).

The end result is that -N2 is actually a bit slower than -N1!

I'm guessing I haven't grasped the concept properly - although as map is
just 'foldl (+) 0' I'm at a loss to see why this approach wouldn't work
given it is pretty similar to parMap - could anyone point out what I'm
missing?

If it's any use the context of the code is below.

Many thanks!


Phil.


mc :: MonteCarloUserData - [[Double]] - Double
mc userData rndss = 
  existentialResult (pfoldl f existenAvg rndss) $ numOfSims userData
where f   = flip $ existentialCombine . payOff' .
expiryValue 
  payOff' = existentialPayOff userData
  expiryValue = foldl' (existentialEvolve userData) (stock
userData)
  existenAvg  = averager userData

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