-- | Pretty bytestrings via printing each byte as two hex digits.
--
-- This is primarily for aeson and when we want better 'show'ing of non-textual
-- bytestrings. It's not really binrep-related, but it needs _somewhere_ to go
-- and my projects that need it usually also touch binrep, so here it is.
--
-- Sadly, we can't use it to make aeson print integers as hex literals. It only
-- deals in Scientifics, and if we tried printing them as strings, it would
-- quote them. I need a YAML-like with better literals...

module Binrep.Extra.HexByteString where

import GHC.Generics ( Generic )
import Data.Data ( Data )

import Data.ByteString qualified as B
import Data.ByteString.Short qualified as B.Short
import Data.Char qualified as Char
import Data.Word
import Data.Text qualified as Text
import Data.Text ( Text )
import Data.List as List

import Text.Megaparsec hiding ( parse )
import Text.Megaparsec.Char qualified as MC
import Data.Void

import Data.Aeson

-- TODO could add some integer instances to print them as hex too

-- No harm in being polymorphic over the byte representation.
newtype Hex a = Hex { forall a. Hex a -> a
unHex :: a }
    deriving stock (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Hex a) x -> Hex a
forall a x. Hex a -> Rep (Hex a) x
$cto :: forall a x. Rep (Hex a) x -> Hex a
$cfrom :: forall a x. Hex a -> Rep (Hex a) x
Generic, Hex a -> DataType
Hex a -> Constr
forall {a}. Data a => Typeable (Hex a)
forall a. Data a => Hex a -> DataType
forall a. Data a => Hex a -> Constr
forall a. Data a => (forall b. Data b => b -> b) -> Hex a -> Hex a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Hex a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Hex a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Hex a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hex a -> c (Hex a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Hex a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Hex a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Hex a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hex a -> c (Hex a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Hex a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Hex a -> m (Hex a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Hex a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Hex a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Hex a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Hex a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r
gmapT :: (forall b. Data b => b -> b) -> Hex a -> Hex a
$cgmapT :: forall a. Data a => (forall b. Data b => b -> b) -> Hex a -> Hex a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Hex a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Hex a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Hex a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Hex a))
dataTypeOf :: Hex a -> DataType
$cdataTypeOf :: forall a. Data a => Hex a -> DataType
toConstr :: Hex a -> Constr
$ctoConstr :: forall a. Data a => Hex a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Hex a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Hex a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hex a -> c (Hex a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hex a -> c (Hex a)
Data)
    deriving Hex a -> Hex a -> Bool
forall a. Eq a => Hex a -> Hex a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hex a -> Hex a -> Bool
$c/= :: forall a. Eq a => Hex a -> Hex a -> Bool
== :: Hex a -> Hex a -> Bool
$c== :: forall a. Eq a => Hex a -> Hex a -> Bool
Eq via a

-- But most users will probably just want this.
type HexByteString = Hex B.ByteString

instance Show (Hex B.ByteString) where
    show :: Hex ByteString -> String
show = Text -> String
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> [Word8]) -> a -> Text
prettyHexByteString ByteString -> [Word8]
B.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Hex a -> a
unHex

instance FromJSON (Hex B.ByteString) where
    parseJSON :: Value -> Parser (Hex ByteString)
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"hex bytestring" forall a b. (a -> b) -> a -> b
$ \Text
t ->
        case forall e s a. (Ord e, Stream s) => Parsec e s a -> s -> Maybe a
parseMaybe @Void (forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char) =>
([Word8] -> a) -> m a
parseHexByteString [Word8] -> ByteString
B.pack) Text
t of
          Maybe ByteString
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"failed to parse hex bytestring (TODO)"
          Just ByteString
t' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Hex a
Hex ByteString
t')

instance ToJSON   (Hex B.ByteString) where
    toJSON :: Hex ByteString -> Value
toJSON = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> [Word8]) -> a -> Text
prettyHexByteString ByteString -> [Word8]
B.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Hex a -> a
unHex

instance Show (Hex B.Short.ShortByteString) where
    show :: Hex ShortByteString -> String
show = Text -> String
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> [Word8]) -> a -> Text
prettyHexByteString ShortByteString -> [Word8]
B.Short.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Hex a -> a
unHex

