[GHC] #13255: aws package fails to build with master
GHC
ghc-devs at haskell.org
Wed Feb 15 15:30:09 UTC 2017
#13255: aws package fails to build with master
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: bgamari
Type: bug | Status: new
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I've managed the problem to isolate this smaller example:
{{{#!hs
module Bug where
-------------------------------------------------------------------------------
import qualified Data.ByteString.Base64 as Base64
import qualified Data.ByteString.Char8 as B
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
data DValue
= DBinary B.ByteString
| DBool Bool
| DBoolSet (S.Set Bool)
-------------------------------------------------------------------------------
class DynSize a where
dynSize :: a -> Int
instance DynSize DValue where
dynSize (DBool _) = 8
dynSize (DBoolSet s) = sum $ map (dynSize . DBool) $ S.toList s
dynSize (DBinary bs) = T.length . T.decodeUtf8 $ Base64.encode bs
}}}
You'll need to run `cabal install base64-bytestring text --enable-library-
profiling` beforehand. Then you can reproduce it like so:
{{{
$ ~/Software/ghc3/inplace/bin/ghc-stage2 -O2 -prof -fforce-recomp Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.1.20170213 for x86_64-unknown-linux):
completeCall
$wloop_length_s87d
Stop[BoringCtxt] Int# -> Int# -> Int
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1197:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1201:37 in
ghc:Outputable
pprPanic, called at compiler/simplCore/Simplify.hs:1598:9 in
ghc:Simplify
CallStack (from -prof):
SimplCore.SimplTopBinds (compiler/simplCore/SimplCore.hs:729:29-64)
SimplCore.Simplify (compiler/simplCore/SimplCore.hs:426:40-55)
HscMain.Core2Core (compiler/main/HscMain.hs:1170:7-42)
HscMain.hscSimplify' (compiler/main/HscMain.hs:(1167,1)-(1170,42))
HscMain.finish (compiler/main/HscMain.hs:(728,1)-(740,20))
HscMain.hscIncrementalCompile
(compiler/main/HscMain.hs:(639,1)-(694,32))
GhcMake.upsweep_mod.compile_it
(compiler/main/GhcMake.hs:(1380,13)-(1382,66))
GhcMake.upsweep_mod (compiler/main/GhcMake.hs:(1328,1)-(1482,49))
GhcMake.upsweep.upsweep' (compiler/main/GhcMake.hs:(1197,3)-(1296,91))
GhcMake.upsweep (compiler/main/GhcMake.hs:(1189,1)-(1296,91))
GhcMake.load'.upsweep_fn (compiler/main/GhcMake.hs:(351,9)-(352,41))
GhcMake.load'.checkHowMuch (compiler/main/GhcMake.hs:(233,9)-(235,27))
GhcMake.load' (compiler/main/GhcMake.hs:(210,1)-(439,38))
GhcMake.load (compiler/main/GhcMake.hs:(202,1)-(204,44))
GHC.withCleanupSession (compiler/main/GHC.hs:(450,1)-(459,37))
GHC.runGhc (compiler/main/GHC.hs:(425,1)-(430,26))
GHC.defaultErrorHandler (compiler/main/GHC.hs:(365,1)-(397,7))
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13255#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list