ClassyPrelude vs. Haskell.Language.Interpreter

No answer on -beginners, so I'm trying -cafe. I'm trying to run interpreted code via ClassyPrelude, and getting some results that make me suspect a bug in the Prelude's type system. Or maybe the interpreter. Anyway, here's a bit of code that works as expected: {-# LANGUAGE NoImplicitPrelude #-} import ClassyPrelude import Language.Haskell.Interpreter main :: IO () main = do fun <- runInterpreter $ makeFun "reverse" case fun of Left e -> print e Right f -> readFile "/etc/motd" >>= hPut stdout . f makeFun expr = do set [languageExtensions := [NoImplicitPrelude]] setImportsQ [("ClassyPrelude", Nothing)] interpret expr (as :: Text -> Text) I don't think I can simplify this any further. It works as expected, and also works as expected, and prints out the contents of /etc/motd reversed. However, if you change the type signature in the last line from Text -> Text to LText -> Ltext (to get lazy text), you get no output. But if you change the function in the first line after main from "reverse" to "id", it works. So far, it might be an issue with lazy IO. However, change the type signature in the last line to LText -> Text. In this case, there is no output for either value of the expression. I expect an error in this case, as neither id nor reverse should be able to have the type LText -> Text! So, is there something I missed in either ClassyPrelude or the Interpreter? Or is this a subtle interaction, in which case can someone suggest a workaround? Or have I found a bug in one of the two?

Hi Mike!
I'm not sure what's going on here. When I run that code with LText, with
the string "hi" (instead of reading motd), I get an "out of memory"
exception. So, I don't think this is an issue with lazy IO.
However, storing values produced by an interpreter session reminds me of
Chris's foreign-store package. Might be worth a shot:
http://hackage.haskell.org/package/foreign-store
-Michael
On Tue, May 26, 2015 at 10:47 AM, Mike Meyer
No answer on -beginners, so I'm trying -cafe.
I'm trying to run interpreted code via ClassyPrelude, and getting some results that make me suspect a bug in the Prelude's type system. Or maybe the interpreter.
Anyway, here's a bit of code that works as expected:
{-# LANGUAGE NoImplicitPrelude #-}
import ClassyPrelude import Language.Haskell.Interpreter
main :: IO () main = do fun <- runInterpreter $ makeFun "reverse" case fun of Left e -> print e Right f -> readFile "/etc/motd" >>= hPut stdout . f
makeFun expr = do set [languageExtensions := [NoImplicitPrelude]] setImportsQ [("ClassyPrelude", Nothing)] interpret expr (as :: Text -> Text)
I don't think I can simplify this any further. It works as expected, and also works as expected, and prints out the contents of /etc/motd reversed.
However, if you change the type signature in the last line from Text -> Text to LText -> Ltext (to get lazy text), you get no output. But if you change the function in the first line after main from "reverse" to "id", it works.
So far, it might be an issue with lazy IO. However, change the type signature in the last line to LText -> Text. In this case, there is no output for either value of the expression. I expect an error in this case, as neither id nor reverse should be able to have the type LText -> Text!
So, is there something I missed in either ClassyPrelude or the Interpreter? Or is this a subtle interaction, in which case can someone suggest a workaround? Or have I found a bug in one of the two?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Lazy text is this one?
http://hackage.haskell.org/package/text-1.1.0.1/docs/Data-Text-Lazy.html
At first sight I'd say it's the way lazy text works with reverse that the
interpreter doesn't like...
On Tue, May 26, 2015 at 7:47 PM, Mike Meyer
No answer on -beginners, so I'm trying -cafe.
I'm trying to run interpreted code via ClassyPrelude, and getting some results that make me suspect a bug in the Prelude's type system. Or maybe the interpreter.
Anyway, here's a bit of code that works as expected:
{-# LANGUAGE NoImplicitPrelude #-}
import ClassyPrelude import Language.Haskell.Interpreter
main :: IO () main = do fun <- runInterpreter $ makeFun "reverse" case fun of Left e -> print e Right f -> readFile "/etc/motd" >>= hPut stdout . f
makeFun expr = do set [languageExtensions := [NoImplicitPrelude]] setImportsQ [("ClassyPrelude", Nothing)] interpret expr (as :: Text -> Text)
I don't think I can simplify this any further. It works as expected, and also works as expected, and prints out the contents of /etc/motd reversed.
However, if you change the type signature in the last line from Text -> Text to LText -> Ltext (to get lazy text), you get no output. But if you change the function in the first line after main from "reverse" to "id", it works.
So far, it might be an issue with lazy IO. However, change the type signature in the last line to LText -> Text. In this case, there is no output for either value of the expression. I expect an error in this case, as neither id nor reverse should be able to have the type LText -> Text!
So, is there something I missed in either ClassyPrelude or the Interpreter? Or is this a subtle interaction, in which case can someone suggest a workaround? Or have I found a bug in one of the two?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Actually, I think there's at least one bug in ghc. My testing was all done
on 7.8. When I tried running it on 7.10, reverse gives the out of memory
error that Michael Sloan reported. Not really good, but acceptable, as you
probably shouldn't be using lazy text in that situation.
Trying to use LText -> Text (which generates a type error if I try it
without the interpreter) on 7.8 gets no output, but on 7.10 eventually
segfaults.
On Tue, May 26, 2015 at 5:11 PM, Corentin Dupont
Lazy text is this one? http://hackage.haskell.org/package/text-1.1.0.1/docs/Data-Text-Lazy.html
At first sight I'd say it's the way lazy text works with reverse that the interpreter doesn't like...
On Tue, May 26, 2015 at 7:47 PM, Mike Meyer
wrote: No answer on -beginners, so I'm trying -cafe.
I'm trying to run interpreted code via ClassyPrelude, and getting some results that make me suspect a bug in the Prelude's type system. Or maybe the interpreter.
Anyway, here's a bit of code that works as expected:
{-# LANGUAGE NoImplicitPrelude #-}
import ClassyPrelude import Language.Haskell.Interpreter
main :: IO () main = do fun <- runInterpreter $ makeFun "reverse" case fun of Left e -> print e Right f -> readFile "/etc/motd" >>= hPut stdout . f
makeFun expr = do set [languageExtensions := [NoImplicitPrelude]] setImportsQ [("ClassyPrelude", Nothing)] interpret expr (as :: Text -> Text)
I don't think I can simplify this any further. It works as expected, and also works as expected, and prints out the contents of /etc/motd reversed.
However, if you change the type signature in the last line from Text -> Text to LText -> Ltext (to get lazy text), you get no output. But if you change the function in the first line after main from "reverse" to "id", it works.
So far, it might be an issue with lazy IO. However, change the type signature in the last line to LText -> Text. In this case, there is no output for either value of the expression. I expect an error in this case, as neither id nor reverse should be able to have the type LText -> Text!
So, is there something I missed in either ClassyPrelude or the Interpreter? Or is this a subtle interaction, in which case can someone suggest a workaround? Or have I found a bug in one of the two?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (3)
-
Corentin Dupont
-
Michael Sloan
-
Mike Meyer