
#11594: closed empty type families fully applied get reduced lazily when in a constraint tuple and fully applied -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | 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 carter): the meat of it is i want the folllowing to not type check {{{ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies, TypeOperators #-} {-# LANGUAGE DataKinds, GADTs #-} {-# LANGUAGE TypeInType, ConstraintKinds #-} module MyLIbrary(sevenBad) where import GHC.Types (Constraint,TYPE,Levity(..)) -- these two only only report an error once I ---resolve the constraint on a to something like Int etc sevenBad :: (ClosedStuckSilly 'True , Num a) => a sevenBad = 7 type family ClosedStuckSilly (x :: a) :: b where }}} if i instead write something like {{{ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies, TypeOperators #-} {-# LANGUAGE DataKinds, GADTs #-} {-# LANGUAGE TypeInType, ConstraintKinds #-} module MyLIbrary(sevenBadWrapped) where import GHC.Types (Constraint,TYPE,Levity(..)) -- these two only only report an error once I resolve ---the constraint on a to something like Int etc sevenBad :: (ClosedStuckSilly 'True , Num a) => a sevenBad = 7 sevenBadWrapped :: Num a => a sevenBadWrapped = sevenBad type family ClosedStuckSilly (x :: a) :: b where }}} i'll get the type error i want, but that, I fear, wont scale very well in terms of usability for more complex codes -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11594#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler