
#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 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've the following small example {{{ {-# LANGUAGE MagicHash, UnboxedSums, NoImplicitPrelude #-} {-# LANGUAGE TypeFamilies #-} -- {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE GADTs ,ExplicitNamespaces#-} {-# LANGUAGE UnboxedTuples #-} module Data.Unboxed.Maybe where import GHC.Exts import GHC.Types import Prelude (undefined) import Data.Void data family Maybe(x :: TYPE (r :: RuntimeRep)) data instance Maybe (a :: * ) where MaybeSum :: (# a | (# #) #) -> Maybe a data instance Maybe (x :: TYPE 'UnliftedRep) where MaybeSumU :: (# x | (# #) #) -> Maybe x }}} and then i get the error (made much saner to read by use of printing explicit kinds) {{{ Prelude> :r [1 of 1] Compiling Data.Unboxed.Maybe ( src/Data/Unboxed/Maybe.hs, interpreted ) src/Data/Unboxed/Maybe.hs:22:3: error: • Data constructor ‘MaybeSumU’ returns type ‘Maybe 'LiftedRep x’ instead of an instance of its parent type ‘Maybe 'UnliftedRep x’ • In the definition of data constructor ‘MaybeSumU’ In the data instance declaration for ‘Maybe’ | 22 | MaybeSumU :: (# x | (# #) #) -> Maybe x }}} this is a) a case where printing runtime reps makes things easier to debug :) b) a very confusing type error since the data instance clearly says "x :: TYPE 'UnliftedRep " is there something i'm overlooking, or is this a bug? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14111 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler