[Haskell-cafe] ClassyPrelude vs. Haskell.Language.Interpreter

Michael Sloan mgsloan at gmail.com
Tue May 26 21:15:28 UTC 2015


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 <mwm at mired.org> 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 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/20150526/51446139/attachment.html>


More information about the Haskell-Cafe mailing list