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

Mike Meyer mwm at mired.org
Sat May 23 19:38:07 UTC 2015


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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150523/e6651843/attachment.html>


More information about the Beginners mailing list