[GHC] #13960: Ticks exhausted with 8.0.2
GHC
ghc-devs at haskell.org
Wed Jul 12 14:49:38 UTC 2017
#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
More information about the ghc-tickets
mailing list