[Haskell-cafe] Bug in System.Environment - EOT inserted into argument string

Clifford Beshers clifford.beshers at gmail.com
Mon Feb 4 12:30:48 EST 2008


No, I cannot reproduce this.

2008/2/4 David Fox <ddssff at gmail.com>:

> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080204/0d318d34/attachment.htm


More information about the Haskell-Cafe mailing list