{-# LANGUAGE ScopedTypeVariables, ForeignFunctionInterface #-}
{-# LANGUAGE Trustworthy #-}
-- | 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.
--
module Data.ByteString.Builder.Prim.ASCII
    (

     -- *** ASCII
     char7

      -- **** 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

    ) where

import Data.ByteString.Builder.Prim.Binary
import Data.ByteString.Builder.Prim.Internal
import Data.ByteString.Builder.Prim.Internal.Floating
import Data.ByteString.Builder.Prim.Internal.Base16

import Data.Char (ord)

import Foreign
import Foreign.C.Types

-- | Encode the least 7-bits of a 'Char' using the ASCII encoding.
{-# INLINE char7 #-}
char7 :: FixedPrim Char
char7 :: FixedPrim Char
char7 = (\Char
c -> forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Char -> Int
ord Char
c forall a. Bits a => a -> a -> a
.&. Int
0x7f) forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word8
word8


------------------------------------------------------------------------------
-- Decimal Encoding
------------------------------------------------------------------------------

-- Signed integers
------------------

foreign import ccall unsafe "static _hs_bytestring_int_dec" c_int_dec
    :: CInt -> Ptr Word8 -> IO (Ptr Word8)

foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec" c_long_long_int_dec
    :: CLLong -> Ptr Word8 -> IO (Ptr Word8)

{-# INLINE encodeIntDecimal #-}
encodeIntDecimal :: Integral a => Int -> BoundedPrim a
encodeIntDecimal :: forall a. Integral a => Int -> BoundedPrim a
encodeIntDecimal Int
bound = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim Int
bound forall a b. (a -> b) -> a -> b
$ CInt -> Ptr Word8 -> IO (Ptr Word8)
c_int_dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Decimal encoding of an 'Int8'.
{-# INLINE int8Dec #-}
int8Dec :: BoundedPrim Int8
int8Dec :: BoundedPrim Int8
int8Dec = forall a. Integral a => Int -> BoundedPrim a
encodeIntDecimal Int
4

-- | Decimal encoding of an 'Int16'.
{-# INLINE int16Dec #-}
int16Dec :: BoundedPrim Int16
int16Dec :: BoundedPrim Int16
int16Dec = forall a. Integral a => Int -> BoundedPrim a
encodeIntDecimal Int
6


-- | Decimal encoding of an 'Int32'.
{-# INLINE int32Dec #-}
int32Dec :: BoundedPrim Int32
int32Dec :: BoundedPrim Int32
int32Dec = forall a. Integral a => Int -> BoundedPrim a
encodeIntDecimal Int
11

-- | Decimal encoding of an 'Int64'.
{-# INLINE int64Dec #-}
int64Dec :: BoundedPrim Int64
int64Dec :: BoundedPrim Int64
int64Dec = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim Int
20 forall a b. (a -> b) -> a -> b
$ CLLong -> Ptr Word8 -> IO (Ptr Word8)
c_long_long_int_dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Decimal encoding of an 'Int'.
{-# INLINE intDec #-}
intDec :: BoundedPrim Int
intDec :: BoundedPrim Int
intDec = forall a. a -> a -> a
caseWordSize_32_64
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< BoundedPrim Int32
int32Dec)
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< BoundedPrim Int64
int64Dec)


-- Unsigned integers
--------------------

foreign import ccall unsafe "static _hs_bytestring_uint_dec" c_uint_dec
    :: CUInt -> Ptr Word8 -> IO (Ptr Word8)

foreign import ccall unsafe "static _hs_bytestring_long_long_uint_dec" c_long_long_uint_dec
    :: CULLong -> Ptr Word8 -> IO (Ptr Word8)

{-# INLINE encodeWordDecimal #-}
encodeWordDecimal :: Integral a => Int -> BoundedPrim a
encodeWordDecimal :: forall a. Integral a => Int -> BoundedPrim a
encodeWordDecimal Int
bound = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim Int
bound forall a b. (a -> b) -> a -> b
$ CUInt -> Ptr Word8 -> IO (Ptr Word8)
c_uint_dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Decimal encoding of a 'Word8'.
{-# INLINE word8Dec #-}
word8Dec :: BoundedPrim Word8
word8Dec :: BoundedPrim Word8
word8Dec = forall a. Integral a => Int -> BoundedPrim a
encodeWordDecimal Int
3

-- | Decimal encoding of a 'Word16'.
{-# INLINE word16Dec #-}
word16Dec :: BoundedPrim Word16
word16Dec :: BoundedPrim Word16
word16Dec = forall a. Integral a => Int -> BoundedPrim a
encodeWordDecimal Int
5

-- | Decimal encoding of a 'Word32'.
{-# INLINE word32Dec #-}
word32Dec :: BoundedPrim Word32
word32Dec :: BoundedPrim Word32
word32Dec = forall a. Integral a => Int -> BoundedPrim a
encodeWordDecimal Int
10

-- | Decimal encoding of a 'Word64'.
{-# INLINE word64Dec #-}
word64Dec :: BoundedPrim Word64
word64Dec :: BoundedPrim Word64
word64Dec = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim Int
20 forall a b. (a -> b) -> a -> b
$ CULLong -> Ptr Word8 -> IO (Ptr Word8)
c_long_long_uint_dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Decimal encoding of a 'Word'.
{-# INLINE wordDec #-}
wordDec :: BoundedPrim Word
wordDec :: BoundedPrim Word
wordDec = forall a. a -> a -> a
caseWordSize_32_64
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< BoundedPrim Word32
word32Dec)
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< BoundedPrim Word64
word64Dec)

------------------------------------------------------------------------------
-- Hexadecimal Encoding
------------------------------------------------------------------------------

-- without lead
---------------

foreign import ccall unsafe "static _hs_bytestring_uint_hex" c_uint_hex
    :: CUInt -> Ptr Word8 -> IO (Ptr Word8)

foreign import ccall unsafe "static _hs_bytestring_long_long_uint_hex" c_long_long_uint_hex
    :: CULLong -> Ptr Word8 -> IO (Ptr Word8)

{-# INLINE encodeWordHex #-}
encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex =
    forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim (Int
2 forall a. Num a => a -> a -> a
* forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: a)) forall a b. (a -> b) -> a -> b
$ CUInt -> Ptr Word8 -> IO (Ptr Word8)
c_uint_hex  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Hexadecimal encoding of a 'Word8'.
{-# INLINE word8Hex #-}
word8Hex :: BoundedPrim Word8
word8Hex :: BoundedPrim Word8
word8Hex = forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex

-- | Hexadecimal encoding of a 'Word16'.
{-# INLINE word16Hex #-}
word16Hex :: BoundedPrim Word16
word16Hex :: BoundedPrim Word16
word16Hex = forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex

-- | Hexadecimal encoding of a 'Word32'.
{-# INLINE word32Hex #-}
word32Hex :: BoundedPrim Word32
word32Hex :: BoundedPrim Word32
word32Hex = forall a. (Storable a, Integral a) => BoundedPrim a
encodeWordHex

-- | Hexadecimal encoding of a 'Word64'.
{-# INLINE word64Hex #-}
word64Hex :: BoundedPrim Word64
word64Hex :: BoundedPrim Word64
word64Hex = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim Int
16 forall a b. (a -> b) -> a -> b
$ CULLong -> Ptr Word8 -> IO (Ptr Word8)
c_long_long_uint_hex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Hexadecimal encoding of a 'Word'.
{-# INLINE wordHex #-}
wordHex :: BoundedPrim Word
wordHex :: BoundedPrim Word
wordHex = forall a. a -> a -> a
caseWordSize_32_64
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< BoundedPrim Word32
word32Hex)
    (forall a b. (Integral a, Num b) => a -> b
fromIntegral 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).
{-# INLINE word8HexFixed #-}
word8HexFixed :: FixedPrim Word8
word8HexFixed :: FixedPrim Word8
word8HexFixed = forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
fixedPrim Int
2 forall a b. (a -> b) -> a -> b
$
    \Word8
x Ptr Word8
op -> forall a. Storable a => Ptr a -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
op) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EncodingTable -> Word8 -> IO Word16
encode8_as_16h EncodingTable
lowerTable Word8
x

-- | Encode a 'Word16' using 4 nibbles.
{-# INLINE word16HexFixed #-}
word16HexFixed :: FixedPrim Word16
word16HexFixed :: FixedPrim Word16
word16HexFixed =
    (\Word16
x -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Word16
x forall a. Bits a => a -> Int -> a
`shiftR` Int
8, forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
x))
      forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< forall a b. FixedPrim a -> FixedPrim b -> FixedPrim (a, b)
pairF FixedPrim Word8
word8HexFixed FixedPrim Word8
word8HexFixed

-- | Encode a 'Word32' using 8 nibbles.
{-# INLINE word32HexFixed #-}
word32HexFixed :: FixedPrim Word32
word32HexFixed :: FixedPrim Word32
word32HexFixed =
    (\Word32
x -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Word32
x forall a. Bits a => a -> Int -> a
`shiftR` Int
16, forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x))
      forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< forall a b. FixedPrim a -> FixedPrim b -> FixedPrim (a, b)
pairF FixedPrim Word16
word16HexFixed FixedPrim Word16
word16HexFixed
-- | Encode a 'Word64' using 16 nibbles.
{-# INLINE word64HexFixed #-}
word64HexFixed :: FixedPrim Word64
word64HexFixed :: FixedPrim Word64
word64HexFixed =
    (\Word64
x -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Word64
x forall a. Bits a => a -> Int -> a
`shiftR` Int
32, forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
x))
      forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< 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).
{-# INLINE int8HexFixed #-}
int8HexFixed :: FixedPrim Int8
int8HexFixed :: FixedPrim Int8
int8HexFixed = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word8
word8HexFixed

-- | Encode a 'Int16' using 4 nibbles.
{-# INLINE int16HexFixed #-}
int16HexFixed :: FixedPrim Int16
int16HexFixed :: FixedPrim Int16
int16HexFixed = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word16
word16HexFixed

-- | Encode a 'Int32' using 8 nibbles.
{-# INLINE int32HexFixed #-}
int32HexFixed :: FixedPrim Int32
int32HexFixed :: FixedPrim Int32
int32HexFixed = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word32
word32HexFixed

-- | Encode a 'Int64' using 16 nibbles.
{-# INLINE int64HexFixed #-}
int64HexFixed :: FixedPrim Int64
int64HexFixed :: FixedPrim Int64
int64HexFixed = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
>$< FixedPrim Word64
word64HexFixed

-- | Encode an IEEE 'Float' using 8 nibbles.
{-# INLINE floatHexFixed #-}
floatHexFixed :: FixedPrim Float
floatHexFixed :: FixedPrim Float
floatHexFixed = FixedPrim Word32 -> FixedPrim Float
encodeFloatViaWord32F FixedPrim Word32
word32HexFixed

-- | Encode an IEEE 'Double' using 16 nibbles.
{-# INLINE doubleHexFixed #-}
doubleHexFixed :: FixedPrim Double
doubleHexFixed :: FixedPrim Double
doubleHexFixed = FixedPrim Word64 -> FixedPrim Double
encodeDoubleViaWord64F FixedPrim Word64
word64HexFixed