module Util.ByteString
  ( HexJSONByteString(..)
  ) where
import Data.Aeson (FromJSON(..), ToJSON(..), withText)
import Text.Hex (decodeHex, encodeHex)
newtype HexJSONByteString = HexJSONByteString { HexJSONByteString -> ByteString
unHexJSONByteString :: ByteString }
  deriving stock (HexJSONByteString -> HexJSONByteString -> Bool
(HexJSONByteString -> HexJSONByteString -> Bool)
-> (HexJSONByteString -> HexJSONByteString -> Bool)
-> Eq HexJSONByteString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HexJSONByteString -> HexJSONByteString -> Bool
$c/= :: HexJSONByteString -> HexJSONByteString -> Bool
== :: HexJSONByteString -> HexJSONByteString -> Bool
$c== :: HexJSONByteString -> HexJSONByteString -> Bool
Eq, Eq HexJSONByteString
Eq HexJSONByteString =>
(HexJSONByteString -> HexJSONByteString -> Ordering)
-> (HexJSONByteString -> HexJSONByteString -> Bool)
-> (HexJSONByteString -> HexJSONByteString -> Bool)
-> (HexJSONByteString -> HexJSONByteString -> Bool)
-> (HexJSONByteString -> HexJSONByteString -> Bool)
-> (HexJSONByteString -> HexJSONByteString -> HexJSONByteString)
-> (HexJSONByteString -> HexJSONByteString -> HexJSONByteString)
-> Ord HexJSONByteString
HexJSONByteString -> HexJSONByteString -> Bool
HexJSONByteString -> HexJSONByteString -> Ordering
HexJSONByteString -> HexJSONByteString -> HexJSONByteString
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HexJSONByteString -> HexJSONByteString -> HexJSONByteString
$cmin :: HexJSONByteString -> HexJSONByteString -> HexJSONByteString
max :: HexJSONByteString -> HexJSONByteString -> HexJSONByteString
$cmax :: HexJSONByteString -> HexJSONByteString -> HexJSONByteString
>= :: HexJSONByteString -> HexJSONByteString -> Bool
$c>= :: HexJSONByteString -> HexJSONByteString -> Bool
> :: HexJSONByteString -> HexJSONByteString -> Bool
$c> :: HexJSONByteString -> HexJSONByteString -> Bool
<= :: HexJSONByteString -> HexJSONByteString -> Bool
$c<= :: HexJSONByteString -> HexJSONByteString -> Bool
< :: HexJSONByteString -> HexJSONByteString -> Bool
$c< :: HexJSONByteString -> HexJSONByteString -> Bool
compare :: HexJSONByteString -> HexJSONByteString -> Ordering
$ccompare :: HexJSONByteString -> HexJSONByteString -> Ordering
$cp1Ord :: Eq HexJSONByteString
Ord, Int -> HexJSONByteString -> ShowS
[HexJSONByteString] -> ShowS
HexJSONByteString -> String
(Int -> HexJSONByteString -> ShowS)
-> (HexJSONByteString -> String)
-> ([HexJSONByteString] -> ShowS)
-> Show HexJSONByteString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HexJSONByteString] -> ShowS
$cshowList :: [HexJSONByteString] -> ShowS
show :: HexJSONByteString -> String
$cshow :: HexJSONByteString -> String
showsPrec :: Int -> HexJSONByteString -> ShowS
$cshowsPrec :: Int -> HexJSONByteString -> ShowS
Show, (forall x. HexJSONByteString -> Rep HexJSONByteString x)
-> (forall x. Rep HexJSONByteString x -> HexJSONByteString)
-> Generic HexJSONByteString
forall x. Rep HexJSONByteString x -> HexJSONByteString
forall x. HexJSONByteString -> Rep HexJSONByteString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HexJSONByteString x -> HexJSONByteString
$cfrom :: forall x. HexJSONByteString -> Rep HexJSONByteString x
Generic)
  deriving newtype (HexJSONByteString -> ()
(HexJSONByteString -> ()) -> NFData HexJSONByteString
forall a. (a -> ()) -> NFData a
rnf :: HexJSONByteString -> ()
$crnf :: HexJSONByteString -> ()
NFData, Int -> HexJSONByteString -> Int
HexJSONByteString -> Int
(Int -> HexJSONByteString -> Int)
-> (HexJSONByteString -> Int) -> Hashable HexJSONByteString
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: HexJSONByteString -> Int
$chash :: HexJSONByteString -> Int
hashWithSalt :: Int -> HexJSONByteString -> Int
$chashWithSalt :: Int -> HexJSONByteString -> Int
Hashable)
instance ToJSON HexJSONByteString where
  toJSON :: HexJSONByteString -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (HexJSONByteString -> Text) -> HexJSONByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
encodeHex (ByteString -> Text)
-> (HexJSONByteString -> ByteString) -> HexJSONByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HexJSONByteString -> ByteString
unHexJSONByteString
instance FromJSON HexJSONByteString where
  parseJSON :: Value -> Parser HexJSONByteString
parseJSON =
    String
-> (Text -> Parser HexJSONByteString)
-> Value
-> Parser HexJSONByteString
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText "Hex-encoded bytestring" ((Text -> Parser HexJSONByteString)
 -> Value -> Parser HexJSONByteString)
-> (Text -> Parser HexJSONByteString)
-> Value
-> Parser HexJSONByteString
forall a b. (a -> b) -> a -> b
$ \t :: Text
t ->
      case Text -> Maybe ByteString
decodeHex Text
t of
        Nothing -> String -> Parser HexJSONByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail "Invalid hex encoding"
        Just res :: ByteString
res -> HexJSONByteString -> Parser HexJSONByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> HexJSONByteString
HexJSONByteString ByteString
res)