[GHC] #16404: Type error recovery crash
GHC
ghc-devs at haskell.org
Thu Mar 7 13:09:38 UTC 2019
#16404: Type error recovery crash
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This program is derived from #16376:
{{{
{-# LANGUAGE TypeApplications #-}
module Bug where
h x = let f = id @Maybe
in Just f
}}}
If you compile with `-fdefer-type-errors -dcore-lint` you'll get
{{{
*** Core Lint errors : in result of Desugar (before optimization) ***
<no location info>: warning:
In the expression: f_arZ @ a_at1
Out of scope: f_arZ :: forall a. a
[LclId]
*** Offending Program ***
Rec {
$trModule :: Module
[LclIdX]
$trModule = Module (TrNameS "main"#) (TrNameS "T16376"#)
h :: forall p a. p -> Maybe a
[LclIdX]
h = \ (@ p_asV) (@ a_at1) ->
case typeError
@ ('TupleRep '[])
@ ((* -> *) ~# *)
"T16376.hs:4:19: error:\n\
\ \\226\\128\\162 Expecting one more argument to
\\226\\128\\152Maybe\\226\\128\\153\n\
\ Expected a type, but
\\226\\128\\152Maybe\\226\\128\\153 has kind \\226\\128\\152* ->
*\\226\\128\\153\n\
\ \\226\\128\\162 In the type
\\226\\128\\152Maybe\\226\\128\\153\n\
\ In the expression: id @Maybe\n\
\ In an equation for \\226\\128\\152f\\226\\128\\153: f
= id @Maybe\n\
\(deferred type error)"#
of co_asZ
{ __DEFAULT ->
letrec {
h_at5 :: p_asV -> Maybe a_at1
[LclId]
h_at5 = \ (x_arY :: p_asV) -> Just @ a_at1 (f_arZ @ a_at1); } in
h_at5
}
end Rec }
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16404>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list