[Haskell-cafe] Can I get 'forall (a :: k). Typeable a => Dict (Typeable k)'?

Oleg Grenrus oleg.grenrus at iki.fi
Wed Aug 23 10:58:16 UTC 2023


What you mean "could we get", add to base or be able to define?
I think you can:

     {-# LANGUAGE GADTs, RankNTypes, KindSignatures, PolyKinds, 
ConstraintKinds #-}

     import Data.Kind
     import Type.Reflection

     data Dict (c :: Constraint) where
       Dict :: c => Dict c

     kindable :: forall {k} (a :: k). Typeable a => Dict (Typeable (a :: k))
     kindable = Dict

works? Or am I missing something? Also isn't TypeRep a from 
Type.Reflection the same as Dict (Typeable a) for all practical 
purposes, `kindable = Type.Reflection.typeRep`, yet better?

     kindable' :: forall {k} (a :: k). Typeable a => TypeRep a
     kindable' = typeRep

- Oleg

On 23.8.2023 13.50, Tom Ellis wrote:
> Morally I think that
>
>      class Typeable (a :: k)
>
> should have been
>
>      class Typeable k => Typeable (a :: k)
>
> If I'm wrong, could someone please elaborate why?  If I'm right,
> please read on ...
>
> That would be a breaking change, but could we at least get
>
>      kindable :: forall (a :: k). Typeable a => Dict (Typable (a :: k))
>
> in the meantime?
>
> Tom
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.


More information about the Haskell-Cafe mailing list