[GHC] #12137: Warning about “INLINE binder is (non-rule) loop breaker” with `-dcore-lint`

#12137: Warning about “INLINE binder is (non-rule) loop breaker” with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- With this code using `lens` {{{#!hs {-# Language TemplateHaskell #-} import Control.Lens data Config = Config { _companyName :: String } data AppState = AppState { _asConfig :: Config } makeClassy ''Config instance HasConfig AppState where config = undefined }}} gives {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP Ok, modules loaded: Main. *Main> }}} ---- `makeClass` actually dumps {{{ <interactive>:64:54-72: Splicing declarations makeClassy ''Config ======> class HasConfig c_axo7 where config :: Lens' c_axo7 Config companyName :: Lens' c_axo7 String {-# INLINE companyName #-} companyName = (.) config companyName instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = iso (\ (Config x_axo8) -> x_axo8) Config }}} Using that to create a small example ---- {{{#!hs data Config = Config { name :: String } class HasConfig a where config :: a -> Config companyName :: a -> String {-# INLINE companyName #-} companyName a = name (config a) instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = name . config }}} which works perfectly fine without `-dcore-lint` but fails with {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q Ok, modules loaded: Main. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12137 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12137: Warning about “INLINE binder is (non-rule) loop breaker” with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -1,1 +1,1 @@ - With this code using `lens` + Using `lens` @@ -74,1 +74,1 @@ - which works perfectly fine without `-dcore-lint` but fails with + which works perfectly fine without `-dcore-lint` but gives a warning with New description: Using `lens` {{{#!hs {-# Language TemplateHaskell #-} import Control.Lens data Config = Config { _companyName :: String } data AppState = AppState { _asConfig :: Config } makeClassy ''Config instance HasConfig AppState where config = undefined }}} gives {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP Ok, modules loaded: Main. *Main> }}} ---- `makeClass` actually dumps {{{ <interactive>:64:54-72: Splicing declarations makeClassy ''Config ======> class HasConfig c_axo7 where config :: Lens' c_axo7 Config companyName :: Lens' c_axo7 String {-# INLINE companyName #-} companyName = (.) config companyName instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = iso (\ (Config x_axo8) -> x_axo8) Config }}} Using that to create a small example ---- {{{#!hs data Config = Config { name :: String } class HasConfig a where config :: a -> Config companyName :: a -> String {-# INLINE companyName #-} companyName a = name (config a) instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = name . config }}} which works perfectly fine without `-dcore-lint` but gives a warning with {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q Ok, modules loaded: Main. }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12137#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12137: Warning about “INLINE binder is (non-rule) loop breaker” with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | 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: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: This issue is explained in ticket:9418#comment:1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12137#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12137: Warning about “INLINE binder is (non-rule) loop breaker” with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Inlining -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12137#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC