This comes from a Haskell game, where  the C program was about 10x
faster again (thanks to SSE).

The C program to test against is here:

    http://stackoverflow.com/questions/3115540

Maybe use it as a benchmark?

-- Don

davidterei:
> Too Slow :).
> 
> I fixed a few bugs in the LLVM backend in the last 24 hours, they seem
> to have fixed this segault (that or I'm not reproducing your results
> right). I can compile and run this program fine with latest GHC Head
> under both 32/64 bit Linux.
> 
> Under 32bit I get a nice speed up with the LLVM backend but under 64
> bit, fasm gives me about 1.5s and fllvm gives me about 1.8s which
> isn't very good. So will have to investigate that, its quite unusual
> for the ncg to beat llvm by anything more then 10%.
> 
> Cheers,
> David
> 
> On 29 June 2010 03:32, Don Stewart <[email protected]> wrote:
> > The following vector program segfaults with the latest head snapshot,
> >
> >    {-# LANGUAGE BangPatterns #-}
> >
> >    {-
> >        ghc 6.12.1 -O2
> >        1.752
> >    -}
> >
> >    import Data.Vector.Storable
> >    import qualified Data.Vector.Storable as V
> >    import Foreign
> >    import Foreign.C.Types
> >
> >    -- Define a 4 element vector type
> >    data Vec4 = Vec4 {-# UNPACK #-} !CFloat
> >                     {-# UNPACK #-} !CFloat
> >                     {-# UNPACK #-} !CFloat
> >                     {-# UNPACK #-} !CFloat
> >
> >    ------------------------------------------------------------------------
> >
> >    -- Ensure we can store it in an array
> >    instance Storable Vec4 where
> >      sizeOf _ = sizeOf (undefined :: CFloat) * 4
> >      alignment _ = alignment (undefined :: CFloat)
> >
> >      {-# INLINE peek #-}
> >      peek p = do
> >                 a <- peekElemOff q 0
> >                 b <- peekElemOff q 1
> >                 c <- peekElemOff q 2
> >                 d <- peekElemOff q 3
> >                 return (Vec4 a b c d)
> >        where
> >          q = castPtr p
> >
> >      {-# INLINE poke #-}
> >      poke p (Vec4 a b c d) = do
> >                                pokeElemOff q 0 a
> >                                pokeElemOff q 1 b
> >                                pokeElemOff q 2 c
> >                                pokeElemOff q 3 d
> >        where
> >          q = castPtr p
> >
> >    ------------------------------------------------------------------------
> >
> >    a = Vec4 0.2 0.1 0.6 1.0
> >    m = Vec4 0.99 0.7 0.8 0.6
> >
> >    add :: Vec4 -> Vec4 -> Vec4
> >    {-# INLINE add #-}
> >    add (Vec4 a b c d) (Vec4 a' b' c' d') = Vec4 (a+a') (b+b') (c+c') (d+d')
> >
> >    mult :: Vec4 -> Vec4 -> Vec4
> >    {-# INLINE mult #-}
> >    mult (Vec4 a b c d) (Vec4 a' b' c' d') = Vec4 (a*a') (b*b') (c*c') (d*d')
> >
> >    vsum :: Vec4 -> CFloat
> >    {-# INLINE vsum #-}
> >    vsum (Vec4 a b c d) = a+b+c+d
> >
> >    multList :: Int -> Vector Vec4 -> Vector Vec4
> >    multList !count !src
> >        | count <= 0    = src
> >        | otherwise     = multList (count-1) $ V.map (\v -> add (mult v m) 
> > a) src
> >
> >    main = do
> >        print $ Data.Vector.Storable.sum
> >              $ Data.Vector.Storable.map vsum
> >              $ multList repCount
> >              $ Data.Vector.Storable.replicate arraySize (Vec4 0 0 0 0)
> >
> >    repCount, arraySize :: Int
> >    repCount = 10000
> >    arraySize = 20000
> >
> >
> >
> > $ ghc-6.13.20100625 -fllvm -O2 --make A.hs
> > [1 of 1] Compiling Main             ( A.hs, A.o )
> > Linking A ...
> > $ ./A
> > zsh: segmentation fault  ./A
> >
> >
> 
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to