[GHC] #11990: Custom Type Error not getting triggered in the nested Type function call

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 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: -------------------------------------+------------------------------------- I have partial type function which is invoked by another type function. When the inner type function fails with TypeError, outer type function is not been able to propagate that type error to its caller. As a result of it, I'm getting following error • No instance for (KnownSymbol (NestedPartialTF (TypeError ...))) instead of • Unexpected type @ NestedPartialTF: Char {{{#!hs {-# LANGUAGE DataKinds, TypeOperators, TypeFamilies, UndecidableInstances, ScopedTypeVariables, FlexibleContexts #-} -- | module CErrs where import GHC.TypeLits import Data.Proxy type family PartialTF t :: Symbol where PartialTF Int = "Int" PartialTF Bool = "Bool" PartialTF a = TypeError (Text "Unexpected type @ PartialTF: " :<>: ShowType a) type family NestedPartialTF (tsym :: Symbol) :: Symbol where NestedPartialTF "Int" = "int" NestedPartialTF "Bool" = "bool" NestedPartialTF a = TypeError (Text "Unexpected type @ NestedPartialTF: " :<>: ShowType a) testPartialTF :: forall a.(KnownSymbol (PartialTF a)) => a -> String testPartialTF t = symbolVal (Proxy :: Proxy (PartialTF a)) --t1 = testPartialTF 'a' {- Above code rightly fails with the following error: • Unexpected type: Char • In the expression: testPartialTF 'a' In an equation for ‘t1’: t1 = testPartialTF 'a' -} -- Bug? testNesPartialTF :: forall a.(KnownSymbol (NestedPartialTF (PartialTF a))) => a -> String testNesPartialTF t = symbolVal (Proxy :: Proxy (NestedPartialTF (PartialTF a))) t2 = testNesPartialTF 'a' {- Above code fails with the following error: • No instance for (KnownSymbol (NestedPartialTF (TypeError ...))) arising from a use of ‘testNesPartialTF’ • In the expression: testNesPartialTF 'a' In an equation for ‘t2’: t2 = testNesPartialTF 'a' -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 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: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: 8.0.1 => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call
-------------------------------------+-------------------------------------
Reporter: magesh.b | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1-rc3
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 Ben Gamari

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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: | -------------------------------------+------------------------------------- Changes (by magesh.b): * Attachment "MutiCE.hs" added. MultipleCustomErrors -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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 magesh.b):
If there are multiple `TypeErrors`, then we just report one of them.
Consider the following class, whose instance has a contrived TypeError {{{ class ShowHL (xs :: [*]) where showHL :: HList xs -> String instance (Show x, ShowHL xs, TypeError (ShowType x)) => ShowHL (x ': xs) where showHL (x :& xs) = show x ++ showHL xs }}} The error message emitted when this type class method is called with **showHL ('a' :& True :& Nil)** contains all the errors in one shot. This behavior is very useful and would this be retained after this fix? {{{ MutiCE.hs:26:8: error: • Bool • In the expression: showHL testRec In an equation for ‘test’: test = showHL testRec MutiCE.hs:26:8: error: • Char • In the expression: showHL testRec In an equation for ‘test’: test = showHL testRec Failed, modules loaded: none. }}} I have attached the full source code which contains the test case for this behaviour -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: merge => new -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => diatchki -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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 diatchki): Hello, sorry for the slow response---I didn't see this before. The current version does exactly what you've pasted so we are OK. Basically, each `TypeError` constraint becomes its own type error, and all of those should be reported as before. The comment about "picking just one type error" was referring to when a single type contains multiple errors. For example, consider the following: {{{ g :: Proxy '[ TypeError (Text "A"), TypeError (Text "B") ] g = Proxy }}} This will generate just one of the type errors. I am not sure if it might be better to generate all of them anyway, or if that would result in too many spurious errors... Even though your example works at the moment, it relies on a specific behavior of the GHC constraint solver that may change in the future. In particular, currently GHC continues to reduce constraints, even though it found a constraint that is impossible to solve (i.e., the `TypeError`). If GHC was to become "lazier" in the future, you would only see one of those errors. A more robust way to get the same behavior would be to write a type function/class that analyzes the type and constructs an error message containing everything that went wrong, and then emitting just one type error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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 bgamari): For the record the patch in comment:3 was merged to `ghc-8.0` as 23be8c99a411f846ae7668682259bcad2a507122. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: From comment:7 it would seem that there isn't really a bug here, merely implementation details that could be improved in the future. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | 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 tstr): Hi, for the example blow I'm wondering why GHC 8.0.2 fails on "TestError" with a custom type error, but at the same time happily accepts "NestedTypeError"? Is that the expected behavior of GHC? Many thanks for your help, Thomas {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module CustomErrorBug where import GHC.TypeLits -- Works as expected and makes GHC complain: type TestError = TypeError (Text "Top level custom errors work!") -- GHC 8.0.2 is absolutely happy with this: type family NestedError (x::Symbol) where NestedError x = TypeError (Text "NestedError: " :<>: ShowType x) type TestNestedError = NestedError "Why are nested custom errors not propagated?" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by tstr): * cc: tstr (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11990#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC