#5673: GHCi ignores {-# LANGUAGE OverloadedStrings #-}
---------------------------------+------------------------------------------
Reporter: erikd | Owner:
Type: bug | Status: new
Priority: normal | Component: GHCi
Version: 7.0.4 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Other
---------------------------------+------------------------------------------
Very simple test file like:
{{{
{-# LANGUAGE OverloadedStrings #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
newlineCount :: ByteString -> Int
newlineCount bs = BS.foldl foldFun 0 bs
where foldFun s ch = if ch == '\n' then s + 1 else s
main :: IO ()
main = print $ newlineCount "a\nb\nc\n"
}}}
If I load this into GHCi, I can run the main function, but if I try to run
newlineCount with a string I provide, I get an error:
{{{
erikd@pharoah > ghci test.hs
GHCi, version 7.0.4: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( test.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
Loading package bytestring-0.9.1.10 ... linking ... done.
3
*Main> newlineCount "a\nb\nc\n"
<interactive>:1:14:
Couldn't match expected type `ByteString' with actual type `[Char]'
In the first argument of `newlineCount', namely `"a\nb\nc\n"'
In the expression: newlineCount "a\nb\nc\n"
In an equation for `it': it = newlineCount "a\nb\nc\n"
}}}
which is rather unexpected.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5673>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs