Indeed, I hadn't come to use that at the type level; the original code used my own types which ended up holding LocalTime; I used Float as a simplification as it displayed the same weird behaviour.
I guess in the act of randomly walking parseable type family code I have inadvertently unearthed a bug, which someone else inadvertently fixed, making me a sort of human QuickCheck. On 22 Jul 2014 10:57, "Simon Peyton Jones" <simo...@microsoft.com> wrote: > I don't know why 7.6.3 accepts it. 'Float' is a valid type but not a > valid kind. For it to be a useful kind we'd need float literal at the type > level, and we have no such thing. You can use Nat instead, which does > exist at the type level. > > Simon > > | -----Original Message----- > | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- > | boun...@haskell.org] On Behalf Of cheater00 . > | Sent: 21 July 2014 18:51 > | To: glasgow-haskell-users@haskell.org > | Subject: Type family stopped compiling on upgrade from GHC 7.6.3 to > | 7.8.3 > | > | 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) > | _______________________________________________ > | Glasgow-haskell-users mailing list > | Glasgow-haskell-users@haskell.org > | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users