Type family stopped compiling on upgrade from GHC 7.6.3 to 7.8.3

cheater00 . cheater00 at gmail.com
Mon Jul 21 17:51:07 UTC 2014


Hi, I was experimenting a bit with type families recently and ran into
a bit of an issue. Given that I don't know type families that well
yet, I was wondering if I made an error somewhere. One thing is that I
can't find any relevant changes in the GHC release notes for 7.8.1, .2
or .3.

Maybe this code contains an error which 7.6.3 simply wasn't able to find?

Thanks.

--------

-- this code compiles in 7.6.3, but breaks in 7.8.3 with the following message:
-- TypeFamilies.hs:14:31:
--     ‘End’ of kind ‘*’ is not promotable
--     In the kind ‘End’
-- In 7.6.3, using :kind!, I can see that the type synonyms contained
in the family do work the way I intend them to.


{-# Language
    GADTs
  , TypeFamilies
  , DataKinds
   #-}
module TypeFamilies where

data End = Least | Spot Float | Most
  deriving (Eq, Show)

data Interval = IntervalCons { left :: End, right :: End }
  deriving (Eq, Show)

type family   Interval2 (a :: End) (b :: End) :: Interval
type instance Interval2  Least      Most      =  IntervalCons  Least    Most
type instance Interval2 (Spot l)    Most      =  IntervalCons (Spot l)  Most
type instance Interval2  Least     (Spot r)   =  IntervalCons  Least   (Spot r)
type instance Interval2 (Spot l)   (Spot r)   =  IntervalCons (Spot l) (Spot r)


More information about the Glasgow-haskell-users mailing list