8

While I was going through the haskell-excercises questions. I saw the following code which creates an aggregate Constraint by applying each type to a Constraint constructor. In GHC it seems deeply nested tuples of Constraints are still of kind Constraint (perhaps flattened ?).

{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE PolyKinds     #-}
{-# LANGUAGE TypeFamilies  #-}
{-# LANGUAGE TypeOperators #-}


type family All (c :: Type -> Constraint) (xs :: [Type]) :: Constraint where
  All c '[] = ()
  All c (x ': xs) = (c x, All c xs)

-- >>> :kind! All
-- All :: (* -> Constraint) -> [*] -> Constraint
-- = All

-- >>> :kind! All Eq '[Int, Double, Float]
-- All Eq '[Int, Double, Float] :: Constraint
-- = (Eq Int, (Eq Double, (Eq Float, () :: Constraint)))

I tried to generalize it using PolyKinds extension as following.

{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE PolyKinds     #-}
{-# LANGUAGE TypeFamilies  #-}
{-# LANGUAGE TypeOperators #-}


type family All' (c :: k -> r) (xs :: [k]) :: r where
  All' c '[] = ()
  All' c (x ': xs) = (c x, All' c xs)

-- >>> :kind! All'
-- All' :: (k -> r) -> [k] -> r
-- = All'

--- This one works. Tuples of Types is a Type.
-- >>> :kind! All' Maybe '[Int, Double, Float]
-- All' Maybe '[Int, Double, Float] :: *
-- = (Maybe Int, (Maybe Double, (Maybe Float, ())))

--- However this one gets stuck.
-- >>> :kind! All' Eq '[Int, Double, Float]
-- All' Eq '[Int, Double, Float] :: Constraint
-- = All' Eq '[Int, Double, Float]

Is the kind of '(,) (a :: k) (b :: k) also of kind k. Looking below it doesn't seems so, so I wonder why the type family definition All' c (x ': xs) = (c x, All' c xs) was accepted in the first place (considering the type family return kind was r)?

λ> :kind! '(,)
'(,) :: a -> b -> (a, b)
= '(,)

λ> :kind! '(,) ('True :: Bool) ('False :: Bool)
'(,) ('True :: Bool) ('False :: Bool) :: (Bool, Bool)
= '( 'True, 'False)

UPDATE

As @Daniel Wagner already mentioned below the (,) used here is considered as Type -> Type -> Type and the kind parameter r is instantiated to Type within the second equation above (All' c (x ': xs) = (c x, All' c xs)). In fact if we had used '(,), it would have correctly returned a type error. I was able to further confirm it using a technique described in this blog post as following (All' is instantiated with kinds k, and *):

λ> :set -fprint-explicit-kinds
λ> :info All'
type All' :: forall k r. (k -> r) -> [k] -> r
type family All' @k @r c xs where
  forall k (c :: k -> *). All' @k @(*) c ('[] @k) = ()
  forall k (c :: k -> *) (x :: k) (xs :: [k]).
    All' @k @(*) c ((':) @k x xs) = (c x, All' @k @(*) c xs)
zeronone
  • 2,912
  • 25
  • 28
  • N.B. the `All'` definition in your update at the end does *not* match the `All` definition at the beginning of the original question! The original one has a `Constraint` kind annotation that the one at the end lacks. – Daniel Wagner Aug 11 '21 at 04:21
  • @DanielWagner Ah, my bad. There was a typo, the original question was actually about `All'` (the one using `PolyKinds`). – zeronone Aug 11 '21 at 04:43
  • 1
    Huh. Reading your `All'` definition more carefully, I actually find it very odd that the compiler accepts it. You demand `All' _ _ :: r`, but then define `All' _ '[] = ()`, and there's no good reason to believe `() :: r`. Could this be a GHC bug? – Daniel Wagner Aug 11 '21 at 04:54
  • 1
    Indeed, GHC 9.2 does not accept your definition of `All'`! Either definition on its own is rejected (i.e. just `All' c '[] = ()` or just `All' c (x ': xs) = (c x, All' c xs)`), as seems like ought to happen. I suspect you have simply stumbled over a bug here. – Daniel Wagner Aug 11 '21 at 04:55
  • Yes, that was basically my question. I was surprised that GHC didn't give a type error. Also as written in the "UPDATE", it seems `r` is always instantiated `Type`, so probably that is why it type-checks. I haven't check with GHC 9.2 yet. – zeronone Aug 11 '21 at 06:00
  • @DanielWagner, it doesn't sound like a bug to me. It's implicitly matching on the return kind. Why doesn't 9.2 accept that? – dfeuer Aug 11 '21 at 13:36

1 Answers1

6

There is a syntactic pun here. There are actually several different commas, with differing kinds:

 (,) :: Type -> Type -> Type
 (,) :: Constraint -> Constraint -> Constraint -- ...ish
'(,) :: a -> b -> (a, b)

Note that none of these kinds unify with any other. Additionally, the second one is a bit of a lie; if x :: Constraint and y :: Constraint, then (x, y) :: Constraint, but the comma cannot be put prefix as in (,) x y.

When attempting to disambiguate the first two, GHC assumes you are using (,) :: Type -> Type -> Type unless you are in a place which syntactically cannot use that (e.g. to the left of an =>) or you have given an explicit kind annotation of :: Constraint. The single-tick ' disambiguates between the first two and the last one.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • 3
    I expect if the early Haskell committee had foreseen that we would have `DataKinds` at some point, they would have ditched the `(Num a, Eq a)` notation and it would instead maybe be `(&) :: Constraint -> Constraint -> Constrained` or something. – leftaroundabout Aug 10 '21 at 18:38
  • Thanks that clears up the confusion, I updated the question with that observation. I guess if we want to have a generic `All` type-level function, it should have separate equations for each `Type`, `Constraint`, and kind `k` (and having a new kind variable for the return kind)? – zeronone Aug 11 '21 at 01:49