[Haskell-cafe] Dead else branch does influence runtime?

Daniel Fischer daniel.is.fischer at googlemail.com
Tue Jun 14 15:51:57 CEST 2011


On Tuesday 14 June 2011, 14:35:19, Johannes Waldmann wrote:
> Dear all,
> 
> I am very puzzled by a program that contains
> an "else" branch that is never executed,
> but still seems to slow down the program.
> (When I replace it by "undefined", the resulting program runs much
> faster.) http://hackage.haskell.org/trac/ghc/ticket/5256
> 
> I thought it may be a type issue (the type of the else branch
> forces the type of the "then" branch to be more general,
> thus some optimization might not fire) but the types of the branches
> look identical. (They are generic, but the specializer should take
> care of that.)

The else branch is not dead code in the sense of 'unreachable', it's just 
not executed in your particular run.
Therefore the compiler has to generate code for it.

In the case of undefined, it's short and simple code:

             (case GHC.Conc.Sync.numCapabilities of _ { GHC.Types.I# x_a1zI 
->
                          case GHC.Prim.<=# x_a1zI 1 of _ {
                            GHC.Bool.False ->
                              GHC.Err.undefined
                              `cast` (CoUnsafe (forall a_a1fu. a_a1fu) 
GHC.Base.String
                                      :: (forall a_a1fu. a_a1fu) ~ 
GHC.Base.String);

appearing in Main.main1 - the undefined makes foldb_cap simple enough to be 
inlined, then V.foldl' and eff, h1 are inlined too, to become a loop on 
three unboxed Int#s.

With id, main1 jumps to foldb_cap, which contains a lot of code for the 
(cap > 1)-branch, and - that's what causes the slowdown - a worker loop

$s$wfoldlM'_loop_s3EE [Occ=LoopBreaker]
            :: GHC.Prim.Int#
               -> (GHC.Types.Int, GHC.Types.Int)
               -> (# GHC.Types.Int, GHC.Types.Int #)

which uses the passed functions (thus you have no inlining of eff and h1, 
and a boxed tuple of boxed Int's in your worker).

> 
> I am sure GHC headquarters will look at this when they find the time
> but perhaps there's some additional knowledge on this mailing list
> that might help.
> 
> J.W.



More information about the Haskell-Cafe mailing list