> C. Maybe the liberate-case threshold should be higher. I'd be
> interested to hear if increasing the threshold has good effects for
> anyone else.
Whenever I used liberate-case in our array work, I supplied a higher
threshold, too. 100 seems to be a good start.
Manuel
__
I couldn't resist looking into this. Here's the story. All of this
applies to the explicitly-recursive program; I have not looked at the
list version.
To preview the headlines:
Original program13.1s
1. Use Int instead of Bool 12.6s
2. Use -fl
Hi again,
> > A first hint is to never try to guess what kind of code ghc generates.
> > If you're in need of performance you need to look at some lower level
> > code. I recommend the -fext-core flag to produce external core, a
> > sort-of-readable output of ghc's internal representation of the
>
duncan.coutts:
> This sort of code runs very slowly when compared to the equivalent in C:
This example uses unboxing and primops over Lemmih's and seems to run a bit
faster:
Lemmih's loops:
./a.out 1.35s user 0.00s system 99% cpu 1.359 total
This code:
./a.out 0.99s user 0.00s
On Tue, 2005-03-15 at 02:06 +0100, Lemmih wrote:
> We can make it a little faster by not doing bound checks:
>
> > test4 :: IO ()
> > test4 = do
> > (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> > doFromTo 0 $ \_ ->
> > doFromTo 0 99 $ \y ->
> > doFromTo 0 99 $ \x ->
>
On Tue, 2005-03-15 at 01:39 +0100, Josef Svenningsson wrote:
> Hi,
>
> On Mon, 14 Mar 2005 13:41:06 +, Duncan Coutts
> <[EMAIL PROTECTED]> wrote:
> > This sort of code runs very slowly when compared to the equivalent in C:
> >
> I'm afraid the kind of array processing code you posted will alw
This one might go even faster again.
Essentially due to Don Stewart but removes the bound checks and uses
Int as an index.
-
module Main
where
import Data.Array.MArray
import Data.Array.IO
import Data.Array.Base
import GHC.Base
import GHC.IOBase
forn a n | n >=# 1# = return ()
On Tue, 15 Mar 2005 02:06:06 +0100, Lemmih <[EMAIL PROTECTED]> wrote:
> We can make it a little faster by not doing bound checks:
>
> > test4 :: IO ()
> > test4 = do
> > (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> > doFromTo 0 $ \_ ->
> > doFromTo 0 99 $ \y ->
> > do
We can make it a little faster by not doing bound checks:
> test4 :: IO ()
> test4 = do
> (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> doFromTo 0 $ \_ ->
> doFromTo 0 99 $ \y ->
> doFromTo 0 99 $ \x ->
> unsafeWrite arr (x*(y+1)) False
Timings (compiled with
Hi,
On Mon, 14 Mar 2005 13:41:06 +, Duncan Coutts
<[EMAIL PROTECTED]> wrote:
> This sort of code runs very slowly when compared to the equivalent in C:
>
I'm afraid the kind of array processing code you posted will always be
slower than the C "equivalent". Haskell only has safe array meaning
On Mon, 2005-03-14 at 13:41 +, Duncan Coutts wrote:
> Hi,
>
> This sort of code runs very slowly when compared to the equivalent in C:
[snip]
BTW These timings were for ghc 6.2.2
My version of ghc 6.3 (CVS from about a month or two ago) gave slightly
beter timings on both loop version.
My
11 matches
Mail list logo