[GHC] #14815: -XStrict prevents code inlining.

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hi, let's consider the following code: {{{ {-# LANGUAGE Strict #-} -- Comment/uncommenting this {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module K where import Control.Monad.Trans import qualified Control.Monad.State.Strict as S import Control.Monad.Primitive newtype StateT s m a = StateT (S.StateT s m a) -- S is Control.Monad.State.Strict deriving (Functor, Applicative, Monad, MonadTrans) instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} }}} If compiled with `-XStrict` this code is not inlined properly and it badly affects the performance. While discussing it on Haskell IRC `lyxia` helped very much with discovering the CORE differences. The lazy version has couple of things which the strict version is missing in form of `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers. Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lyxia): Maybe it's more correct to look at the interface rather than the simplifier. INLINE annotations still differ, but at least unfoldings appear in both. https://gist.github.com/Lysxia/355c4f1fa4ad0724c105d3baa42cbd4c -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lyxia): In the previous link, one difference for example is, in `K.lazy-iface`, `$fPrimMonadStateT_$cprimitive` is marked `Inline: INLINE (sat-args=1)`, whereas in `K.strict-iface`, `$fPrimMonadStateT1` is not marked such, and also has a much larger unfolding for some reason. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): So the bug here is not related with inlining. In general, any flag that effects generated Core (or analysis passes like the demand analysis) can effect inlining decisions. In particular, -XStrict can lead to more case expressions to evaluate intermediate results eagerly, which may cause larger code, which effects inlining decisions. Also, because some part of inlining decisions are done in the use site we'd also need to see the code that uses your `primitive` function. That being said, the bug here is that `-XStrict` shouldn't have any effect on generated Core because you only have one binding (`a` in your `primitive` function), and that has a laziness annotation. [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts... #strict-by-default-pattern-bindings GHC user manual on -XStrict] says that adding `~` in front of bindings gives us the regular lazy behavior. So really there's nothing `-XStrict` can do in this module. However the desugared code really changes with `-XStrict` in GHC 8.2.2, and that's the bug. I just tested with HEAD and 8.4 RC1 and this is fixed in both versions so you just have to update GHC when 8.4 released. (I don't know if there will be another 8.2 release, if so maybe we can include the fix in that version) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I just tested with HEAD and 8.4 RC1 and this is fixed in both versions
Can you offer a test case to add to our regression suite? Thanks! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I'm not sure how to write a test for this. The problem is in GHC 8.2 for the `primitive` function shown in the bug report we generate a desugared function with `RHS size: {terms: 16, types: 52, coercions: 15, joins: 0/1}` without `-XStrict`, and with `-XStrict` it becomes `-- RHS size: {terms: 16, types: 58, coercions: 15, joins: 1/2}` even though there should be no difference (as is already the case with GHC 8.4 and GHC HEAD). It's hard to write a program that generates different outputs based on the term size, so I guess I have to compare desugarer outputs with and without `-XStrict`, but even then I get different variables generated in each run, so I need equality modulo renaming.. bgamari, do you know how to implement such a test? Do we have any similar tests in the test suite already? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ulysses4ever): Couldn't Joachim's library [https://github.com/nomeata/inspection-testing inspection-testing] help here somehow? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Old description:
Hi, let's consider the following code:
{{{
{-# LANGUAGE Strict #-} -- Comment/uncommenting this {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module K where
import Control.Monad.Trans import qualified Control.Monad.State.Strict as S import Control.Monad.Primitive
newtype StateT s m a = StateT (S.StateT s m a) -- S is Control.Monad.State.Strict deriving (Functor, Applicative, Monad, MonadTrans)
instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} }}}
If compiled with `-XStrict` this code is not inlined properly and it badly affects the performance. While discussing it on Haskell IRC `lyxia` helped very much with discovering the CORE differences. The lazy version has couple of things which the strict version is missing in form of `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers.
Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542
New description: Hi, let's consider the following code: {{{#!hs {-# LANGUAGE Strict #-} -- Comment/uncommenting this {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module K where import Control.Monad.Trans import qualified Control.Monad.State.Strict as S import Control.Monad.Primitive newtype StateT s m a = StateT (S.StateT s m a) -- S is Control.Monad.State.Strict deriving (Functor, Applicative, Monad, MonadTrans) instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} }}} If compiled with `-XStrict` this code is not inlined properly and it badly affects the performance. While discussing it on Haskell IRC `lyxia` helped very much with discovering the CORE differences. The lazy version has couple of things which the strict version is missing in form of `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers. Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542 -- Comment (by bgamari): Indeed it sounds like testing this would be fiddly at best. That being said, it does seem quite unfortunate to simply close this. A user enabled `-XStrict` thinking that it would improve program performance and it got significantly worse, leaving the user with little recourse. I'm not sure what we can do better here, but this doesn't seem like much of a resolution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D4531 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): As discussed last week, I submitted a patch that compares program sizes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining.
-------------------------------------+-------------------------------------
Reporter: danilo2 | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4531
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: deSugar/T14815 (added) * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC