Polymorphic implicit parameters
Roman Cheplyaka
roma at ro-che.info
Thu Mar 21 10:58:02 CET 2013
That makes sense, thank you.
Roman
* Simon Peyton-Jones <simonpj at microsoft.com> [2013-03-21 08:25:03+0000]
> Generally speaking ALL constraints (class constraints, equality constraints, implicit parameters) range only over monotypes.
>
> The apparatus should extend to polymorphic types, be it's somewhat uncharted territory. I doubt there'd be much problem in the case of implicit parameters.
>
> In short, in principle it might be possible, but it would take a little careful thought and I have too few careful-thought electrons available right now.
>
> Simon
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
> | bounces at haskell.org] On Behalf Of Roman Cheplyaka
> | Sent: 20 March 2013 08:58
> | To: glasgow-haskell-users at haskell.org
> | Subject: Polymorphic implicit parameters
> |
> | I'm curious as to why GHC doesn't accept the following (contrived)
> | module:
> |
> | {-# LANGUAGE ImplicitParams, RankNTypes #-}
> |
> | f :: (?g :: (forall a . a -> a)) => a -> a
> | f = ?g
> |
> | The error message is:
> |
> | Illegal polymorphic or qualified type: forall a. a -> a
> | In the type signature for `f':
> | f :: ?g :: (forall a. a -> a) => a -> a
> |
> | It's not a big deal since one can wrap the polymorphism in a newtype,
> | but it's somewhat unexpected.
> |
> | Roman
> |
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list