[GHC] #13960: Ticks exhausted with 8.0.2

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: -------------------------------------+------------------------------------- This is unfortunately a closed-source codebase I'm experiencing this with, but we get a GHC panic with a small/not-doing-anything-crazy codebase: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired Class op return To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 118123 }}} When upping to `-fsimpl-tick-factor=150`, the error is a little different: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone $ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 177190 }}} Upping to 200 makes the issue go away. We're building with `ghc-options: -fhpc` Before each build, we remove all .tix files and the .hpc directory At the point this error fires, we're compiling the 6th module of 9. The first 6 modules to compile only have a total of 635 lines of code. To address issues I've seen in other similar tickets: - There are no recursive module imports - We don't use any `{-# INLINE #-}` or similar pragmas - There is no Template Haskell other than a `makeLenses ''App` for a small Snaplet. - We don't have any "very"/exponentially recursive code - We don't use any unboxed tuples (there *is* ST code in a module that's compiled, but not the one ghc panics on) - We don't use type families - We don't use TypeRep or Typeable - We don't use Generic When this error occurs, it fails on a module which has very little code in it. It's mainly a list of ~200-300 Query[0] values, using OverloadedStrings. I notice Query's `mappend`, which we use, is `INLINE`d. Please let me know if I can provide more detail! [0] http://hackage.haskell.org/package/postgresql-simple-0.5.3.0/docs /Database-PostgreSQL-Simple-Types.html#t:Query -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): In general it is expected that some modules will occasionally need to have the tick limit bumped in order to compile. Afterall, the simplifier tick mechanism is merely a heuristic. In your case it sounds like this is a rather small and simple program, which makes the failure a bit more surprising. However, it's hard to tell without seeing actual code. It would be quite helpful if you could try to reduce the problem down to a something that you can share. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Description changed by tom-bop: @@ -1,2 +1,75 @@ - This is unfortunately a closed-source codebase I'm experiencing this with, - but we get a GHC panic with a small/not-doing-anything-crazy codebase: + **Update**: I've been able to provide a much simpler test case for this + error: + + Broken.hs: + + {{{ + #!haskell + {-# LANGUAGE OverloadedStrings #-} + + module Broken (breaks) where + + import Database.PostgreSQL.Simple.Types (Query(..)) + + breaks :: [(Query, Query)] + breaks = [ + ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + , ("query", "query") + ] + }}} + + broken.cabal: + + {{{ + name: broken + version: 0.1.0.0 + build-type: Simple + cabal-version: >=1.10 + + library + exposed-modules: + Broken + other-extensions: + OverloadedStrings + build-depends: + base + -- >=4.9 && <4.10 + , postgresql-simple + -- >=0.5 && <0.6 + default-language: Haskell2010 + }}} + + `cabal install broken.cabal` results in: + + {{{ + ghc: panic! (the 'impossible' happened) + (GHC version 8.0.2 for x86_64-unknown-linux): + Simplifier ticks exhausted + When trying UnfoldingDone ord + To increase the limit, use -fsimpl-tick-factor=N (default 100) + If you need to do this, let GHC HQ know, and what factor you needed + To see detailed counts use -ddump-simpl-stats + Total ticks: 20731 + + Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug + }}} + + ---- + + ---- + + **Older info:** + + + ~~This is unfortunately a closed-source codebase I'm experiencing this + with, but we get a GHC panic with a small/not-doing-anything-crazy + codebase:~~ New description: **Update**: I've been able to provide a much simpler test case for this error: Broken.hs: {{{ #!haskell {-# LANGUAGE OverloadedStrings #-} module Broken (breaks) where import Database.PostgreSQL.Simple.Types (Query(..)) breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}} broken.cabal: {{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10 library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base -- >=4.9 && <4.10 , postgresql-simple -- >=0.5 && <0.6 default-language: Haskell2010 }}} `cabal install broken.cabal` results in: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone ord To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 20731 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} ---- ---- **Older info:** ~~This is unfortunately a closed-source codebase I'm experiencing this with, but we get a GHC panic with a small/not-doing-anything-crazy codebase:~~ {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired Class op return To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 118123 }}} When upping to `-fsimpl-tick-factor=150`, the error is a little different: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone $ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 177190 }}} Upping to 200 makes the issue go away. We're building with `ghc-options: -fhpc` Before each build, we remove all .tix files and the .hpc directory At the point this error fires, we're compiling the 6th module of 9. The first 6 modules to compile only have a total of 635 lines of code. To address issues I've seen in other similar tickets: - There are no recursive module imports - We don't use any `{-# INLINE #-}` or similar pragmas - There is no Template Haskell other than a `makeLenses ''App` for a small Snaplet. - We don't have any "very"/exponentially recursive code - We don't use any unboxed tuples (there *is* ST code in a module that's compiled, but not the one ghc panics on) - We don't use type families - We don't use TypeRep or Typeable - We don't use Generic When this error occurs, it fails on a module which has very little code in it. It's mainly a list of ~200-300 Query[0] values, using OverloadedStrings. I notice Query's `mappend`, which we use, is `INLINE`d. Please let me know if I can provide more detail! [0] http://hackage.haskell.org/package/postgresql-simple-0.5.3.0/docs /Database-PostgreSQL-Simple-Types.html#t:Query -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 tom-bop): Thanks @bgamari - I've been able to simplify it substantially and provide a repo case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Description changed by tom-bop: @@ -12,1 +12,1 @@ - import Database.PostgreSQL.Simple.Types (Query(..)) + import Database.PostgreSQL.Simple.Types (Query) New description: **Update**: I've been able to provide a much simpler test case for this error: Broken.hs: {{{ #!haskell {-# LANGUAGE OverloadedStrings #-} module Broken (breaks) where import Database.PostgreSQL.Simple.Types (Query) breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}} broken.cabal: {{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10 library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base -- >=4.9 && <4.10 , postgresql-simple -- >=0.5 && <0.6 default-language: Haskell2010 }}} `cabal install broken.cabal` results in: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone ord To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 20731 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} ---- ---- **Older info:** ~~This is unfortunately a closed-source codebase I'm experiencing this with, but we get a GHC panic with a small/not-doing-anything-crazy codebase:~~ {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired Class op return To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 118123 }}} When upping to `-fsimpl-tick-factor=150`, the error is a little different: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone $ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 177190 }}} Upping to 200 makes the issue go away. We're building with `ghc-options: -fhpc` Before each build, we remove all .tix files and the .hpc directory At the point this error fires, we're compiling the 6th module of 9. The first 6 modules to compile only have a total of 635 lines of code. To address issues I've seen in other similar tickets: - There are no recursive module imports - We don't use any `{-# INLINE #-}` or similar pragmas - There is no Template Haskell other than a `makeLenses ''App` for a small Snaplet. - We don't have any "very"/exponentially recursive code - We don't use any unboxed tuples (there *is* ST code in a module that's compiled, but not the one ghc panics on) - We don't use type families - We don't use TypeRep or Typeable - We don't use Generic When this error occurs, it fails on a module which has very little code in it. It's mainly a list of ~200-300 Query[0] values, using OverloadedStrings. I notice Query's `mappend`, which we use, is `INLINE`d. Please let me know if I can provide more detail! [0] http://hackage.haskell.org/package/postgresql-simple-0.5.3.0/docs /Database-PostgreSQL-Simple-Types.html#t:Query -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): Thanks for reducing the test! I looked briefly at the 8.0.2 core-to-core output and it looks like we are seeing a great deal of simplification due to `bytestring`'s `Builder` mechanism. I also tested on 8.2.1 and it seems that the compiler is again able to simplify this program with the default ticks limit. That being said, we are still seeing a lot more builder things than I would expect in such a simple program, so I think a bit more investigation is in order. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2
-------------------------------------+-------------------------------------
Reporter: tom-bop | Owner: (none)
Type: bug | Status: infoneeded
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.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 bgamari):
So it looks like the issue here is that `Query`'s `fromString` instance
inlines:
{{{
Inlining done: Database.PostgreSQL.Simple.Types.$fIsStringQuery_g
Inlined fn: \ (x [Occ=Once] :: GHC.Base.String) ->
let {
cs :: Data.ByteString.Lazy.Internal.ByteString
[LclId]
cs
= Data.ByteString.Builder.toLazyByteString
(src

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): Actually, looking a bit closer, it seems that we may need to encode byte- by-byte due to UTF-8 encoding. However, it doesn't seem to me like we should be inlining this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 tom-bop): I've updated the repro case to not depend on the postgresql-simple library: Broken.hs: {{{ #!haskell {-# LANGUAGE OverloadedStrings #-} module Broken (breaks) where import Data.ByteString import Data.ByteString.Builder import Data.ByteString.Lazy (toStrict) import Data.String (IsString(..)) newtype Query = Query ByteString toByteString :: Builder -> ByteString toByteString x = toStrict (toLazyByteString x) instance IsString Query where fromString = Query . toByteString . stringUtf8 breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}} broken.cabal: {{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10 library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base , bytestring , bytestring-builder default-language: Haskell2010 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Changes (by LocutusOfBorg): * cc: costamagnagianfranco@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Description changed by tom-bop: Old description:
**Update**: I've been able to provide a much simpler test case for this error:
Broken.hs:
{{{ #!haskell {-# LANGUAGE OverloadedStrings #-}
module Broken (breaks) where
import Database.PostgreSQL.Simple.Types (Query)
breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}}
broken.cabal:
{{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10
library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base -- >=4.9 && <4.10 , postgresql-simple -- >=0.5 && <0.6 default-language: Haskell2010 }}}
`cabal install broken.cabal` results in:
{{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone ord To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 20731
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
----
----
**Older info:**
~~This is unfortunately a closed-source codebase I'm experiencing this with, but we get a GHC panic with a small/not-doing-anything-crazy codebase:~~
{{{
ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired Class op return To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 118123
}}}
When upping to `-fsimpl-tick-factor=150`, the error is a little different:
{{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone $ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 177190 }}}
Upping to 200 makes the issue go away.
We're building with
`ghc-options: -fhpc`
Before each build, we remove all .tix files and the .hpc directory
At the point this error fires, we're compiling the 6th module of 9. The first 6 modules to compile only have a total of 635 lines of code.
To address issues I've seen in other similar tickets: - There are no recursive module imports - We don't use any `{-# INLINE #-}` or similar pragmas - There is no Template Haskell other than a `makeLenses ''App` for a small Snaplet. - We don't have any "very"/exponentially recursive code - We don't use any unboxed tuples (there *is* ST code in a module that's compiled, but not the one ghc panics on) - We don't use type families - We don't use TypeRep or Typeable - We don't use Generic
When this error occurs, it fails on a module which has very little code in it. It's mainly a list of ~200-300 Query[0] values, using OverloadedStrings. I notice Query's `mappend`, which we use, is `INLINE`d.
Please let me know if I can provide more detail!
[0] http://hackage.haskell.org/package/postgresql-simple-0.5.3.0/docs /Database-PostgreSQL-Simple-Types.html#t:Query
New description: **Update 2**: repro case with fewer dependencies: Broken.hs: {{{ #!haskell {-# LANGUAGE OverloadedStrings #-} module Broken (breaks) where import Data.ByteString import Data.ByteString.Builder import Data.ByteString.Lazy (toStrict) import Data.String (IsString(..)) newtype Query = Query ByteString toByteString :: Builder -> ByteString toByteString x = toStrict (toLazyByteString x) instance IsString Query where fromString = Query . toByteString . stringUtf8 breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}} broken.cabal: {{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10 library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base , bytestring , bytestring-builder default-language: Haskell2010 }}} Errors with: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone pokeN_a1Db To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 22484 }}} ---- ---- **Update 1**: I've been able to provide a much simpler test case for this error: Broken.hs: {{{ #!haskell {-# LANGUAGE OverloadedStrings #-} module Broken (breaks) where import Database.PostgreSQL.Simple.Types (Query) breaks :: [(Query, Query)] breaks = [ ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") , ("query", "query") ] }}} broken.cabal: {{{ name: broken version: 0.1.0.0 build-type: Simple cabal-version: >=1.10 library exposed-modules: Broken other-extensions: OverloadedStrings build-depends: base -- >=4.9 && <4.10 , postgresql-simple -- >=0.5 && <0.6 default-language: Haskell2010 }}} `cabal install broken.cabal` results in: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone ord To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 20731 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} ---- ---- **Older info:** ~~This is unfortunately a closed-source codebase I'm experiencing this with, but we get a GHC panic with a small/not-doing-anything-crazy codebase:~~ {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired Class op return To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 118123 }}} When upping to `-fsimpl-tick-factor=150`, the error is a little different: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone $ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 177190 }}} Upping to 200 makes the issue go away. We're building with `ghc-options: -fhpc` Before each build, we remove all .tix files and the .hpc directory At the point this error fires, we're compiling the 6th module of 9. The first 6 modules to compile only have a total of 635 lines of code. To address issues I've seen in other similar tickets: - There are no recursive module imports - We don't use any `{-# INLINE #-}` or similar pragmas - There is no Template Haskell other than a `makeLenses ''App` for a small Snaplet. - We don't have any "very"/exponentially recursive code - We don't use any unboxed tuples (there *is* ST code in a module that's compiled, but not the one ghc panics on) - We don't use type families - We don't use TypeRep or Typeable - We don't use Generic When this error occurs, it fails on a module which has very little code in it. It's mainly a list of ~200-300 Query[0] values, using OverloadedStrings. I notice Query's `mappend`, which we use, is `INLINE`d. Please let me know if I can provide more detail! [0] http://hackage.haskell.org/package/postgresql-simple-0.5.3.0/docs /Database-PostgreSQL-Simple-Types.html#t:Query -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): Thanks tom-bop! What is happening here is that GHC is inlining the guts of `toStrict (toLazyByteString x)` into each call site of `fromString` (since this is what `bytestring` requests). In the case that we are calling `fromString` on a dynamically computed `String` this might make sense since we could possibly fuse the encoding logic and buffer write into the producer. However, in this particular case the `String` is a literal (that is, produced by `unpackCString#`). I really don't think there is any good reason to inline here. Moreover, in principle `Builder` should handle string literals with a simple `memcpy`. Unfortunately, it can't currently do this (easily) since string literals don't have an exposed size and we treat `'\0'` a bit funnily (encoding it as `'\xC0\x80'`, which the `memcpy` would need to undo). Ultimately I think the right solution would be to simply treat literals properly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11312 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #11312 Comment: #11312 has previously suggested that we introduce a distinct `String#` primitive type (potentially with a fixed length). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11312 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, I have opened a [[https://github.com/haskell/bytestring/pull/132|pull request]] against `bytestring` implementing a more efficient codepath for building string literals. I have confirmed that this new codepath easily fits under the tick limit when compiling the above testcase. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13960: Ticks exhausted with 8.0.2 -------------------------------------+------------------------------------- Reporter: tom-bop | Owner: (none) Type: bug | Status: upstream Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11312 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: infoneeded => upstream Comment: At this point we are waiting on `bytestring` upstream. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13960#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC