Copyright | (c) Matt Morrow 2008 Francesco Ariis 2022 |
---|---|
License | BSD3 |
Maintainer | Francesco Ariis <fa-ml@ariis.it> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Lightweight UTF8 handling.
Synopsis
- class UTF8 a where
- encode :: a -> ByteString
- decode :: ByteString -> a
- 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
- data Int8
- data Int16
- data Int32
- data Word
- data Word8
- data Word16
- data Word32
- c2w :: Char -> Word32
- w2c :: Word32 -> Char
Documentation
Instances:
ByteString
, String
, [Word32]
, [Word]
, [Int32]
, [Int]
encode :: a -> ByteString Source #
decode :: ByteString -> a Source #
Instances
UTF8 ByteString Source # | |
Defined in Codec.Binary.UTF8.Light encode :: ByteString -> ByteString Source # decode :: ByteString -> ByteString Source # | |
UTF8 String Source # | |
Defined in Codec.Binary.UTF8.Light encode :: String -> ByteString Source # decode :: ByteString -> String Source # | |
UTF8 [Int32] Source # | |
Defined in Codec.Binary.UTF8.Light encode :: [Int32] -> ByteString Source # decode :: ByteString -> [Int32] Source # | |
UTF8 [Word32] Source # | |
Defined in Codec.Binary.UTF8.Light encode :: [Word32] -> ByteString Source # decode :: ByteString -> [Word32] Source # | |
UTF8 [Int] Source # | |
Defined in Codec.Binary.UTF8.Light encode :: [Int] -> ByteString Source # decode :: ByteString -> [Int] Source # | |
UTF8 [Word] Source # | |
Defined in Codec.Binary.UTF8.Light encode :: [Word] -> ByteString Source # decode :: ByteString -> [Word] Source # |
countUTF8 :: ByteString -> [Int] Source #
Lengths in Word8s
decodeUTF8 :: ByteString -> [Word32] Source #
encodeUTF8 :: [Word32] -> ByteString Source #
encodeUTF8' :: [Word32] -> [[Word8]] Source #
Word32s not representing valid UTF8 chars are dropped.
withUTF8 :: UTF8 a => a -> (ByteString -> b) -> b Source #
hGetUTF8 :: UTF8 a => Handle -> Int -> IO a Source #
Be careful that you're sure you're not chopping a UTF8 char in two!
unflipUTF8 :: UTF8 a => a -> a Source #
ghci> putUTF8Ln $ (unflipUTF8 . flipUTF8) "[?np_bs!]" [?np_bs!]
8-bit signed integer type
Instances
Bits Int8 | Since: base-2.1 |
Defined in GHC.Int (.&.) :: Int8 -> Int8 -> Int8 # (.|.) :: Int8 -> Int8 -> Int8 # complement :: Int8 -> Int8 # shift :: Int8 -> Int -> Int8 # rotate :: Int8 -> Int -> Int8 # setBit :: Int8 -> Int -> Int8 # clearBit :: Int8 -> Int -> Int8 # complementBit :: Int8 -> Int -> Int8 # testBit :: Int8 -> Int -> Bool # bitSizeMaybe :: Int8 -> Maybe Int # shiftL :: Int8 -> Int -> Int8 # unsafeShiftL :: Int8 -> Int -> Int8 # shiftR :: Int8 -> Int -> Int8 # unsafeShiftR :: Int8 -> Int -> Int8 # rotateL :: Int8 -> Int -> Int8 # | |
FiniteBits Int8 | Since: base-4.6.0.0 |
Defined in GHC.Int | |
Bounded Int8 | Since: base-2.1 |
Enum Int8 | Since: base-2.1 |
Ix Int8 | Since: base-2.1 |
Num Int8 | Since: base-2.1 |
Read Int8 | Since: base-2.1 |
Integral Int8 | Since: base-2.1 |
Real Int8 | Since: base-2.1 |
Defined in GHC.Int toRational :: Int8 -> Rational # | |
Show Int8 | Since: base-2.1 |
Eq Int8 | Since: base-2.1 |
Ord Int8 | Since: base-2.1 |
16-bit signed integer type
Instances
32-bit signed integer type
Instances
Instances
Bits Word | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Word -> Word -> Word # (.|.) :: Word -> Word -> Word # complement :: Word -> Word # shift :: Word -> Int -> Word # rotate :: Word -> Int -> Word # setBit :: Word -> Int -> Word # clearBit :: Word -> Int -> Word # complementBit :: Word -> Int -> Word # testBit :: Word -> Int -> Bool # bitSizeMaybe :: Word -> Maybe Int # shiftL :: Word -> Int -> Word # unsafeShiftL :: Word -> Int -> Word # shiftR :: Word -> Int -> Word # unsafeShiftR :: Word -> Int -> Word # rotateL :: Word -> Int -> Word # | |
FiniteBits Word | Since: base-4.6.0.0 |
Defined in GHC.Bits | |
Bounded Word | Since: base-2.1 |
Enum Word | Since: base-2.1 |
Num Word | Since: base-2.1 |
Read Word | Since: base-4.5.0.0 |
Integral Word | Since: base-2.1 |
Real Word | Since: base-2.1 |
Defined in GHC.Real toRational :: Word -> Rational # | |
Show Word | Since: base-2.1 |
Eq Word | |
Ord Word | |
Foldable (UWord :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UWord m -> m # foldMap :: Monoid m => (a -> m) -> UWord a -> m # foldMap' :: Monoid m => (a -> m) -> UWord a -> m # foldr :: (a -> b -> b) -> b -> UWord a -> b # foldr' :: (a -> b -> b) -> b -> UWord a -> b # foldl :: (b -> a -> b) -> b -> UWord a -> b # foldl' :: (b -> a -> b) -> b -> UWord a -> b # foldr1 :: (a -> a -> a) -> UWord a -> a # foldl1 :: (a -> a -> a) -> UWord a -> a # elem :: Eq a => a -> UWord a -> Bool # maximum :: Ord a => UWord a -> a # minimum :: Ord a => UWord a -> a # | |
Traversable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
UTF8 [Word] Source # | |
Defined in Codec.Binary.UTF8.Light encode :: [Word] -> ByteString Source # decode :: ByteString -> [Word] Source # |
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type