[GHC] #14458: ghc: panic! -- initTc: unsolved constraints
GHC
ghc-devs at haskell.org
Sun Nov 12 22:28:18 UTC 2017
#14458: ghc: panic! -- initTc: unsolved constraints
-------------------------------------+-------------------------------------
Reporter: lijero | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Keywords: | Operating System: Linux
Architecture: x86_64 | Type of failure: Compile-time
(amd64) | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
So this is an interesting bug. If I mistype parse' as parse, /and/ do not
have main defined, the error occurs, but not with either individual one.
I'm sure the code sucks, but I wasn't intending for this to end up
anywhere, it just happened to trigger the crash.
{{{
lijero at desktop:~/code/ab$ ghc AB.hs
[1 of 1] Compiling Main ( AB.hs, AB.o )
ghc: panic! (the 'impossible' happened)
(GHC version 8.0.2 for x86_64-unknown-linux):
initTc: unsolved constraints
WC {wc_insol =
[W] parse_ay8 :: t_ay7[tau:1] (CHoleCan: parse)
[W] parse_ayp :: t_ayo[tau:1] (CHoleCan: parse)}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
{{{#!hs
module Main where
data Token = KUnit
| KApp
| KLam
| KVar String
data Ast = AUnit
| AApp Ast Ast
| ALam Ast Ast
| AVar String
parse' :: [Token] -> ([Token] -> Ast -> Maybe Ast) -> Maybe Ast
parse' (KUnit:xs) fail = fail xs AUnit
-- GHC does not crash when parse is correctly written parse' in both of
the below instances
parse' (KApp:xs) fail =
parse' xs (\ xs' f -> AApp f <$> parse xs' fail)
parse' (KLam:xs) fail =
parse' xs (\ xs' a -> ALam a <$> parse xs' fail)
parse' (KVar n:xs) fail = fail xs (AVar n)
-- GHC does not crash when main is defined
--main :: IO ()
--main = putStrLn ""
}}}
With main defined, GHC correctly reports "variable not in scope".
With parse corrected to parse', GHC correctly reports that main is not
defined.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14458>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list