instance FromJSON (Hex B.Short.ShortByteString) where
    parseJSON :: Value -> Parser (Hex ShortByteString)
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"hex bytestring" forall a b. (a -> b) -> a -> b
$ \Text
t ->
        case forall e s a. (Ord e, Stream s) => Parsec e s a -> s -> Maybe a
parseMaybe @Void (forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char) =>
([Word8] -> a) -> m a
parseHexByteString [Word8] -> ShortByteString
B.Short.pack) Text
t of
          Maybe ShortByteString
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"failed to parse hex bytestring (TODO)"
          Just ShortByteString
t' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. a -> Hex a
Hex ShortByteString
t')

instance ToJSON   (Hex B.Short.ShortByteString) where
    toJSON :: Hex ShortByteString -> Value
toJSON = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> [Word8]) -> a -> Text
prettyHexByteString ShortByteString -> [Word8]
B.Short.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Hex a -> a
unHex

-- | A hex bytestring looks like this: @00 01 89 8a   FEff@. You can mix and
-- match capitalization and spacing, but I prefer to space each byte, full caps.
parseHexByteString
    :: (MonadParsec e s m, Token s ~ Char)
    => ([Word8] -> a) -> m a
parseHexByteString :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char) =>
([Word8] -> a) -> m a
parseHexByteString [Word8] -> a
pack = [Word8] -> a
pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
parseHexByte forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy` forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
MC.hspace

-- | Parse a byte formatted as two hex digits e.g. EF. You _must_ provide both
-- nibbles e.g. @0F@, not @F@. They cannot be spaced e.g. @E F@ is invalid.
--
-- Returns a value 0-255, so can fit in any Num type that can store that.
parseHexByte :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
parseHexByte :: forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
parseHexByte = do
    Char
c1 <- forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
MC.hexDigitChar
    Char
c2 <- forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
MC.hexDigitChar
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ a
0x10 forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c1) forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
Char.digitToInt Char
c2)

-- | Pretty print to default format @00 12 AB FF@: space between each byte, all
--   caps.
--
-- This format I consider most human readable. I prefer caps to draw attention
-- to this being data instead of text (you don't see that many capital letters
-- packed together in prose).
prettyHexByteString :: (a -> [Word8]) -> a -> Text
prettyHexByteString :: forall a. (a -> [Word8]) -> a -> Text
prettyHexByteString a -> [Word8]
unpack =
      [Text] -> Text
Text.concat
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
List.intersperse (Char -> Text
Text.singleton Char
' ')
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char, Char) -> Text
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> Word8 -> (Char, Char)
prettyHexByte Char -> Char
Char.toUpper)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Word8]
unpack
  where
    f :: (Char, Char) -> Text
    f :: (Char, Char) -> Text
f (Char
c1, Char
c2) = Char -> Text -> Text
Text.cons Char
c1 forall a b. (a -> b) -> a -> b
$ Char -> Text
Text.singleton Char
c2

prettyHexByte :: (Char -> Char) -> Word8 -> (Char, Char)
prettyHexByte :: (Char -> Char) -> Word8 -> (Char, Char)
prettyHexByte Char -> Char
f Word8
w = (Int -> Char
prettyNibble Int
h, Int -> Char
prettyNibble Int
l)
  where
    (Int
h,Int
l) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w forall a. Integral a => a -> a -> (a, a)
`divMod` Int
0x10
    prettyNibble :: Int -> Char
prettyNibble = Char -> Char
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
Char.intToDigit -- Char.intToDigit returns lower case

-- | Pretty print to "compact" format @0012abff@ (often output by hashers).
prettyHexByteStringCompact :: (a -> [Word8]) -> a -> Text
prettyHexByteStringCompact :: forall a. (a -> [Word8]) -> a -> Text
prettyHexByteStringCompact a -> [Word8]
unpack =
    [Text] -> Text
Text.concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char, Char) -> Text
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> Word8 -> (Char, Char)
prettyHexByte forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Word8]
unpack
  where
    f :: (Char, Char) -> Text
    f :: (Char, Char) -> Text
f (Char
c1, Char
c2) = Char -> Text -> Text
Text.cons Char
c1 forall a b. (a -> b) -> a -> b
$ Char -> Text
Text.singleton Char
c2