[GHC] #16404: Type error recovery crash

#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

#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: | -------------------------------------+------------------------------------- Comment (by simonpj): Reason for this: this code in `TcBinds` {{{ tcPolyBinds sig_fn prag_fn rec_group rec_tc closed bind_list = setSrcSpan loc $ recoverM (recoveryCode binder_names sig_fn) $ do -- Set up main recover; take advantage of any type sigs }}} recovers from an error in the binding for `f`. But the recovery code is: {{{ recoveryCode :: [Name] -> TcSigFun -> TcM (LHsBinds GhcTcId, [Id]) recoveryCode binder_names sig_fn = do { traceTc "tcBindsWithSigs: error recovery" (ppr binder_names) ; let poly_ids = map mk_dummy binder_names ; return (emptyBag, poly_ids) } }}} That is, it returns no bindings. That's probably wrong if we have `-fdefer-type-errors`. We should probably generate a stub binding {{{ f = typeError "Deferred error in binding for f" }}} That would avoid downstream breakage. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16404#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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: | -------------------------------------+------------------------------------- Comment (by simonpj): My conclusions: * Add a stub binding in `TcBinds.recoveryCode` * Maybe the case-of-error transformation happen even in GHCi. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16404#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC