STG lint panic
While attempting to build thyme
from Hackage with core, stg, and cmm linting and -O2 enabled, GHC crashed with an internal panic. See attached terminal log.
rrdhcp-10-32-234-247:thyme-0.2.4.1 Alexander$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.6.3
rrdhcp-10-32-234-247:thyme-0.2.4.1 Alexander$ cabal --version
cabal-install version 1.16.0.2
using version 1.16.0 of the Cabal library
rrdhcp-10-32-234-247:thyme-0.2.4.1 Alexander$ which ghc
/usr/local/bin/ghc
rrdhcp-10-32-234-247:thyme-0.2.4.1 Alexander$ which cabal
/Users/Alexander/Library/Haskell/bin/cabal
Trac metadata
Trac field | Value |
---|---|
Version | 7.6.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | MacOS X |
Architecture | x86_64 (amd64) |
- Show closed items
Relates to
- #53455
Activity
-
Newest first Oldest first
-
Show all activity Show comments only Show history only
- Alexander Altman changed weight to 5
changed weight to 5
- Alexander Altman added Tbug Trac import labels
added Tbug Trac import labels
- Author
Attached file
log.zip
(download).terminal log (compressed)
- Developer
As far as I can tell, the origin of the STG Lint error is Data.Text.Array in the text package.
Here's the crucial part of that module. To reproduce, save this code as Array.hs and compile with
ghc -dstg-lint Array
. This gives a Lint error in 7.6.3 and HEAD.{-# LANGUAGE MagicHash, RecordWildCards, UnboxedTuples #-} module Array where import GHC.Base (ByteArray#, MutableByteArray#, unsafeCoerce#) import GHC.ST (ST(..), runST) data Array = Array { aBA :: ByteArray# } data MArray s = MArray { maBA :: MutableByteArray# s } unsafeFreeze :: MArray s -> ST s Array unsafeFreeze MArray{..} = ST $ \s# -> (# s#, Array (unsafeCoerce# maBA) #)
- Developer
the lint error message (using the minimal example that monoidal provides), on ghc 7.6.3 on OS X is the following
carter repoScratcher/testtyme » ghc -dstg-lint Array [1 of 1] Compiling Array ( Array.hs, Array.o ) stgEqType: unequal ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv h} [tv] ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-apple-darwin): *** Stg Lint ErrMsgs: in Stg2Stg *** <no location info>: Warning: [RHS of sat_sgA{v} [lid] :: main:Array.Array{tc rfc}] In a RHS constructor application, con type doesn't match arg types: Constructor type: ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} -> main:Array.Array{tc rfc} Arg types: ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv h} [tv] *** Offending Program *** main:Array.unsafeFreeze{v rff} [gid] :: forall s{tv afh} [tv]. main:Array.MArray{tc rf9} s{tv afh} [tv] -> base:GHC.ST.ST{tc r4k} s{tv afh} [tv] main:Array.Array{tc rfc} [GblId, Arity=1, Unf=OtherCon []] = [] \r srt:SRT:[(01Z, base:GHC.Base.${v 01Z} [gid])] [ds{v sgf} [lid]] case ds{v sgf} [lid] :: Alg main:Array.MArray{tc rf9} of (wild{v sgD} [lid] [Occ=Dead] :: main:Array.MArray{tc rf9} s{tv h} [tv]) { -- lvs: [ds{v sgf} [lid]]; rhs lvs: []; srt:SRT:[(01Z, base:GHC.Base.${v 01Z} [gid])] main:Array.MArray{d rfa} (ds1{v sgn} [lid] :: ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv h} [tv]) -> let { sat_sgB{v} [lid] :: base:GHC.ST.STRep{tc r4i} s{tv h} [tv] main:Array.Array{tc rfc} [LclId] = [ds1{v sgn} [lid]] \r srt:SRT:[] [s#{v sgm} [lid]] let { sat_sgA{v} [lid] :: main:Array.Array{tc rfc} [LclId] = NO_CCS main:Array.Array{d rfd}! [ds1{v sgn} [lid]]; } in ghc-prim:GHC.Prim.(#,#){(w) d 84} [s#{v sgm} [lid] sat_sgA{v} [lid]]; } in let { sat_sgC{v} [lid] :: base:GHC.ST.STRep{tc r4i} s{tv h} [tv] main:Array.Array{tc rfc} -> base:GHC.ST.ST{tc r4k} s{tv h} [tv] main:Array.Array{tc rfc} [LclId] = [] \r srt:SRT:[] [tpl{v sgj} [lid]] tpl{v sgj} [lid]; } in base:GHC.Base.${v 01Z} [gid] sat_sgC{v} [lid] sat_sgB{v} [lid]; }; main:Array.aBA{v rfe} [gid[[RecSel]]] :: main:Array.Array{tc rfc} -> ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} [GblId[[RecSel]], Arity=1, Caf=NoCafRefs, Unf=OtherCon []] = [] \r srt:SRT:[] [ds{v sgr} [lid]] case ds{v sgr} [lid] :: Alg main:Array.Array{tc rfc} of (wild{v sgE} [lid] [Occ=Dead] :: main:Array.Array{tc rfc}) { -- lvs: [ds{v sgr} [lid]]; rhs lvs: []; srt:SRT:[] main:Array.Array{d rfd} (ds1{v sgu} [lid] :: ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f}) -> ds1{v sgu} [lid]; }; main:Array.maBA{v rfb} [gid[[RecSel]]] :: forall s{tv afg} [tv]. main:Array.MArray{tc rf9} s{tv afg} [tv] -> ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv afg} [tv] [GblId[[RecSel]], Arity=1, Caf=NoCafRefs, Unf=OtherCon []] = [] \r srt:SRT:[] [ds{v sgw} [lid]] case ds{v sgw} [lid] :: Alg main:Array.MArray{tc rf9} of (wild{v sgF} [lid] [Occ=Dead] :: main:Array.MArray{tc rf9} s{tv d} [tv]) { -- lvs: [ds{v sgw} [lid]]; rhs lvs: []; srt:SRT:[] main:Array.MArray{d rfa} (ds1{v sgz} [lid] :: ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv d} [tv]) -> ds1{v sgz} [lid]; }; main:Array.MArray{v rfr} [gid[DataCon]] :: forall s{tv afg} [tv]. ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv afg} [tv] -> main:Array.MArray{tc rf9} s{tv afg} [tv] [GblId[DataCon], Arity=1, Caf=NoCafRefs, Str=DmdType Tm, Unf=OtherCon []] = [] \r srt:SRT:[] [eta_B1{v} [lid]] main:Array.MArray{d rfa} [eta_B1{v} [lid]]; main:Array.Array{v rfn} [gid[DataCon]] :: ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} -> main:Array.Array{tc rfc} [GblId[DataCon], Arity=1, Caf=NoCafRefs, Str=DmdType Tm, Unf=OtherCon []] = [] \r srt:SRT:[] [eta_B1{v} [lid]] main:Array.Array{d rfd} [eta_B1{v} [lid]]; *** End of Offense *** Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
- Developer
the meat of the error message is
stgEqType: unequal ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv h} [tv] ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-apple-darwin): *** Stg Lint ErrMsgs: in Stg2Stg *** <no location info>: Warning: [RHS of sat_sgA{v} [lid] :: main:Array.Array{tc rfc}] In a RHS constructor application, con type doesn't match arg types: Constructor type: ghc-prim:GHC.Prim.ByteArray#{(w) tc 3f} -> main:Array.Array{tc rfc} Arg types: ghc-prim:GHC.Prim.MutableByteArray#{(w) tc 31p} s{tv h} [tv]
- Developer
See also Simon's comment at #5345 (closed).
- Thomas Miedema changed title from {-GHC panic when building
thyme
-} to STG lint panicchanged title from {-GHC panic when building
thyme
-} to STG lint panic Confirmed on Linux with ghc-7.9.20141115 using example from ticket:8114#comment:72942.
Trac metadata
Trac field Value Related → #5345 (closed) Operating system MacOS X → Unknown/Multiple Architecture x86_64 (amd64) → Unknown/Multiple - Maintainer
Apart from the STG lint issue (which I really can't comment on), it's not clear to me why
text
is usingunsafeCoerce#
here instead ofunsafeFreezeByteArray#
, which seems to pre-dateData.Text.Array
. - Maintainer
Indeed reworking the code in question to use
unsafeFreezeByteArray#
resolves the STG lint violation. I've opened a pull request againsttext
fixing this.Given that this issue is only observed with
unsafeCoerce#
and STG linting is already a bit sketchy, I'm going to close this as won't fix.Thanks for your report!
- Ben Gamari closed
closed
- Maintainer
Trac metadata
Trac field Value Resolution Unresolved → ResolvedWon'tFix - trac-import added compiler crash label
added compiler crash label
- Ben Gamari added Pnormal label
added Pnormal label