
#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