[GHC] #3738: Typechecker floats stuff out of INLINE right hand sides
GHC
ghc-devs at haskell.org
Mon Dec 14 14:27:05 UTC 2015
#3738: Typechecker floats stuff out of INLINE right hand sides
-------------------------------------+-------------------------------------
Reporter: rl | Owner: igloo
Type: bug | Status: closed
Priority: normal | Milestone: 7.0.1
Component: Compiler | Version: 6.13
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case: T3738
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by bgamari:
Old description:
> Small program:
> {{{
> foo :: Num a => [a] -> a
> {-# INLINE foo #-}
> foo = go 0
> where
> go m (n:ns) = m `seq` go (m+n) ns
> go m [] = m
>
> bar :: [Int] -> Int
> {-# INLINE bar #-}
> bar = foo
> }}}
> Here is what `bar` looks like in the interface file:
> {{{
> a6de4c46e53e565ed25ab5a38910e9cb
> $wgo :: GHC.Prim.Int# -> [GHC.Types.Int] -> GHC.Prim.Int#
> {- Arity: 2, HasNoCafRefs, Strictness: LS -}
> 6838e3faa095285614477ebc92f54987
> bar :: [GHC.Types.Int] -> GHC.Types.Int
> {- Arity: 1, HasNoCafRefs, Strictness: Sm, Inline: INLINE,
> Unfolding: InlineRule: (arity 0 False) (Foo.bar_foo) -}
> 5d06906ae99b9aefa1c6d251c3f2fc46
> bar_foo :: [GHC.Types.Int] -> GHC.Types.Int
> {- Arity: 1, HasNoCafRefs, Strictness: Sm,
> Unfolding: InlineRule: (arity 0 True) (\ w :: [GHC.Types.Int] ->
> case @ GHC.Types.Int
> Foo.$wgo 0 w of ww { DEFAULT ->
> GHC.Types.I# ww }) -}
> }}}
> Note that the loop has disappeared from `bar`'s unfolding. Also,
> `bar_foo` doesn't have an INLINE pragma.
>
> Incidentally, GHC specialises `foo` here and the specialisation doesn't
> get an INLINE pragma, either:
> {{{
> foo :: forall a. GHC.Num.Num a => [a] -> a
> {- Arity: 1, HasNoCafRefs, Strictness: L, Inline: INLINE,
> Unfolding: InlineRule: (arity 1 False) ... -}
>
> foo_$sfoo :: [GHC.Types.Int] -> GHC.Types.Int
> {- Arity: 1, HasNoCafRefs, Strictness: Sm,
> Unfolding: InlineRule: (arity 0 False) ... -}
>
> "SPEC Foo.foo [GHC.Types.Int]" ALWAYS forall $dNum :: GHC.Num.Num
> GHC.Types.Int
> Foo.foo @ GHC.Types.Int $dNum = Foo.foo_$sfoo
> }}}
New description:
Small program:
{{{#!hs
foo :: Num a => [a] -> a
{-# INLINE foo #-}
foo = go 0
where
go m (n:ns) = m `seq` go (m+n) ns
go m [] = m
bar :: [Int] -> Int
{-# INLINE bar #-}
bar = foo
}}}
Here is what `bar` looks like in the interface file:
{{{
a6de4c46e53e565ed25ab5a38910e9cb
$wgo :: GHC.Prim.Int# -> [GHC.Types.Int] -> GHC.Prim.Int#
{- Arity: 2, HasNoCafRefs, Strictness: LS -}
6838e3faa095285614477ebc92f54987
bar :: [GHC.Types.Int] -> GHC.Types.Int
{- Arity: 1, HasNoCafRefs, Strictness: Sm, Inline: INLINE,
Unfolding: InlineRule: (arity 0 False) (Foo.bar_foo) -}
5d06906ae99b9aefa1c6d251c3f2fc46
bar_foo :: [GHC.Types.Int] -> GHC.Types.Int
{- Arity: 1, HasNoCafRefs, Strictness: Sm,
Unfolding: InlineRule: (arity 0 True) (\ w :: [GHC.Types.Int] ->
case @ GHC.Types.Int
Foo.$wgo 0 w of ww { DEFAULT ->
GHC.Types.I# ww }) -}
}}}
Note that the loop has disappeared from `bar`'s unfolding. Also, `bar_foo`
doesn't have an INLINE pragma.
Incidentally, GHC specialises `foo` here and the specialisation doesn't
get an INLINE pragma, either:
{{{
foo :: forall a. GHC.Num.Num a => [a] -> a
{- Arity: 1, HasNoCafRefs, Strictness: L, Inline: INLINE,
Unfolding: InlineRule: (arity 1 False) ... -}
foo_$sfoo :: [GHC.Types.Int] -> GHC.Types.Int
{- Arity: 1, HasNoCafRefs, Strictness: Sm,
Unfolding: InlineRule: (arity 0 False) ... -}
"SPEC Foo.foo [GHC.Types.Int]" ALWAYS forall $dNum :: GHC.Num.Num
GHC.Types.Int
Foo.foo @ GHC.Types.Int $dNum = Foo.foo_$sfoo
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/3738#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list