[GHC] #5775: Inconsistency in demand analysis

GHC ghc-devs at haskell.org
Wed Dec 16 11:57:32 UTC 2015


#5775: Inconsistency in demand analysis
-------------------------------------+-------------------------------------
        Reporter:  rl                |                Owner:  bgamari
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.2.1
       Component:  Compiler          |              Version:  7.5
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by bgamari):

 * priority:  normal => high
 * owner:   => bgamari
 * milestone:  8.0.1 => 8.2.1


Old description:

> A small program:
>
> {{{
> {-# LANGUAGE MagicHash, UnboxedTuples #-}
> module U where
> import GHC.Prim
> import GHC.Types
>
> idx :: Addr# -> Int -> Int
> {-# INLINE idx #-}
> idx a (I# i) = case readIntOffAddr# a i realWorld# of (# _, y #) -> I# y
>
> f :: Int -> Int -> Int
> {-# INLINE f #-}
> f x y = y + x
>
> foo :: Addr# -> Int -> Int
> foo a n = n `seq` loop (idx a 0) 1
>   where
>     loop x i = case i >= n of
>       False -> loop (f x (idx a i)) (i+1)
>       True  -> x
> }}}
>
> GHC infers the demand `LU(L)` for `loop`, only unboxes the second
> argument, ultimately generates a loop of type `Int -> Int# -> Int` and
> always allocates a thunk for the first argument:
>
> {{{
>       $wloop_si9 [Occ=LoopBreaker] :: Int -> Int# -> Int
>       [LclId, Arity=2, Str=DmdType LL]
>       $wloop_si9 =
>         \ (w1_shU :: Int) (ww1_shX :: Int#) ->
>           case >=# ww1_shX ww_si5 of _ {
>             False ->
>               $wloop_si9
>                 (case readIntOffAddr# @ RealWorld w_si2 ww1_shX
> realWorld#
>                  of _ { (# _, y_a9S #) ->
>                  case w1_shU of _ { I# y1_ahb -> I# (+# y_a9S y1_ahb) }
>                  })
>                 (+# ww1_shX 1);
>             True -> w1_shU
>           }; }
> }}}
>
> But if I change the pragma on `f` from `INLINE` to `NOINLINE`, `loop`
> gets the demand `U(L)U(L)m` and GHC manages to unbox both arguments as
> well as the result, producing a nice tight loop:
>
> {{{
>       $wloop_sii [Occ=LoopBreaker] :: Int# -> Int# -> Int#
>       [LclId, Arity=2, Str=DmdType LL]
>       $wloop_sii =
>         \ (ww1_shW :: Int#) (ww2_si0 :: Int#) ->
>           case >=# ww2_si0 ww_sib of _ {
>             False ->
>               case readIntOffAddr# @ RealWorld w_si8 ww2_si0 realWorld#
>               of _ { (# _, y1_Xac #) ->
>               case f (I# ww1_shW) (I# y1_Xac) of _ { I# ww3_Xin ->
>               $wloop_sii ww3_Xin (+# ww2_si0 1)
>               }
>               };
>             True -> ww1_shW
>           }; }
> }}}
>
> It would be nice if this happened in both cases.

New description:

 A small program:

 {{{#!hs
 {-# LANGUAGE MagicHash, UnboxedTuples #-}
 module U where
 import GHC.Prim
 import GHC.Types

 idx :: Addr# -> Int -> Int
 {-# INLINE idx #-}
 idx a (I# i) = case readIntOffAddr# a i realWorld# of (# _, y #) -> I# y

 f :: Int -> Int -> Int
 {-# INLINE f #-}
 f x y = y + x

 foo :: Addr# -> Int -> Int
 foo a n = n `seq` loop (idx a 0) 1
   where
     loop x i = case i >= n of
       False -> loop (f x (idx a i)) (i+1)
       True  -> x
 }}}

 GHC infers the demand `LU(L)` for `loop`, only unboxes the second
 argument, ultimately generates a loop of type `Int -> Int# -> Int` and
 always allocates a thunk for the first argument:

 {{{#!hs
       $wloop_si9 [Occ=LoopBreaker] :: Int -> Int# -> Int
       [LclId, Arity=2, Str=DmdType LL]
       $wloop_si9 =
         \ (w1_shU :: Int) (ww1_shX :: Int#) ->
           case >=# ww1_shX ww_si5 of _ {
             False ->
               $wloop_si9
                 (case readIntOffAddr# @ RealWorld w_si2 ww1_shX realWorld#
                  of _ { (# _, y_a9S #) ->
                  case w1_shU of _ { I# y1_ahb -> I# (+# y_a9S y1_ahb) }
                  })
                 (+# ww1_shX 1);
             True -> w1_shU
           }; }
 }}}

 But if I change the pragma on `f` from `INLINE` to `NOINLINE`, `loop` gets
 the demand `U(L)U(L)m` and GHC manages to unbox both arguments as well as
 the result, producing a nice tight loop:

 {{{#!hs
       $wloop_sii [Occ=LoopBreaker] :: Int# -> Int# -> Int#
       [LclId, Arity=2, Str=DmdType LL]
       $wloop_sii =
         \ (ww1_shW :: Int#) (ww2_si0 :: Int#) ->
           case >=# ww2_si0 ww_sib of _ {
             False ->
               case readIntOffAddr# @ RealWorld w_si8 ww2_si0 realWorld#
               of _ { (# _, y1_Xac #) ->
               case f (I# ww1_shW) (I# y1_Xac) of _ { I# ww3_Xin ->
               $wloop_sii ww3_Xin (+# ww2_si0 1)
               }
               };
             True -> ww1_shW
           }; }
 }}}

 It would be nice if this happened in both cases.

--

Comment:

 For the record this is still reproducible with GHC 7.10.3.

 It sounds like this ought to be revisited (if for no other reason than to
 ensure that the fragility really is only exposed with `unsafePerformIO`).

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/5775#comment:16>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list