diffing dir...
Wed Mar 20 12:09:24 GMT 2013 Daniel Wagner <da...@wa...>
* use utf8-string for encoding and decoding
Ignore-this: 70c5f89ec363a0dc7c90b3179f0fcc17
hunk ./cairo/Graphics/Rendering/Cairo/Internal/Utilities.chs 21
+import Codec.Binary.UTF8.String
hunk ./cairo/Graphics/Rendering/Cairo/Internal/Utilities.chs 30
--- These functions taken from System/Glib/UTFString.hs
--- Copyright (c) 1999..2002 Axel Simon
-
--- Define withUTFString to emit UTF-8.
---
hunk ./cairo/Graphics/Rendering/Cairo/Internal/Utilities.chs 31
-withUTFString hsStr = withCAString (toUTF hsStr)
- where
- -- Convert Unicode characters to UTF-8.
- --
- toUTF :: String -> String
- toUTF [] = []
- toUTF (x:xs) | ord x<=0x007F = x:toUTF xs
- | ord x<=0x07FF = chr (0xC0 .|. ((ord x `shift` (-6)) .&. 0x1F)):
- chr (0x80 .|. (ord x .&. 0x3F)):
- toUTF xs
- | otherwise = chr (0xE0 .|. ((ord x `shift` (-12)) .&. 0x0F)):
- chr (0x80 .|. ((ord x `shift` (-6)) .&. 0x3F)):
- chr (0x80 .|. (ord x .&. 0x3F)):
- toUTF xs
+withUTFString = withCAString . encodeString
hunk ./cairo/cairo.cabal 49
+ utf8-string >= 0.2 && < 0.4,
hunk ./glib/System/Glib/UTFString.hs 49
-import Control.Monad (liftM)
+import Codec.Binary.UTF8.String
+import Control.Monad (liftM)
hunk ./glib/System/Glib/UTFString.hs 59
-withUTFString hsStr = withCAString (toUTF hsStr)
+withUTFString = withCAString . encodeString
hunk ./glib/System/Glib/UTFString.hs 64
-withUTFStringLen hsStr = withCAStringLen (toUTF hsStr)
+withUTFStringLen = withCAStringLen . encodeString
hunk ./glib/System/Glib/UTFString.hs 69
-newUTFString = newCAString . toUTF
+newUTFString = newCAString . encodeString
hunk ./glib/System/Glib/UTFString.hs 74
-newUTFStringLen = newCAStringLen . toUTF
+newUTFStringLen = newCAStringLen . encodeString
hunk ./glib/System/Glib/UTFString.hs 79
-peekUTFString strPtr = liftM fromUTF $ peekCAString strPtr
+peekUTFString = liftM decodeString . peekCAString
hunk ./glib/System/Glib/UTFString.hs 85
-maybePeekUTFString strPtr = liftM (maybe Nothing (Just . fromUTF)) $ maybePeek peekCAString strPtr
+maybePeekUTFString = liftM (maybe Nothing (Just . decodeString)) . maybePeek peekCAString
hunk ./glib/System/Glib/UTFString.hs 90
-peekUTFStringLen strPtr = liftM fromUTF $ peekCAStringLen strPtr
+peekUTFStringLen = liftM decodeString . peekCAStringLen
hunk ./glib/System/Glib/UTFString.hs 167
--- | Encode a Haskell Unicode String as UTF-8
---
--- You should think of this as it it had type @String -> [Word8]@
---
-toUTF :: String -> String
-toUTF [] = []
-toUTF (x:xs) | ord x<=0x007F = x:toUTF xs
- | ord x<=0x07FF = chr (0xC0 .|. ((ord x `shift` (-6)) .&. 0x1F)):
- chr (0x80 .|. (ord x .&. 0x3F)):
- toUTF xs
- | ord x<=0xFFFF = chr (0xE0 .|. ((ord x `shift` (-12)) .&. 0x0F)):
- chr (0x80 .|. ((ord x `shift` (-6)) .&. 0x3F)):
- chr (0x80 .|. (ord x .&. 0x3F)):
- toUTF xs
- | otherwise = chr (0xF0 .|. ((ord x `shift` (-18)) .&. 0x07)):
- chr (0x80 .|. ((ord x `shift` (-12)) .&. 0x3F)):
- chr (0x80 .|. ((ord x `shift` (-6)) .&. 0x3F)):
- chr (0x80 .|. (ord x .&. 0x3F)):
- toUTF xs
-
--- | Decode a UTF-8 string into a Haskell Unicode String.
---
--- You should think of this as it it had type @[Word8] -> String@
---
-fromUTF :: String -> String
-fromUTF [] = []
-fromUTF (all@(x:xs)) | ord x<=0x7F = x:fromUTF xs
- | ord x<=0xBF = err
- | ord x<=0xDF = twoBytes all
- | ord x<=0xEF = threeBytes all
- | ord x<=0xF7 = fourBytes all
- | otherwise = err
- where
- twoBytes (x1:x2:xs) = chr (((ord x1 .&. 0x1F) `shift` 6) .|.
- (ord x2 .&. 0x3F)):fromUTF xs
- twoBytes _ = error "fromUTF: illegal two byte sequence"
-
- threeBytes (x1:x2:x3:xs) = chr (((ord x1 .&. 0x0F) `shift` 12) .|.
- ((ord x2 .&. 0x3F) `shift` 6) .|.
- (ord x3 .&. 0x3F)):fromUTF xs
- threeBytes _ = error "fromUTF: illegal three byte sequence"
-
- fourBytes (x1:x2:x3:x4:xs) = chr (((ord x1 .&. 0x07) `shift` 18) .|.
- ((ord x2 .&. 0x3F) `shift` 12) .|.
- ((ord x3 .&. 0x3F) `shift` 6) .|.
- (ord x4 .&. 0x3F)):fromUTF xs
- fourBytes _ = error "fromUTF: illegal four byte sequence"
-
- err = error "fromUTF: illegal UTF-8 character"
-
hunk ./glib/glib.cabal 36
+ utf8-string >= 0.2 && < 0.4,
|