-- | Copyright : (c) 2010 Jasper Van der Jeugt-- (c) 2010 - 2011 Simon Meier-- License : BSD3-style (see LICENSE)---- Maintainer : Simon Meier <iridcode@gmail.com>-- Portability : GHC---- Encodings using ASCII encoded Unicode characters.--moduleData.ByteString.Builder.Prim.ASCII(-- *** ASCIIchar7 -- **** Decimal numbers-- | Decimal encoding of numbers using ASCII encoded characters.,int8Dec ,int16Dec ,int32Dec ,int64Dec ,intDec ,word8Dec ,word16Dec ,word32Dec ,word64Dec ,wordDec {- -- These are the functions currently provided by Bryan O'Sullivans -- double-conversion library. -- -- , float -- , floatWith -- , double -- , doubleWith -}-- **** Hexadecimal numbers-- | Encoding positive integers as hexadecimal numbers using lower-case-- ASCII characters. The shortest possible representation is used. For-- example,---- > toLazyByteString (primBounded word16Hex 0x0a10) = "a10"---- Note that there is no support for using upper-case characters. Please-- contact the maintainer if your application cannot work without-- hexadecimal encodings that use upper-case characters.--,word8Hex ,word16Hex ,word32Hex ,word64Hex ,wordHex -- **** Fixed-width hexadecimal numbers---- | Encoding the bytes of fixed-width types as hexadecimal-- numbers using lower-case ASCII characters. For example,---- > toLazyByteString (primFixed word16HexFixed 0x0a10) = "0a10"--,int8HexFixed ,int16HexFixed ,int32HexFixed ,int64HexFixed ,word8HexFixed ,word16HexFixed ,word32HexFixed ,word64HexFixed ,floatHexFixed ,doubleHexFixed )whereimportData.ByteString.Internal.Type importData.ByteString.Builder.Prim.Binary importData.ByteString.Builder.Prim.Internal importData.ByteString.Builder.Prim.Internal.Floating importData.ByteString.Builder.Prim.Internal.Base16 importData.ByteString.Utils.UnalignedAccess importData.Char(ord)importForeign-- | Encode the least 7-bits of a 'Char' using the ASCII encoding.{-# INLINEchar7 #-}char7 ::FixedPrim Charchar7 :: FixedPrim Char char7 =(\Char c ->Int -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Word8) -> Int -> Word8 forall a b. (a -> b) -> a -> b $Char -> Int ordChar c Int -> Int -> Int forall a. Bits a => a -> a -> a .&.Int 0x7f)(Char -> Word8) -> FixedPrim Word8 -> FixedPrim Char forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word8 word8 -------------------------------------------------------------------------------- Decimal Encoding-------------------------------------------------------------------------------- Signed integers------------------{-# INLINEencodeIntDecimal #-}encodeIntDecimal ::Integrala =>Int->BoundedPrim a encodeIntDecimal :: forall a. Integral a => Int -> BoundedPrim a encodeIntDecimal Int bound =Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim Int bound ((a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a) -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a b. (a -> b) -> a -> b $CInt -> Ptr Word8 -> IO (Ptr Word8) c_int_dec (CInt -> Ptr Word8 -> IO (Ptr Word8)) -> (a -> CInt) -> a -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Decimal encoding of an 'Int8'.{-# INLINEint8Dec #-}int8Dec ::BoundedPrim Int8int8Dec :: BoundedPrim Int8 int8Dec =Int -> BoundedPrim Int8 forall a. Integral a => Int -> BoundedPrim a encodeIntDecimal Int 4-- | Decimal encoding of an 'Int16'.{-# INLINEint16Dec #-}int16Dec ::BoundedPrim Int16int16Dec :: BoundedPrim Int16 int16Dec =Int -> BoundedPrim Int16 forall a. Integral a => Int -> BoundedPrim a encodeIntDecimal Int 6-- | Decimal encoding of an 'Int32'.{-# INLINEint32Dec #-}int32Dec ::BoundedPrim Int32int32Dec :: BoundedPrim Int32 int32Dec =Int -> BoundedPrim Int32 forall a. Integral a => Int -> BoundedPrim a encodeIntDecimal Int 11-- | Decimal encoding of an 'Int64'.{-# INLINEint64Dec #-}int64Dec ::BoundedPrim Int64int64Dec :: BoundedPrim Int64 int64Dec =Int -> (Int64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Int64 forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim Int 20((Int64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Int64) -> (Int64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Int64 forall a b. (a -> b) -> a -> b $CLLong -> Ptr Word8 -> IO (Ptr Word8) c_long_long_int_dec (CLLong -> Ptr Word8 -> IO (Ptr Word8)) -> (Int64 -> CLLong) -> Int64 -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .Int64 -> CLLong forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Decimal encoding of an 'Int'.{-# INLINEintDec #-}intDec ::BoundedPrim IntintDec :: BoundedPrim Int intDec =BoundedPrim Int -> BoundedPrim Int -> BoundedPrim Int forall a. a -> a -> a caseWordSize_32_64 (Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Int32) -> BoundedPrim Int32 -> BoundedPrim Int forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Int32 int32Dec )(Int -> Int64 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int -> Int64) -> BoundedPrim Int64 -> BoundedPrim Int forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Int64 int64Dec )-- Unsigned integers--------------------{-# INLINEencodeWordDecimal #-}encodeWordDecimal ::Integrala =>Int->BoundedPrim a encodeWordDecimal :: forall a. Integral a => Int -> BoundedPrim a encodeWordDecimal Int bound =Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim Int bound ((a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a) -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a b. (a -> b) -> a -> b $CUInt -> Ptr Word8 -> IO (Ptr Word8) c_uint_dec (CUInt -> Ptr Word8 -> IO (Ptr Word8)) -> (a -> CUInt) -> a -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> CUInt forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Decimal encoding of a 'Word8'.{-# INLINEword8Dec #-}word8Dec ::BoundedPrim Word8word8Dec :: BoundedPrim Word8 word8Dec =Int -> BoundedPrim Word8 forall a. Integral a => Int -> BoundedPrim a encodeWordDecimal Int 3-- | Decimal encoding of a 'Word16'.{-# INLINEword16Dec #-}word16Dec ::BoundedPrim Word16word16Dec :: BoundedPrim Word16 word16Dec =Int -> BoundedPrim Word16 forall a. Integral a => Int -> BoundedPrim a encodeWordDecimal Int 5-- | Decimal encoding of a 'Word32'.{-# INLINEword32Dec #-}word32Dec ::BoundedPrim Word32word32Dec :: BoundedPrim Word32 word32Dec =Int -> BoundedPrim Word32 forall a. Integral a => Int -> BoundedPrim a encodeWordDecimal Int 10-- | Decimal encoding of a 'Word64'.{-# INLINEword64Dec #-}word64Dec ::BoundedPrim Word64word64Dec :: BoundedPrim Word64 word64Dec =Int -> (Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64 forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim Int 20((Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64) -> (Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64 forall a b. (a -> b) -> a -> b $CULLong -> Ptr Word8 -> IO (Ptr Word8) c_long_long_uint_dec (CULLong -> Ptr Word8 -> IO (Ptr Word8)) -> (Word64 -> CULLong) -> Word64 -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .Word64 -> CULLong forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Decimal encoding of a 'Word'.{-# INLINEwordDec #-}wordDec ::BoundedPrim WordwordDec :: BoundedPrim Word wordDec =BoundedPrim Word -> BoundedPrim Word -> BoundedPrim Word forall a. a -> a -> a caseWordSize_32_64 (Word -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word -> Word32) -> BoundedPrim Word32 -> BoundedPrim Word forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Word32 word32Dec )(Word -> Word64 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word -> Word64) -> BoundedPrim Word64 -> BoundedPrim Word forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Word64 word64Dec )-------------------------------------------------------------------------------- Hexadecimal Encoding-------------------------------------------------------------------------------- without lead---------------{-# INLINEencodeWordHex #-}encodeWordHex ::foralla .(Storablea ,Integrala )=>BoundedPrim a encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a encodeWordHex =Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim (Int 2Int -> Int -> Int forall a. Num a => a -> a -> a *a -> Int forall a. Storable a => a -> Int sizeOf(a forall a. HasCallStack => a undefined::a ))((a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a) -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a forall a b. (a -> b) -> a -> b $CUInt -> Ptr Word8 -> IO (Ptr Word8) c_uint_hex (CUInt -> Ptr Word8 -> IO (Ptr Word8)) -> (a -> CUInt) -> a -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> CUInt forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Hexadecimal encoding of a 'Word8'.{-# INLINEword8Hex #-}word8Hex ::BoundedPrim Word8word8Hex :: BoundedPrim Word8 word8Hex =BoundedPrim Word8 forall a. (Storable a, Integral a) => BoundedPrim a encodeWordHex -- | Hexadecimal encoding of a 'Word16'.{-# INLINEword16Hex #-}word16Hex ::BoundedPrim Word16word16Hex :: BoundedPrim Word16 word16Hex =BoundedPrim Word16 forall a. (Storable a, Integral a) => BoundedPrim a encodeWordHex -- | Hexadecimal encoding of a 'Word32'.{-# INLINEword32Hex #-}word32Hex ::BoundedPrim Word32word32Hex :: BoundedPrim Word32 word32Hex =BoundedPrim Word32 forall a. (Storable a, Integral a) => BoundedPrim a encodeWordHex -- | Hexadecimal encoding of a 'Word64'.{-# INLINEword64Hex #-}word64Hex ::BoundedPrim Word64word64Hex :: BoundedPrim Word64 word64Hex =Int -> (Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64 forall a. Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a boundedPrim Int 16((Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64) -> (Word64 -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim Word64 forall a b. (a -> b) -> a -> b $CULLong -> Ptr Word8 -> IO (Ptr Word8) c_long_long_uint_hex (CULLong -> Ptr Word8 -> IO (Ptr Word8)) -> (Word64 -> CULLong) -> Word64 -> Ptr Word8 -> IO (Ptr Word8) forall b c a. (b -> c) -> (a -> b) -> a -> c .Word64 -> CULLong forall a b. (Integral a, Num b) => a -> b fromIntegral-- | Hexadecimal encoding of a 'Word'.{-# INLINEwordHex #-}wordHex ::BoundedPrim WordwordHex :: BoundedPrim Word wordHex =BoundedPrim Word -> BoundedPrim Word -> BoundedPrim Word forall a. a -> a -> a caseWordSize_32_64 (Word -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word -> Word32) -> BoundedPrim Word32 -> BoundedPrim Word forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Word32 word32Hex )(Word -> Word64 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word -> Word64) -> BoundedPrim Word64 -> BoundedPrim Word forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< BoundedPrim Word64 word64Hex )-- fixed width; leading zeroes-------------------------------- | Encode a 'Word8' using 2 nibbles (hexadecimal digits).{-# INLINEword8HexFixed #-}word8HexFixed ::FixedPrim Word8word8HexFixed :: FixedPrim Word8 word8HexFixed =Int -> (Word8 -> Ptr Word8 -> IO ()) -> FixedPrim Word8 forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a fixedPrim Int 2((Word8 -> Ptr Word8 -> IO ()) -> FixedPrim Word8) -> (Word8 -> Ptr Word8 -> IO ()) -> FixedPrim Word8 forall a b. (a -> b) -> a -> b $\Word8 x Ptr Word8 op ->doWord16 enc <-EncodingTable -> Word8 -> IO Word16 encode8_as_16h EncodingTable lowerTable Word8 x Word16 -> Ptr Word8 -> IO () unalignedWriteU16 Word16 enc Ptr Word8 op -- | Encode a 'Word16' using 4 nibbles.{-# INLINEword16HexFixed #-}word16HexFixed ::FixedPrim Word16word16HexFixed :: FixedPrim Word16 word16HexFixed =(\Word16 x ->(Word16 -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word16 -> Word8) -> Word16 -> Word8 forall a b. (a -> b) -> a -> b $Word16 x Word16 -> Int -> Word16 forall a. Bits a => a -> Int -> a `shiftR`Int 8,Word16 -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegralWord16 x ))(Word16 -> (Word8, Word8)) -> FixedPrim (Word8, Word8) -> FixedPrim Word16 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word8 -> FixedPrim Word8 -> FixedPrim (Word8, Word8) forall a b. FixedPrim a -> FixedPrim b -> FixedPrim (a, b) pairF FixedPrim Word8 word8HexFixed FixedPrim Word8 word8HexFixed -- | Encode a 'Word32' using 8 nibbles.{-# INLINEword32HexFixed #-}word32HexFixed ::FixedPrim Word32word32HexFixed :: FixedPrim Word32 word32HexFixed =(\Word32 x ->(Word32 -> Word16 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word32 -> Word16) -> Word32 -> Word16 forall a b. (a -> b) -> a -> b $Word32 x Word32 -> Int -> Word32 forall a. Bits a => a -> Int -> a `shiftR`Int 16,Word32 -> Word16 forall a b. (Integral a, Num b) => a -> b fromIntegralWord32 x ))(Word32 -> (Word16, Word16)) -> FixedPrim (Word16, Word16) -> FixedPrim Word32 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word16 -> FixedPrim Word16 -> FixedPrim (Word16, Word16) forall a b. FixedPrim a -> FixedPrim b -> FixedPrim (a, b) pairF FixedPrim Word16 word16HexFixed FixedPrim Word16 word16HexFixed -- | Encode a 'Word64' using 16 nibbles.{-# INLINEword64HexFixed #-}word64HexFixed ::FixedPrim Word64word64HexFixed :: FixedPrim Word64 word64HexFixed =(\Word64 x ->(Word64 -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral(Word64 -> Word32) -> Word64 -> Word32 forall a b. (a -> b) -> a -> b $Word64 x Word64 -> Int -> Word64 forall a. Bits a => a -> Int -> a `shiftR`Int 32,Word64 -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegralWord64 x ))(Word64 -> (Word32, Word32)) -> FixedPrim (Word32, Word32) -> FixedPrim Word64 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word32 -> FixedPrim Word32 -> FixedPrim (Word32, Word32) forall a b. FixedPrim a -> FixedPrim b -> FixedPrim (a, b) pairF FixedPrim Word32 word32HexFixed FixedPrim Word32 word32HexFixed -- | Encode a 'Int8' using 2 nibbles (hexadecimal digits).{-# INLINEint8HexFixed #-}int8HexFixed ::FixedPrim Int8int8HexFixed :: FixedPrim Int8 int8HexFixed =Int8 -> Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int8 -> Word8) -> FixedPrim Word8 -> FixedPrim Int8 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word8 word8HexFixed -- | Encode a 'Int16' using 4 nibbles.{-# INLINEint16HexFixed #-}int16HexFixed ::FixedPrim Int16int16HexFixed :: FixedPrim Int16 int16HexFixed =Int16 -> Word16 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int16 -> Word16) -> FixedPrim Word16 -> FixedPrim Int16 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word16 word16HexFixed -- | Encode a 'Int32' using 8 nibbles.{-# INLINEint32HexFixed #-}int32HexFixed ::FixedPrim Int32int32HexFixed :: FixedPrim Int32 int32HexFixed =Int32 -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int32 -> Word32) -> FixedPrim Word32 -> FixedPrim Int32 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word32 word32HexFixed -- | Encode a 'Int64' using 16 nibbles.{-# INLINEint64HexFixed #-}int64HexFixed ::FixedPrim Int64int64HexFixed :: FixedPrim Int64 int64HexFixed =Int64 -> Word64 forall a b. (Integral a, Num b) => a -> b fromIntegral(Int64 -> Word64) -> FixedPrim Word64 -> FixedPrim Int64 forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b >$< FixedPrim Word64 word64HexFixed -- | Encode an IEEE 'Float' using 8 nibbles.{-# INLINEfloatHexFixed #-}floatHexFixed ::FixedPrim FloatfloatHexFixed :: FixedPrim Float floatHexFixed =FixedPrim Word32 -> FixedPrim Float encodeFloatViaWord32F FixedPrim Word32 word32HexFixed -- | Encode an IEEE 'Double' using 16 nibbles.{-# INLINEdoubleHexFixed #-}doubleHexFixed ::FixedPrim DoubledoubleHexFixed :: FixedPrim Double doubleHexFixed =FixedPrim Word64 -> FixedPrim Double encodeDoubleViaWord64F FixedPrim Word64 word64HexFixed