utf8-light-0.3: utf8-lightSource codeContentsIndex
Codec.Binary.UTF8.Light
Portabilityportable
Stabilityprovisional
MaintainerMatt Morrow <mjm2002@gmail.com>
Description
Lightweight UTF8 handling.
Synopsis
class UTF8 a where
encode :: a -> ByteString
decode :: ByteString -> a
c2w :: Char -> Word32
w2c :: Word32 -> Char
i2w :: Int -> Word32
w2i :: Word32 -> Int
lenUTF8 :: Word8 -> Int
lenUTF16 :: Word16 -> Int
countUTF8 :: ByteString -> [Int]
decodeUTF8 :: ByteString -> [Word32]
encodeUTF8 :: [Word32] -> ByteString
encodeUTF8' :: [Word32] -> [[Word8]]
withUTF8 :: UTF8 a => a -> (ByteString -> b) -> b
putUTF8 :: UTF8 a => a -> IO ()
putUTF8Ln :: UTF8 a => a -> IO ()
hPutUTF8 :: UTF8 a => Handle -> a -> IO ()
hPutUTF8Ln :: UTF8 a => Handle -> a -> IO ()
readUTF8File :: UTF8 a => FilePath -> IO a
writeUTF8File :: UTF8 a => FilePath -> a -> IO ()
appendUTF8File :: UTF8 a => FilePath -> a -> IO ()
hGetUTF8Line :: UTF8 a => Handle -> IO a
hGetUTF8Contents :: UTF8 a => Handle -> IO a
hGetUTF8 :: UTF8 a => Handle -> Int -> IO a
hGetUTF8NonBlocking :: UTF8 a => Handle -> Int -> IO a
flipUTF8 :: UTF8 a => a -> a
unflipUTF8 :: UTF8 a => a -> a
flipTab :: [(Int, Int)]
unflipTab :: [(Int, Int)]
showHex :: Int -> String
toBits :: Word8 -> [Word8]
fromBits :: [Word8] -> Word8
Documentation
class UTF8 a whereSource
Instances: ByteString, String , [Word32], [Word] , [Int32], [Int]
Methods
encode :: a -> ByteStringSource
decode :: ByteString -> aSource
show/hide Instances
c2w :: Char -> Word32Source
w2c :: Word32 -> CharSource
i2w :: Int -> Word32Source
w2i :: Word32 -> IntSource
lenUTF8 :: Word8 -> IntSource
Length in Word8s
lenUTF16 :: Word16 -> IntSource
Length in Word16s
countUTF8 :: ByteString -> [Int]Source
Lengths in Word8s
decodeUTF8 :: ByteString -> [Word32]Source
encodeUTF8 :: [Word32] -> ByteStringSource
encodeUTF8' :: [Word32] -> [[Word8]]Source
Word32s not representing valid UTF8 chars are dropped.
withUTF8 :: UTF8 a => a -> (ByteString -> b) -> bSource
putUTF8 :: UTF8 a => a -> IO ()Source
putUTF8Ln :: UTF8 a => a -> IO ()Source
hPutUTF8 :: UTF8 a => Handle -> a -> IO ()Source
hPutUTF8Ln :: UTF8 a => Handle -> a -> IO ()Source
readUTF8File :: UTF8 a => FilePath -> IO aSource
writeUTF8File :: UTF8 a => FilePath -> a -> IO ()Source
appendUTF8File :: UTF8 a => FilePath -> a -> IO ()Source
hGetUTF8Line :: UTF8 a => Handle -> IO aSource
hGetUTF8Contents :: UTF8 a => Handle -> IO aSource
hGetUTF8 :: UTF8 a => Handle -> Int -> IO aSource
Be careful that you're sure you're not chopping a UTF8 char in two!
hGetUTF8NonBlocking :: UTF8 a => Handle -> Int -> IO aSource
Same warning as for hGetUTF8
flipUTF8 :: UTF8 a => a -> aSource
 ghci> putUTF8Ln $ flipUTF8 "[?np_bs!]"
 [¡sqbu¿]
unflipUTF8 :: UTF8 a => a -> aSource
 ghci> putUTF8Ln $ (unflipUTF8 . flipUTF8) "[?np_bs!]"
 [?np_bs!]
flipTab :: [(Int, Int)]Source
unflipTab :: [(Int, Int)]Source
showHex :: Int -> StringSource
toBits :: Word8 -> [Word8]Source
fromBits :: [Word8] -> Word8Source
Produced by Haddock version 2.3.0