Kind classes and associated closed type families

Thanks to Richard's hard work, I can now define kind classes! class Extractable k where type Extract (n :: Nat) (x :: k) :: y (For context, Extract is something roughly resembling the X type family in the paper Generic Programming for Indexed Datatypes. [1]) This is really, really cool. Except that when I tried using this class, I quickly ran into issues: instance Extractable (a, b) where type Extract 0 '(l, _) = l type Extract 1 '(_, r) = r type Extract _ _ = TypeError ('Text "out of bounds") This yields the error: Extractable.hs:16:8: error: Conflicting family instance declarations: forall a b (r :: b) (_ :: a). Extract 1 '(_, r) = r -- Defined at Extractable.hs:16:8 forall a b (_ :: Nat) (_1 :: (a, b)) y. Extract _ _1 = (TypeError ...) -- Defined at Extractable.hs:17:8 It hit me as to why: GHC is interpreting each Extract type instance as being separate from each other, not as a part of a single, closed type family over kind (a, b). And as it turns out, GHC does not allow closed associated type families. [2] That leads me to wonder: is there a particular reason why GHC couldn't allow closed associated type families? Because of this restriction, I have to define the Extractable (a, b) instance like this: instance Extractable (a, b) where type Extract n p = ExtractPair n p type family ExtractPair (n :: Nat) (x :: (a, b)) :: y where ExtractPair 0 '(a, _) = a ExtractPair 1 '(_, b) = b ExtractPair _ _ = TypeError ('Text "out of bounds") But that requires -XUndecidableInstances, and makes it much more difficult to examine type family reductions with GHCi's :kind! command. Ryan S. ----- [1] http://dreixel.net/research/pdf/gpid.pdf [2] https://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#syno...

On Dec 18, 2015, at 1:37 PM, Ryan Scott
It hit me as to why: GHC is interpreting each Extract type instance as being separate from each other, not as a part of a single, closed type family over kind (a, b). And as it turns out, GHC does not allow closed associated type families. [2]
Yes, that's exactly right.
That leads me to wonder: is there a particular reason why GHC couldn't allow closed associated type families?
No. At the time, we thought that associated closed type families are easy enough to build (as you do here) and just one more wrinkle that GHC didn't need. No theoretical trouble at all. Just some routine engineering, I imagine.
Because of this restriction, I have to define the Extractable (a, b) instance like this:
instance Extractable (a, b) where type Extract n p = ExtractPair n p
type family ExtractPair (n :: Nat) (x :: (a, b)) :: y where ExtractPair 0 '(a, _) = a ExtractPair 1 '(_, b) = b ExtractPair _ _ = TypeError ('Text "out of bounds")
But that requires -XUndecidableInstances, and makes it much more difficult to examine type family reductions with GHCi's :kind! command.
Why does this interfere with :kind! ? It shouldn't. (Yes, the -XUndecidableInstances is regrettable. We really need a better type-level termination checker. Care to write one? :) ) Richard
Ryan S. ----- [1] http://dreixel.net/research/pdf/gpid.pdf [2] https://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#syno... _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Why does this interfere with :kind! ? It shouldn't.
Well, it seems to interfere in my usage of it, at least:
:kind! Extract 0 '(Int, Char) Extract 0 '(Int, Char) :: y = ExtractPair 0 '(Int, Char)
I presumed this was because :kind! didn't do any type family reduction
whenever something was undecidable in general (to ensure :kind! always
terminates, I suppose).
Ryan S.
On Fri, Dec 18, 2015 at 10:56 AM, Richard Eisenberg
On Dec 18, 2015, at 1:37 PM, Ryan Scott
wrote: It hit me as to why: GHC is interpreting each Extract type instance as being separate from each other, not as a part of a single, closed type family over kind (a, b). And as it turns out, GHC does not allow closed associated type families. [2]
Yes, that's exactly right.
That leads me to wonder: is there a particular reason why GHC couldn't allow closed associated type families?
No. At the time, we thought that associated closed type families are easy enough to build (as you do here) and just one more wrinkle that GHC didn't need. No theoretical trouble at all. Just some routine engineering, I imagine.
Because of this restriction, I have to define the Extractable (a, b) instance like this:
instance Extractable (a, b) where type Extract n p = ExtractPair n p
type family ExtractPair (n :: Nat) (x :: (a, b)) :: y where ExtractPair 0 '(a, _) = a ExtractPair 1 '(_, b) = b ExtractPair _ _ = TypeError ('Text "out of bounds")
But that requires -XUndecidableInstances, and makes it much more difficult to examine type family reductions with GHCi's :kind! command.
Why does this interfere with :kind! ? It shouldn't. (Yes, the -XUndecidableInstances is regrettable. We really need a better type-level termination checker. Care to write one? :) )
Richard
Ryan S. ----- [1] http://dreixel.net/research/pdf/gpid.pdf [2] https://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#syno... _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Dec 18, 2015, at 2:03 PM, Ryan Scott
I presumed this was because :kind! didn't do any type family reduction whenever something was undecidable in general (to ensure :kind! always terminates, I suppose).
No. :kind! isn't that smart. Out of curiosity, what happens if you try again? As in, run :kind! ... twice, exactly the same both times. I seem to recall a ticket saying that worked. Regardless, this is just a plain old bug. Please post a report. Thanks! Richard

Running :kind! twice in a row does nothing, and your hunch was correct: it does appear to be a bug. Specifically, it's a bug that affects type families with polymorphic return kinds (like Extract, which has kind y). I've opened Trac #11275 [1] for this issue. Ryan S. ----- [1] https://ghc.haskell.org/trac/ghc/ticket/11275

...actually, nevermind, it's not a bug after all. It was just me being boneheaded. Since Extract has a polymorphic return kind, there's no way for GHCi to know what the kind of Extract 0 '(Int, Char) will be unless there's a kind ascription. If you be more explicit, then GHCi knows what to do: > :kind! (Extract 0 '(Int, Char) :: *) (Extract 0 '(Int, Char) :: *) :: * = Int > :kind! (Extract 0 '(Int, Char) :: * -> *) (Extract 0 '(Int, Char) :: * -> *) :: * -> * = (TypeError ...) Thanks to Reid Barton for pointing this out to me. Ryan S. ----- [1] https://ghc.haskell.org/trac/ghc/ticket/10116
participants (2)
-
Richard Eisenberg
-
Ryan Scott