[Haskell-cafe] Extending constraints

Bas van Dijk v.dijk.bas at gmail.com
Tue Jun 5 17:29:02 CEST 2012


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)

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