RE: [Haskell-cafe] force inlining in GHC (fwd)

maybe also of interest in the ghc-core thread
---------- Forwarded message ----------
Date: Fri, 23 May 2008 21:21:03 +0200 (CEST)
From: Henning Thielemann
On Tue, 29 Apr 2008, Simon Peyton-Jones wrote:
As luck would have it, I'm working on INLINE pragmas for Roman right at this moment.
Could you spare a moment to give me a concrete test case, to make sure I hit your case too? If you can give me a program that doesn't optimise as you expect, I'm much more likely to get it right.
I examined some more examples and found out that the behaviours of GHC-6.4.1 and GHC-6.8.2 are quite consistent, that is, accelerations I achieved for GHC-6.8.2 also worked for GHC-6.4.1. Main problem in both GHC-6.4.1 and GHC-6.8.2 remains that sometimes GHC decides to SPECIALISE a function that is tagged with INLINE. I think that SPECIALISE should either copy the INLINE tag to the specialised function (confluent rewriting, right?) or should not SPECIALISE an INLINE function at all. I can now present a simple example, however it needs a (self-contained) package: http://darcs.haskell.org/storablevector/ module Main where import qualified Data.StorableVector.Lazy as SV zipData :: SV.Vector Double zipData = SV.take 500000 $ SV.zipWith (+) (SV.iterate SV.defaultChunkSize ((1-1e-6)*) 0.5) (SV.iterate SV.defaultChunkSize (1e-6 +) 0) main :: IO () main = do SV.writeFile "test-data" zipData ghc-core -o dist/build/fusiontest/fusiontest -O -Wall -fexcess-precision -package storablevector speedtest/SpecialiseTest.hs I get quite at the beginning of the Core: a1 :: Data.StorableVector.Lazy.ChunkSize -> (Double -> Data.Maybe.Maybe (Double, Double)) -> Double -> [Data.StorableVector.Base.Vector Double] This looks much like specialised SV.unfoldr, the expansion of SV.iterate. It seems to be that GHC detects that SV.unfoldr is called twice with the same type and thus specialises it to Double - while forgetting that SV.unfoldr should be inlined anyway.
participants (1)
-
Henning Thielemann