#3736: GHC specialising instead of inlining
-------------------------+--------------------------------------------------
    Reporter:  guest     |        Owner:                         
        Type:  bug       |       Status:  new                    
    Priority:  normal    |    Milestone:  6.14.1                 
   Component:  Compiler  |      Version:  6.10.4                 
    Keywords:            |   Difficulty:                         
          Os:  Linux     |     Testcase:                         
Architecture:  x86       |      Failure:  Runtime performance bug
-------------------------+--------------------------------------------------

Comment(by igloo):

 The two versions seem to perform the same now, but the stable branch is
 faster:
 {{{
 $ ghc-head --make Main -O
 [1 of 1] Compiling Main             ( Main.hs, Main.o )
 Linking Main ...
 $ time ./Main 1
 ./Main 1  1.19s user 0.12s system 99% cpu 1.314 total
 $ time ./Main 2
 ./Main 2  1.18s user 0.15s system 100% cpu 1.323 total

 $ ghc-stable --make Main -O
 [1 of 1] Compiling Main             ( Main.hs, Main.o )
 Linking Main ...
 $ time ./Main 1
 ./Main 1  3.02s user 0.19s system 99% cpu 3.218 total
 $ time ./Main 2
 ./Main 2  0.33s user 0.16s system 99% cpu 0.493 total
 }}}

 When looking at the core generated, I noticed that HEAD was making a
 binding:
 {{{
 a_r1Ld :: GHC.Types.Float
 [GblId, Caf=NoCafRefs, Str=DmdType m]
 a_r1Ld = GHC.Types.F# __float 0.6
 }}}
 whereas stable made no such binding. Here's a much smaller example:


 {{{
 module Main (main) where

 import System.IO.Unsafe (unsafePerformIO)

 main :: IO ()
 main = (fst $ unfoldrN (fst initPhase2)) `seq` return ()

 {-# INLINE initPhase2 #-}
 initPhase2 :: (Float, Float)
 initPhase2 = (0.2, 0.6)

 unfoldrN :: a -> ((), a)
 unfoldrN x0 = unsafePerformIO $ createAndTrim x0

 createAndTrim :: b -> IO ((), b)
 createAndTrim f = return ((), f)
 }}}

 {{{
 $ ghc-head -Wall --make -O q.hs -fforce-recomp -ddump-simpl | grep '0\.6'
 [1 of 1] Compiling Main             ( q.hs, q.o )
 a_ri8 = GHC.Types.F# __float 0.6
          Tmpl= (GHC.Types.F# __float 0.2, GHC.Types.F# __float 0.6)}]
 Linking q ...
 }}}

 {{{
 $ ghc-stable -Wall --make -O q.hs -fforce-recomp -ddump-simpl | grep
 '0\.6'
 [1 of 1] Compiling Main             ( q.hs, q.o )
 Linking q ...
 }}}

 I don't know if this is actually related to the slowdown, but it seems
 suspicious anyway.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3736#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to