[GHC] #14608: Different GHCi error messages for similar scenarios
GHC
ghc-devs at haskell.org
Sat Dec 23 05:48:05 UTC 2017
#14608: Different GHCi error messages for similar scenarios
-------------------------------------+-------------------------------------
Reporter: mb64 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.2.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Poor/confusing
Unknown/Multiple | error message
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
With the following code:
{{{#!hs
{-# LANGUAGE UnboxedTuples #-}
module Test where
data UnboxedTupleData = MkUTD (# (),() #)
doThings :: UnboxedTupleData -> ()
doThings (MkUTD t) = ()
}}}
This is accepted and compiled with a simple `ghc --make Test.hs`. However,
with `ghci Test.hs`, you get an ugly error message:
{{{#!hs
GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Test ( Test.hs, interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 8.2.2 for x86_64-unknown-linux):
bcIdPrimRep
t_s1ro :: (# (), () #)
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:1133:58 in ghc:Outputable
callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in
ghc:Outputable
pprPanic, called at compiler/ghci/ByteCodeGen.hs:1582:5 in
ghc:ByteCodeGen
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Replacing `(MkUTD t)` with just `t` obtains a different error, with a
nicer message:
{{{#!hs
GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Test ( Test.hs, interpreted )
Error: bytecode compiler can't handle unboxed tuples and sums.
Possibly due to foreign import/export decls in source.
Workaround: use -fobject-code, or compile this module to .o separately.
}}}
True to its word, GHCi accepts it with `-fobject-code`, but it also
accepts the unwrapping one, with the worse error message, with `-fobject-
code`.
It only happens with unboxed tuples in GHCi: if you replace the unboxed
tuple with an unboxed int, GHCi will happily accept it. GHC cheerfully
compiles everything.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14608>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list