returning a polymorphic function

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

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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Thanks, I'd never have guessed.
I have a GADT Get a where I define a protocol to query a database where 'a'
is the return type a.
Then prepare :: IO (Get a -> ErrorAndWriterMonad a) is opening the database
and return the query function.
I suspect I have to insert the constraint in the wrapper to let transform
'a' to JSON or String, which I don't like. I'll have to dig it.
Regards
paolino
2015-06-15 16:18 GMT+02:00 Patrick Chilton
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

It worked without adding JSON constraint in the newtype.
I can do whatever I want with 'a'.
A simplified example where the database module is not polluted with future
use of the query results.
http://lpaste.net/134541#a134548
I tried refactoring common code ...... not easy
Thanks again
paolino
2015-06-15 16:26 GMT+02:00 Paolino
Thanks, I'd never have guessed. I have a GADT Get a where I define a protocol to query a database where 'a' is the return type a. Then prepare :: IO (Get a -> ErrorAndWriterMonad a) is opening the database and return the query function. I suspect I have to insert the constraint in the wrapper to let transform 'a' to JSON or String, which I don't like. I'll have to dig it.
Regards
paolino
2015-06-15 16:18 GMT+02:00 Patrick Chilton
: 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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

I've done something similar recently for an emulator I'm writing. It
essentially turns GHCI into a debugger for free:
newtype Run = Run (forall a. Emu a -> IO a)
start :: FilePath -> IO Run
breakpoint :: Word16 -> Emu ()
readMem :: Word16 -> Emu Word8
step :: Emu ()
Run emu <- start "foo.rom"
emu $ breakpoint 0x4567
emu $ readMem 0xdead
emu step
etc
On Mon, Jun 15, 2015 at 4:57 PM, Paolino
It worked without adding JSON constraint in the newtype. I can do whatever I want with 'a'.
A simplified example where the database module is not polluted with future use of the query results.
http://lpaste.net/134541#a134548
I tried refactoring common code ...... not easy
Thanks again
paolino
2015-06-15 16:26 GMT+02:00 Paolino
: Thanks, I'd never have guessed. I have a GADT Get a where I define a protocol to query a database where 'a' is the return type a. Then prepare :: IO (Get a -> ErrorAndWriterMonad a) is opening the database and return the query function. I suspect I have to insert the constraint in the wrapper to let transform 'a' to JSON or String, which I don't like. I'll have to dig it.
Regards
paolino
2015-06-15 16:18 GMT+02:00 Patrick Chilton
: 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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi. The most robust way to achieve this is to define
{-# LANGUAGE RankNTypes #-}
newtype PolyId = PolyId (forall a. a -> a)
f :: IO PolyId f = return (PolyId id)
main = do PolyId g <- f print $ g 1 print $ g "ciao"
You can also do this more directly using ImpredicativeTypes, but that language extension is quite fragile and not really supported. Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com
participants (3)
-
Andres Löh
-
Paolino
-
Patrick Chilton