[Haskell-cafe] returning a polymorphic function

Patrick Chilton chpatrick at gmail.com
Mon Jun 15 14:18:22 UTC 2015


Yes, but you have to wrap it up:

{-# LANGUAGE RankNTypes #-}

-- obviously not to useful for this example :)
newtype Id = Id (forall a. a -> a)

f :: IO Id
f = return (Id id)

main = do
  Id g <- f
  print $ g 1
  print $ g "ciao"

Can I ask what you're trying to do with this?

Patrick

On Mon, Jun 15, 2015 at 3:11 PM, Paolino <paolo.veronelli at gmail.com> wrote:

> Hello list, I'm trying to accomplish something along this line
>
> {-# LANGUAGE ScopedTypeVariables #-}
>
> f :: IO (a -> a)
> f = return id
>
> main = do
>   (g :: a -> a) <- f
>   print $ g 1
>   print $ g "ciao"
>
>
>
> Is it possible or I have to call f more than once to get different g's
>
>
> Thanks
>
> paolino
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150615/a93afc25/attachment.html>


More information about the Haskell-Cafe mailing list