
I think it is a bug in the emacs shell mode.
On Feb 4, 2008 9:30 AM, Clifford Beshers
No, I cannot reproduce this.
2008/2/4 David Fox
: I'm seeing the character ^D inserted into argument strings that are about 256 characters long with GHC 6.8.2. Anyone else?
Test.hs:
module Main where
import System.Environment import System.IO
main = do args <- getArgs hPutStrLn stderr ("args: " ++ show args)
Output:
$ ghc6 --make Test.hs -o test [1 of 1] Compiling Main ( Test.hs, Test.o ) Linking test ... $ ./test "012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789" args: ["01234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234\EOT5678901234567890123456789"]
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe