[ghc-steering-committee] Mind the gap

Simon Peyton Jones simon.peytonjones at gmail.com
Wed Jul 6 08:35:28 UTC 2022


Like Richard, I'd be sad to think that PolyKinds is causing problems, and
would like to understand better.  For example, at the term level we wioudl
not dream of making monomorphism the default!  So why would we do that at
the type level?  Maybe it is a shortcoming of inference or error messages.

However the error is a bit perplexing.

class (Typeable a) => S a

newtype D a = D { getD :: Int }

instance (Typeable a) => S (D a)

We get the error Chris shows.  But it looks as if we have done all that is
needful.  We need (Typeable (D a)) and we have provided (Typeable a).  What
gives?   Well, what we really need is (Typeable (D @k a)), and for that we
need (Typeable k) too.  But that's very far from clear.

I sort of wonder: if we have (Typeable t) should that not give us (Typeable
k) where (t :: k)?  That would require us to have a function typeRepKind ::
TypeRep (a::k) -> TypeRep k, and I don't know how hard that is to get.

Simon

On Tue, 5 Jul 2022 at 16:03, Richard Eisenberg <lists at richarde.dev> wrote:

> I find that surprising, and disappointing. I think of PolyKinds as largely
> innocuous, except in strange scenarios, which is why PolyKinds is included
> in GHC2021. If that is wrong, perhaps we should consider not including
> PolyKinds in GHC2023...
>
> It would be interesting to learn more about what's going wrong.
>
> Richard
>
> On Jul 5, 2022, at 10:26 AM, Chris Dornan <chris at chrisdornan.com> wrote:
>
> yup, i should have started there—all my recent troubles have come from
> PolyKinds!
>
> On Tue, 5 Jul 2022 at 15:00, Richard Eisenberg <lists at richarde.dev> wrote:
>
>> This is PolyKinds, which generalizes the kind of D, meaning that
>> satisfying the Typeable a superclass constraint of C also requires a
>> Typeable k constraint, where (a :: k).
>>
>> Richard
>>
>> > On Jul 2, 2022, at 12:49 AM, Chris Dornan <chris at chrisdornan.com>
>> wrote:
>> >
>> > Quick quiz: the below Haskell2010 ‘Phantoms' module (also in this Gist:
>> https://gist.github.com/cdornan/f75cd8024434d998c87610cbb7fb6ab3)
>> appears (for me on GHC 9.2.2 and 9.2.3) to not be a GHC2021 module,
>> reporting this error under the latter configuration:
>> >
>> > Phantoms.hs:22:10: error:
>> >    • Could not deduce (Typeable k)
>> >        arising from the superclasses of an instance declaration
>> >      from the context: (C a, Typeable a)
>> >        bound by the instance declaration
>> >        at Phantoms.hs:22:10-36
>> >    • In the instance declaration for ‘S (D a)’
>> >   |
>> > 22 | instance (C a,Typeable a) => S (D a) where smethod = undefined
>> >   |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^
>> >
>> > Phantoms.hs:22:10: error:
>> >    • Could not deduce (Typeable k)
>> >        arising from the superclasses of an instance declaration
>> >      from the context: (C a, Typeable a)
>> >        bound by the instance declaration
>> >        at Phantoms.hs:22:10-36
>> >    • In the instance declaration for ‘S (D a)’
>> >   |
>> > 22 | instance (C a,Typeable a) => S (D a) where smethod = undefined
>> >
>> > The question is which language extension(s) are giving rise to these
>> errors?
>> >
>> > The ‘Phantoms' module is this:
>> >
>> > {-# LANGUAGE DerivingVia #-}
>> >
>> > module Phantoms where
>> >
>> > import Data.Typeable
>> >
>> >
>> > class C a where
>> >  cmethod :: Proxy a -> ()
>> >
>> > class (Show a, Typeable a) => S a where
>> >  smethod :: a -> Int
>> >
>> >
>> > newtype UsingD a = UsingD { getUsingD :: a }
>> >
>> >
>> > newtype D a = D { getD :: Int }
>> >    deriving (Show) via UsingD (D a)
>> >
>> >
>> > instance (C a,Typeable a) => S (D a) where smethod = undefined
>> >
>> > instance (C a,Typeable a) => Show (UsingD a) where showsPrec = undefined
>> >
>> >
>> > instance (C a) => C (D a) where cmethod _ = undefined
>> >
>> > _______________________________________________
>> > ghc-steering-committee mailing list
>> > ghc-steering-committee at haskell.org
>> >
>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
>>
>>
> _______________________________________________
> ghc-steering-committee mailing list
> ghc-steering-committee at haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-steering-committee/attachments/20220706/9ffcc347/attachment-0001.html>


More information about the ghc-steering-committee mailing list