Changes to Typeable

Bas van Dijk v.dijk.bas at gmail.com
Mon Feb 13 12:07:46 CET 2012


Edward,

it was my impression that you have to use ScopedTypeVariables or other
tricks to work with Proxy to.

For example say I want to write:

typeOf :: Typeable a => a -> TypeRep

With Proxy I can either write:

{-# LANGUAGE ScopedTypeVariables #-}
typeOf :: forall a. Typeable a => a -> TypeRep
typeOf _ = typeRep (Proxy :: Proxy a)

or without extensions:

typeOf :: Typeable a => a -> TypeRep
typeOf x = typeRep (p x)
  where
    p :: b -> Proxy b
    p _ = Proxy

But with Tagged the situation is similar:

{-# LANGUAGE ScopedTypeVariables #-}
typeOf :: forall a. Typeable a => a -> TypeRep
typeOf _ = unTagged (typeRep :: Tagged a TypeRep)

or without extensions:

typeOf :: Typeable a => a -> TypeRep
typeOf x = unTagged (t x)
  where
    t :: Typeable b => b -> Tagged b TypeRep
    t _  = typeRep

Where is the "huge pain" you are talking about?

I do have to admit that the Proxy versions are slightly smaller and
easier to read.

Bas

On 12 February 2012 00:56, Edward Kmett <ekmett at gmail.com> wrote:
> In practice I've found that working with Tagged is a huge pain relative to
> working with Proxy.
>
> You usually need to use ScopedTypeVariables or do asTypeOf/asArgOf tricks
> that are far more complicated than they need to be.
>
> For reference you can compare the internals of reflection before when it
> used to use Tagged, and after I switched it to use Proxy.
>
> The Proxy version is much simpler.
>
> Tagged works well when you only need one tag and are going to use it for a
> lot of types. That really isn't the usecase with Typeable most of the time.
>
> -Edward
>
> On Fri, Feb 10, 2012 at 7:35 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
>>
>> On 11 February 2012 00:30, John Meacham <john at repetae.net> wrote:
>> > Would it be useful to make 'Proxy' an unboxed type itself? so
>> >
>> > Proxy :: forall k . k -> #
>> >
>> > This would statically ensure that no one accidentally passes ⊥ as a
>> > parameter
>> > or will get anything other than the unit 'Proxy' when trying to evaluate
>> > it.
>> > So the compiler can unconditionally elide the parameter at runtime.
>> > Pretty
>> > much exactly how State# gets dropped which has almost the same
>> > definition.
>>
>> Or don't use an argument at all:
>>
>> class Typeable t where
>>  typeRep :: Tagged t TypeRep
>>
>> newtype Tagged s b = Tagged { unTagged :: b }
>>
>> See:
>>
>>
>> http://hackage.haskell.org/packages/archive/tagged/0.2.3.1/doc/html/Data-Tagged.html
>>
>> Bas
>>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>



More information about the Libraries mailing list