[Haskell-cafe] Extending constraints

Gábor Lehel illissius at gmail.com
Tue Jun 5 18:46:43 CEST 2012


On Tue, Jun 5, 2012 at 5:29 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> Hello,
>
> I have the following program:
>
> --------------------------------------------------------------------------
> {-# LANGUAGE ConstraintKinds #-}
> {-# LANGUAGE ExistentialQuantification #-}
> {-# LANGUAGE ScopedTypeVariables #-}
>
> import Data.Proxy (Proxy)
> import Data.Typeable (Typeable, TypeRep, typeOf)
>
> data ProxyWrapper constraint =
>    forall a. constraint a => ProxyWrapper (Proxy a)

I must be missing something, but this seems a bit useless to me. You
have a phantom type parameter on Proxy, and then you're hiding it. So
when you pattern match on ProxyWrapper you recover the fact that there
was a type which satisfies the constraint, but you don't know what
type it was, and neither do you know about any values which are of the
type. What are you trying to do?

That said, if you want to be able to recover a Typeable constraint, I
don't see any way except for using 'ProxyWrapper (Ext Typeable
constraint)' as Andres says or putting 'forall a. (constraint a,
Typeable a)' in the definition of ProxyWrapper.

>
> typeOfInnerProxy :: ProxyWrapper constraint -> TypeRep
> typeOfInnerProxy (ProxyWrapper p) = typeOfArg p
>
> typeOfArg :: forall t a. Typeable a => t a -> TypeRep
> typeOfArg _ = typeOf (undefined :: a)
> --------------------------------------------------------------------------
>
> Type checking this gives the following expected type error:
>
> ProxyWrapper.hs:12:37:
>    Could not deduce (Typeable a) arising from a use of `typeOfArg'
>    from the context (constraint a)
>      bound by a pattern with constructor
>                 ProxyWrapper :: forall (constraint :: * -> Constraint) a.
>                                 (constraint a) =>
>                                 Proxy a -> ProxyWrapper constraint,
>               in an equation for `typeOfInnerProxy'
>
> Is there a way to extend the 'constraint' with the 'Typeable'
> constraint in the type signature of 'typeOfInnerProxy'?
>
> Regards,
>
> Bas



More information about the Haskell-Cafe mailing list