[GHC] #15325: Panic in getIdFromTrivialExpr with -fdefer-type-errors
GHC
ghc-devs at haskell.org
Sat Jun 30 14:38:12 UTC 2018
#15325: Panic in getIdFromTrivialExpr with -fdefer-type-errors
-------------------------------------+-------------------------------------
Reporter: dramforever | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
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:
-------------------------------------+-------------------------------------
== Steps to reproduce:
Put this in `bug.hs`: (It's a very failed attempt to make a polymorphic
list maker function.)
{{{#!hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module PolyvariadicFunctions where
class PolyList e a where
polyList :: ([e] -> [e]) -> a
-- instance PolyList e [e] where
-- polyList dl = dl []
instance (e ~ e2, PolyList e a) => PolyList e (e2 -> a) where
polyList dl x = polyList ((x :) . dl)
plh :: [Integer]
plh = polyList 1 2 3 4 5
}}}
Load it in GHCi with `-fdefer-type-errors` to get the following output.
Note the 'panic' in the end, and also note that the last `>` line is a no-
module-loaded GHCi prompt.
The question marks `?` seem to be encoding related and not relevant.
This panic not seem to occur with GHC the compiler. The rest of the error
messages seem otherwise identical.
{{{
GHCi, version 8.4.3: http://www.haskell.org/ghc/ :? for help
Prelude> :set -fdefer-type-errors
Prelude> :l bug.hs
[1 of 1] Compiling PolyvariadicFunctions ( bug.hs, interpreted )
bug.hs:17:7: warning: [-Wdeferred-type-errors]
? No instance for (PolyList t0 [Integer])
arising from a use of ‘polyList’
? In the expression: polyList 1 2 3 4 5
In an equation for ‘plh’: plh = polyList 1 2 3 4 5
|
17 | plh = polyList 1 2 3 4 5
| ^^^^^^^^^^^^^^^^^^
bug.hs:17:16: warning: [-Wdeferred-type-errors]
? No instance for (Num ([t0] -> [t0])) arising from the literal ‘1’
(maybe you haven't applied a function to enough arguments?)
? In the first argument of ‘polyList’, namely ‘1’
In the expression: polyList 1 2 3 4 5
In an equation for ‘plh’: plh = polyList 1 2 3 4 5
|
17 | plh = polyList 1 2 3 4 5
| ^
bug.hs:17:18: warning: [-Wdeferred-type-errors]
? Ambiguous type variable ‘t0’ arising from the literal ‘2’
prevents the constraint ‘(Num t0)’ from being solved.
Probable fix: use a type annotation to specify what ‘t0’ should be.
These potential instances exist:
instance Num Integer -- Defined in ‘GHC.Num’
instance Num Double -- Defined in ‘GHC.Float’
instance Num Float -- Defined in ‘GHC.Float’
...plus two others
(use -fprint-potential-instances to see them all)
? In the second argument of ‘polyList’, namely ‘2’
In the expression: polyList 1 2 3 4 5
In an equation for ‘plh’: plh = polyList 1 2 3 4 5
|
17 | plh = polyList 1 2 3 4 5
| ^
ghc.exe: panic! (the 'impossible' happened)
(GHC version 8.4.3 for x86_64-unknown-mingw32):
getIdFromTrivialExpr
case $dNum_a1Be of wild_00 { }
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler\utils\Outputable.hs:1150:37 in
ghc:Outputable
pprPanic, called at compiler\\coreSyn\\CoreUtils.hs:883:18 in
ghc:CoreUtils
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15325>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list