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

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


On Tuesday 14 June 2011, 15:51:57, Daniel Fischer wrote:
> On Tuesday 14 June 2011, 14:35:19, Johannes Waldmann wrote:

> 
> 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.

Note that you get good behaviour when you help GHC a bit, in particular a 
static argument transformation for the function parameters of foldb_cap 
allows them to be inlined and (in this case) you get the nice loop on 
unboxed Int#s again:


foldb_cap :: ( V.Unbox a, V.Unbox b )
      => Int
      -> b
      -> ( a -> b )
      -> ( b -> b -> b )
      -> Vector a
      -> b
foldb_cap cp strt f g xs = work cp strt xs
  where
    work cap e s =
      if cap <= 1
      then V.foldl' g e $ V.map f s
         -- replace "id" by "undefined" in the following,
         -- and notice a drastic decrease in runtime -
         -- although this branch is never executed:
      else id $ case V.length s of
        0 -> e
        1 -> f $! V.head s
        n -> let splitAt k v =
                       ( V.take k v, V.drop k v )
                 ( s1, s2 ) = splitAt ( div n 2 ) s
                 cap' = div cap 2
                 v1 = work cap' e s1
                 v2 = work cap' e s2
                 v = g v1 v2
             in par v1 $ pseq v2 $ v





More information about the Haskell-Cafe mailing list