#5512: UTF-16//ROUNDTRIP encoding behaves weirdly
---------------------------------+------------------------------------------
Reporter: batterseapower | Owner:
Type: bug | Status: new
Priority: normal | Component: libraries/base
Version: 7.2.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
Description changed by batterseapower:
Old description:
> Try this program:
>
> {{{
> module Main where
>
> import System.IO
>
> main = do
> roundtrip_enc <- mkTextEncoding "UTF16//ROUNDTRIP"
> h <- openFile "out.temp" WriteMode
> hSetEncoding h roundtrip_enc
> hPutStr h "Hi\xEFE8Hi"
> }}}
>
> It fails with:
>
> {{{
> hSetEncoding: invalid argument (Invalid argument)
> }}}
>
> If you change UTF16 to UTF-16 (so we use the builtin encoding rather than
> iconv) it works, but the output file only contains the first Hi.
>
> I think what is going on here is that iconv does not generate EILSEQ for
> identity transformations such as that between a UTF-16 text file and our
> UTF-16 CharBuffers. Since we never get that exception, we can't fix up
> the lone surrogates we use to encode roundtrip characters.
New description:
Try this program:
{{{
module Main where
import System.IO
main = do
roundtrip_enc <- mkTextEncoding "UTF16//ROUNDTRIP"
h <- openFile "out.temp" WriteMode
hSetEncoding h roundtrip_enc
hPutStr h "Hi\xEFE8Hi"
}}}
It fails with:
{{{
hSetEncoding: invalid argument (Invalid argument)
}}}
If you change UTF16 to UTF-16 (so we use the builtin encoding rather than
iconv) it works, but the output file only contains the first Hi.
I think part of what is going on here is that iconv does not generate
EILSEQ for identity transformations such as that between a UTF-16 text
file and our UTF-16 CharBuffers. Since we never get that exception, we
can't fix up the lone surrogates we use to encode roundtrip characters.
--
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5512#comment:1>
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