Weird interaction between literate haskell, ghci and OverloadedStrings

Hi, I'm working on a literate haskell document (actually TeX, but the example below is just test) and I'm using ByteStrings in the code. I know I can do: ghci -XOverloadedStrings file.lhs or, after ghci is running I can do: Main> :set -XOverloadedStrings but I'd like to embed a directive in the file so that when loaded in GHCi, I will automatically get OverloadedStrings. This is mainly so that it JustWorks(tm) when I pass the file on to someone else. Is there a way to do this? There is a short example file below. I'm using ghc-7.0.4 from Debian testing. Cheers, Erik ----------8<----------8<----------8<----------8<----------
{-# LANGUAGE OverloadedStrings #-}
This is just text that that ghc/ghci should ignore
import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as BS
Simple function:
newlineCount :: ByteString -> Int newlineCount bs = BS.foldl foldFun 0 bs where foldFun s ch = if ch == '\n' then s + 1 else s
Once this file is loaded, I should be able to do this: newlineCount "abcd\ncdead\nasdasd\n" ----------8<----------8<----------8<----------8<---------- -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On 3 December 2011 16:18, Erik de Castro Lopo
Hi,
I'm working on a literate haskell document (actually TeX, but the example below is just test) and I'm using ByteStrings in the code. I know I can do:
ghci -XOverloadedStrings file.lhs
or, after ghci is running I can do:
Main> :set -XOverloadedStrings
Add ":set -XOverloadedStrings" to a (possibly local) .ghci file? It doesn't contain it within the same document, but then if it's a local one you could also add ":load file.lhs" in there so that you just have to type ghci. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan Lazar Miljenovic wrote:
Add ":set -XOverloadedStrings" to a (possibly local) .ghci file? It doesn't contain it within the same document, but then if it's a local one you could also add ":load file.lhs" in there so that you just have to type ghci.
Unfortunately, thats no better than telling people do: ghci -XOverloadedStrings file.lhs Probably worse actually. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

Hi, Am Samstag, den 03.12.2011, 16:18 +1100 schrieb Erik de Castro Lopo:
I'm working on a literate haskell document (actually TeX, but the example below is just test) and I'm using ByteStrings in the code. I know I can do:
ghci -XOverloadedStrings file.lhs
or, after ghci is running I can do:
Main> :set -XOverloadedStrings
but I'd like to embed a directive in the file so that when loaded in GHCi, I will automatically get OverloadedStrings. This is mainly so that it JustWorks(tm) when I pass the file on to someone else.
Is there a way to do this?
There is a short example file below. I'm using ghc-7.0.4 from Debian testing.
it does not seem to be related to literate haskell, if I copy the code from your file into a .hs without the "> ", ghci still does not activate the OverloadedStrings extension when loading the file. I’d consider this a bug until the developers explain why this should or cannot be different, and suggest you file it as such. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

Joachim Breitner wrote:
it does not seem to be related to literate haskell, if I copy the code from your file into a .hs without the "> ", ghci still does not activate the OverloadedStrings extension when loading the file.
I hadn't noticed that.
I’d consider this a bug until the developers explain why this should or cannot be different, and suggest you file it as such.
I agree. I've lodged a bug report here: http://hackage.haskell.org/trac/ghc/ticket/5673 Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On 3 December 2011 11:19, Erik de Castro Lopo
Joachim Breitner wrote:
it does not seem to be related to literate haskell, if I copy the code from your file into a .hs without the "> ", ghci still does not activate the OverloadedStrings extension when loading the file.
I hadn't noticed that.
I’d consider this a bug until the developers explain why this should or cannot be different, and suggest you file it as such.
I agree. I've lodged a bug report here:
I think it's very dangerous if language extensions "leak" from modules by default. For example if someone creates a library and needs to use some unsafe language extensions like: {-# LANGUAGE UndecidableInstances, OverlappingInstances, IncoherentInstances #-} module SomeLib where ... You surely don't want to silently enable these in some unsuspecting client: module MyFirstHaskellModule where import SomeLib ... I can imagine having a pragma for explicitly exporting language extensions: {-# EXPORT_LANGUAGE OverloadedStrings #-} Cheers, Bas
participants (4)
-
Bas van Dijk
-
Erik de Castro Lopo
-
Ivan Lazar Miljenovic
-
Joachim Breitner