
#14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies 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 RyanGlScott): * keywords: => TypeFamilies Comment: One important to note is that in this data instance: {{{#!hs data instance Maybe (x :: TYPE 'UnliftedRep) where MaybeSumU :: (# x | (# #) #) -> Maybe x }}} The `x` in `data instance Maybe (x :: TYPE 'UnliftedRep)` does //not// scope over the constructors (this is a quirk of GADTs). Therefore, the kind of `x` in `data instance Maybe (x :: TYPE 'UnliftedRep)` doesn't necessarily determine the kind of `x` in `MaybeSumU`'s type signature (as the `x` in `(# x | (# #) #) -> Maybe x` is bound by an implicit `forall x`). That being said, I'm still surprised this doesn't typecheck. Here's a simpler example of this bug that doesn't involve levity polymorphism or `TypeInType`: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module Bug where data family F (a :: k) data instance F (a :: Bool) where MkF :: F a }}} {{{ $ ~/Software/ghc3/inplace/bin/ghc-stage2 --interactive Bug.hs GHCi, version 8.3.20170807: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:3: error: • Data constructor ‘MkF’ returns type ‘F a’ instead of an instance of its parent type ‘F a’ • In the definition of data constructor ‘MkF’ In the data instance declaration for ‘F’ | 9 | MkF :: F a | ^ Failed, 0 modules loaded. λ> :set -fprint-explicit-kinds λ> :r [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:3: error: • Data constructor ‘MkF’ returns type ‘F k a’ instead of an instance of its parent type ‘F Bool a’ • In the definition of data constructor ‘MkF’ In the data instance declaration for ‘F’ | 9 | MkF :: F a | ^ Failed, 0 modules loaded. }}} Here's we can see that since `a` appears unadorned in `F a`, its kind seems to be inferred as `k` (as given from the data family definition), although we'd much rather have it inferred as `Bool`, which you'd expect from the instance head. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14111#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler