On 11/06/2012, at 18:52, Evan Laforge wrote:

> On Tue, May 29, 2012 at 12:52 PM, Roman Leshchinskiy <r...@cse.unsw.edu.au> 
> wrote:
>> 
>> Vector should definitely fuse this, if it doesn't it's a bug. Please report 
>> if it doesn't for you. To verify, just count the number of letrecs in the 
>> optimised Core. You'll see one letrec if it has been fused and two if it 
>> hasn't.
> 
> I see two letrecs in find_before2, but both of them are on findIndex.
> I only have one findIndex so I'm not sure what's going on.  The first
> one calls the second, but there's an boxed Either argument in there,
> which must be coming out of vector internals.

Hmm, which version of GHC and what compiler flags are you using? I'm not 
familiar with ghc-core, maybe that's doing something wrong. Just run ghc -O2 
-ddump-simpl and look at the output. Below is the code I'm getting for 
find_before2 with 7.4.2. As you can see, everything has been fused (although I 
notice that GHC isn't pushing x_a11p and y1_a124 into the branches for some 
reason, looks like a new regression but not a particularly bad one and nothing 
to do with fusion).

find_before2_rkk :: Int -> Vector Int -> Int
[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType LU(LLL)m]
find_before2_rkk =
  \ (n_arE :: Int) (vec_arF :: Vector Int) ->
    case vec_arF `cast` ...
    of _ { Vector ipv_s2Jf ipv1_s2Jg ipv2_s2Jh ->
    case n_arE of _ { I# y_a11t ->
    case ># 0 y_a11t of _ {
      False ->
        letrec {
          $sfindIndex_loop_s2Qz [Occ=LoopBreaker]
            :: Int# -> Int# -> Int# -> Id (Maybe Int)
          [LclId, Arity=3, Str=DmdType LLL]
          $sfindIndex_loop_s2Qz =
            \ (sc_s2Q8 :: Int#) (sc1_s2Q9 :: Int#) (sc2_s2Qa :: Int#) ->
              case >=# sc_s2Q8 ipv1_s2Jg of _ {
                False ->
                  case indexIntArray# ipv2_s2Jh (+# ipv_s2Jf sc_s2Q8)
                  of wild_a2JM { __DEFAULT ->
                  let {
                    x_a11p [Dmd=Just L] :: Int#
                    [LclId, Str=DmdType]
                    x_a11p = +# sc1_s2Q9 wild_a2JM } in
                  case ># x_a11p y_a11t of _ {
                    False ->
                      $sfindIndex_loop_s2Qz (+# sc_s2Q8 1) x_a11p (+# sc2_s2Qa 
1);
                    True -> (Just @ Int (I# sc2_s2Qa)) `cast` ...
                  }
                  };
                True -> (Nothing @ Int) `cast` ...
              }; } in
        case ($sfindIndex_loop_s2Qz 0 0 1) `cast` ... of _ {
          Nothing -> lvl_r2QO;
          Just i_arH ->
            case i_arH of _ { I# x_a11Q ->
            let {
              y1_a124 [Dmd=Just L] :: Int#
              [LclId, Str=DmdType]
              y1_a124 = -# x_a11Q 1 } in
            case <=# 0 y1_a124 of _ {
              False -> lvl_r2QO;
              True -> I# y1_a124
            }
            }
        };
      True -> lvl_r2QO
    }
    }
    }

Roman


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to