[GHC] #11990: Custom Type Error not getting triggered in the nested Type function call
GHC
ghc-devs at haskell.org
Tue Jun 27 19:41:40 UTC 2017
#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
More information about the ghc-tickets
mailing list