[GHC] #16404: Type error recovery crash

GHC ghc-devs at haskell.org
Thu Mar 7 13:44:30 UTC 2019


#16404: Type error recovery crash
-------------------------------------+-------------------------------------
        Reporter:  simonpj           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.6.3
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Old description:

> 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 }
> }}}

New description:

 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 }
 }}}
 Without Lint it just squeezes by, because that `case typeError of ..."
 discards the "..." since it is unreachable

--

Comment (by simonpj):

 The breakage is worse for GHCi, with `-fdefer-type-errors`, because the
 `case (typeError "...") ...` transformation doesn't happen, so `f` is
 still there at the end:
 {{{
 ==================== Simplified expression ====================
 case Control.Exception.Base.typeError
        @ ('GHC.Types.TupleRep '[])
        @ ((* -> *) GHC.Prim.~# *)
        "<interactive>:2:9: 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_a1zL
 { __DEFAULT ->
 GHC.Base.returnIO
   @ [()]
   (GHC.Types.:
      @ ()
      (f_a1yP
       `cast` (UnsafeCo representational (forall a. a) ()
               :: (forall a. a) ~R# ()))
      (GHC.Types.[] @ ()))
 }
 }}}
 which leads to an outright crash.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16404#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list