[Haskell-cafe] Getting a string from url-converted UTF8 input
Eugene Dzhurinsky
bofh at redwerk.com
Sun May 16 11:42:08 EDT 2010
Hello all!
Can somebody please explain wha am I doing in wrong way?
===============================================================
module UrlEncode where
import System
import Codec.Binary.UTF8.String as SU
import Codec.Binary.Url as U
import Data.Maybe
main :: IO ()
main = do
args <- getArgs
processWithArgs args
processWithArgs ("-d":[]) =
getLine >>= putStrLn . maybe "" SU.decode . U.decode
processWithArgs ("-e":[]) =
getLine >>= putStrLn . U.encode . SU.encode
processWithArgs _ =
putStrLn "Usage: -e (encode) or -d (decode)"
===============================================================
With this script if fed with input:
===============================================================
1%29%20%D0%B3%D0%B4%D0%B5%20%D0%BD%D1%8B%D0%BD%D1%87%D0%B5%20%D0%BC%D0%BE%D0%B4%D0%BD%D0%BE%20%D0%B1%D1%80%D0%B0%D1%82%D1%8C%20%D0%BA%D0%BD%D0%B8%D0%B6%D0%BA%D0%B8%20%D0%B2%20%D0%B2%D0%B8%D0%B4%D0%B5%20FB2%3F%0D%0A%0D%0A2%29%20%D0%BA%D0%B0%D0%BA%D0%BE%D0%B9%20%D0%B5%D1%81%D1%82%D1%8C%20%D1%81%D0%BE%D1%84%D1%82%20%D0%BD%D0%B0%20%D0%B6%D0%B5%D0%BB%D0%B5%D0%B7%D0%BA%D1%83%20%D1%82%D0%B8%D0%BF%D0%B0%20%D1%82%D0%B5%D0%BB%D0%B5%D1%84%D0%BE%D0%BD%20%D1%81%20Symbian
===============================================================
I am getting the output:
===============================================================
1) 345 =K=G5 <>4=> 1 at 0BL :=86:8 2 2845 FB2?
2) :0:>9 5ABL A>DB =0 65;57:C B8?0 B5;5D>= A Symbian
===============================================================
which is wrong. So what do I miss in encoding the data in UTF?
Thank you in advance!
--
Eugene Dzhurinsky
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 196 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100516/a43c342f/attachment.bin
More information about the Haskell-Cafe
mailing list