{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
-- |
-- Module      : Data.ByteString.Base16
-- Copyright   : (c) 2011 MailRank, Inc.
--
-- License     : BSD
-- Maintainer  : Herbert Valerio Riedel <hvr@gnu.org>,
--               Mikhail Glushenkov <mikhail.glushenkov@gmail.com>,
--               Emily Pillmore <emilypi@cohomolo.gy>
-- Stability   : stable
-- Portability : non-portable
--
-- RFC 4648-compliant Base16 (Hexadecimal) encoding for 'ByteString' values.
-- For a complete Base16 encoding specification, please see <https://tools.ietf.org/html/rfc4648#section-8 RFC-4648 section 8>.
--
module Data.ByteString.Base16
( encode
, decode
, decodeLenient
) where

import Data.ByteString (empty)
import Data.ByteString.Base16.Internal (encodeLoop, decodeLoop, lenientLoop, mkBS, withBS)
import Data.ByteString.Internal (ByteString)

import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (plusPtr)

import GHC.ForeignPtr (mallocPlainForeignPtrBytes)

-- | Encode a 'ByteString' value in base16 (i.e. hexadecimal).
-- Encoded values will always have a length that is a multiple of 2.
--
-- === __Examples__:
--
-- > encode "foo"  == "666f6f"
--
encode :: ByteString -> ByteString
encode :: ByteString -> ByteString
encode ByteString
bs = ByteString -> (Ptr Word8 -> Int -> IO ByteString) -> ByteString
forall a. ByteString -> (Ptr Word8 -> Int -> IO a) -> a
withBS ByteString
bs Ptr Word8 -> Int -> IO ByteString
go
  where
    go :: Ptr Word8 -> Int -> IO ByteString
go !Ptr Word8
sptr !Int
slen
      | Int
slen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
forall a. Bounded a => a
maxBound Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2 =
        [Char] -> IO ByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.ByteString.Base16.encode: input too long"
      | Bool
otherwise = do
          let l :: Int
l = Int
slen Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2
          ForeignPtr Word8
dfp <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocPlainForeignPtrBytes Int
l
          ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
dfp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dptr ->
            Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
encodeLoop Ptr Word8
dptr Ptr Word8
sptr (Ptr Word8
sptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
slen)
          ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> Int -> ByteString
mkBS ForeignPtr Word8
dfp Int
l

-- | Decode a base16-encoded 'ByteString' value.
-- If errors are encountered during the decoding process,
-- then an error message and character offset will be returned in
-- the @Left@ clause of the coproduct.
--
-- === __Examples__:
--
-- > decode "666f6f"  == Right "foo"
-- > decode "66quux"  == Left "invalid character at offset: 2"
-- > decode "666quux" == Left "invalid character at offset: 3"
--
-- @since 1.0.0.0
--
decode :: ByteString -> Either String ByteString
decode :: ByteString -> Either [Char] ByteString
decode ByteString
bs = ByteString
-> (Ptr Word8 -> Int -> IO (Either [Char] ByteString))
-> Either [Char] ByteString
forall a. ByteString -> (Ptr Word8 -> Int -> IO a) -> a
withBS ByteString
bs Ptr Word8 -> Int -> IO (Either [Char] ByteString)
go
  where
    go :: Ptr Word8 -> Int -> IO (Either [Char] ByteString)
go !Ptr Word8
sptr !Int
slen
      | Int
slen Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Either [Char] ByteString -> IO (Either [Char] ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Char] ByteString -> IO (Either [Char] ByteString))
-> Either [Char] ByteString -> IO (Either [Char] ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either [Char] ByteString
forall a b. b -> Either a b
Right ByteString
empty
      | Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = Either [Char] ByteString -> IO (Either [Char] ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Char] ByteString -> IO (Either [Char] ByteString))
-> Either [Char] ByteString -> IO (Either [Char] ByteString)
forall a b. (a -> b) -> a -> b
$ [Char] -> Either [Char] ByteString
forall a b. a -> Either a b
Left [Char]
"invalid bytestring size"
      | Bool
otherwise = do
        ForeignPtr Word8
dfp <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocPlainForeignPtrBytes Int
q
        ForeignPtr Word8
-> (Ptr Word8 -> IO (Either [Char] ByteString))
-> IO (Either [Char] ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
dfp ((Ptr Word8 -> IO (Either [Char] ByteString))
 -> IO (Either [Char] ByteString))
-> (Ptr Word8 -> IO (Either [Char] ByteString))
-> IO (Either [Char] ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dptr ->
          ForeignPtr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> IO (Either [Char] ByteString)
decodeLoop ForeignPtr Word8
dfp Ptr Word8
dptr Ptr Word8
sptr (Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
sptr Int
slen)
      where
        !q :: Int
q = Int
slen Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2
        !r :: Int
r = Int
slen Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
2

-- | Decode a Base16-encoded 'ByteString' value leniently, using a
-- strategy that never fails.
--
-- /N.B./: this is not RFC 4648-compliant
--
-- === __Examples__:
--
-- > decodeLenient "666f6f"  == "foo"
-- > decodeLenient "66quuxx" == "f"
-- > decodeLenient "666quux" == "f"
-- > decodeLenient "666fquu" -- "fo"
--
-- @since 1.0.0.0
--
decodeLenient :: ByteString -> ByteString
decodeLenient :: ByteString -> ByteString
decodeLenient ByteString
bs = ByteString -> (Ptr Word8 -> Int -> IO ByteString) -> ByteString
forall a. ByteString -> (Ptr Word8 -> Int -> IO a) -> a
withBS ByteString
bs Ptr Word8 -> Int -> IO ByteString
go
  where
    go :: Ptr Word8 -> Int -> IO ByteString
go !Ptr Word8
sptr !Int
slen
      | Int
slen Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
      | Bool
otherwise = do
        ForeignPtr Word8
dfp <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocPlainForeignPtrBytes (Int
q Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2)
        ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
dfp ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dptr ->
          ForeignPtr Word8
-> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ByteString
lenientLoop ForeignPtr Word8
dfp Ptr Word8
dptr Ptr Word8
sptr (Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
sptr Int
slen)
      where
        !q :: Int
q = Int
slen Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2