{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
-- |
-- Module      : Data.ByteString.Base16.Lazy
-- 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 lazy '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.Lazy
( encode
, decode
, decodeLenient
) where


import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Base16 as B16
import Data.ByteString.Base16.Internal
import Data.ByteString.Lazy.Internal (ByteString(..))

-- | 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
Empty = ByteString
Empty
encode (Chunk ByteString
c ByteString
cs) = ByteString -> ByteString -> ByteString
Chunk (ByteString -> ByteString
B16.encode ByteString
c) (ByteString -> ByteString
encode ByteString
cs)

-- | 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 "666quu" == Left "invalid character at offset: 3"
--
-- @since 1.0.0.0
--
decode :: ByteString -> Either String ByteString
decode :: ByteString -> Either String ByteString
decode = Either String ByteString -> Either String ByteString
forall a. Either a ByteString -> Either a ByteString
f (Either String ByteString -> Either String ByteString)
-> (ByteString -> Either String ByteString)
-> ByteString
-> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
B16.decode (ByteString -> Either String ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.concat ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
LBS.toChunks
  where
    f :: Either a ByteString -> Either a ByteString
f (Left a
t) = a -> Either a ByteString
forall a b. a -> Either a b
Left a
t
    f (Right ByteString
bs') = ByteString -> Either a ByteString
forall a b. b -> Either a b
Right ([ByteString] -> ByteString
LBS.fromChunks [ByteString
bs'])

-- | 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 "66quux" == "f"
-- > decodeLenient "666quu" == "f"
-- > decodeLenient "666fqu" == "fo"
--
-- @since 1.0.0.0
--
decodeLenient :: ByteString -> ByteString
decodeLenient :: ByteString -> ByteString
decodeLenient = [ByteString] -> ByteString
LBS.fromChunks
    ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
B16.decodeLenient
    ([ByteString] -> [ByteString])
-> (ByteString -> [ByteString]) -> ByteString -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> [ByteString]
reChunk
    ([ByteString] -> [ByteString])
-> (ByteString -> [ByteString]) -> ByteString -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Word8 -> Bool) -> ByteString -> ByteString
BS.filter ((Word8 -> ByteString -> Bool) -> ByteString -> Word8 -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> ByteString -> Bool
BS.elem ByteString
extendedHex))
    ([ByteString] -> [ByteString])
-> (ByteString -> [ByteString]) -> ByteString -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
LBS.toChunks
  where
    extendedHex :: ByteString
extendedHex = [Word8] -> ByteString
BS.pack ((Char -> Word8) -> String -> [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Word8
c2w String
"0123456789abcdefABCDEF")