Changes to Typeable
Edward Kmett
ekmett at gmail.com
Tue Feb 14 02:32:43 CET 2012
On Mon, Feb 13, 2012 at 6:07 AM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> Edward,
>
> it was my impression that you have to use ScopedTypeVariables or other
> tricks to work with Proxy to.
>
> 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?
>
The pain is the need to define t.
With Proxy you can often use pre-existing combinators, because as a data
type, it admits a ton of instances. In this case you can just use 'return'
or 'pure'.
typeOf :: Typeable a => a -> TypeRep
typeOf = typeRep . pure
There are fewer combinators from commonly used classes for working with the
left argument of a bifunctor, however.
-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20120213/08f5f919/attachment.htm>
More information about the Libraries
mailing list