{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.ByteArray.HexString where
import Data.Aeson (FromJSON (..), ToJSON (..),
Value (String), withText)
import Data.ByteArray (ByteArray, ByteArrayAccess, convert)
import qualified Data.ByteArray as BA (drop, take)
import Data.ByteArray.Encoding (Base (Base16), convertFromBase,
convertToBase)
import Data.ByteString (ByteString)
import Data.Monoid (Monoid, (<>))
import Data.Semigroup (Semigroup)
import Data.String (IsString (..))
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
newtype HexString = HexString { unHexString :: ByteString }
deriving (Eq, Ord, Semigroup, Monoid, ByteArrayAccess, ByteArray)
instance Show HexString where
show = ("HexString " ++) . show . toText
instance IsString HexString where
fromString = hexString' . fromString
where
hexString' :: ByteString -> HexString
hexString' = either error id . hexString
instance FromJSON HexString where
parseJSON = withText "HexString" $ either fail pure . hexString . encodeUtf8
instance ToJSON HexString where
toJSON = String . toText
hexString :: ByteArray ba => ba -> Either String HexString
hexString bs = HexString <$> convertFromBase Base16 bs'
where
hexStart = convert ("0x" :: ByteString)
bs' | BA.take 2 bs == hexStart = BA.drop 2 bs
| otherwise = bs
fromBytes :: ByteArrayAccess ba => ba -> HexString
fromBytes = HexString . convert
toBytes :: ByteArray ba => HexString -> ba
toBytes = convert . unHexString
toText :: HexString -> Text
toText = ("0x" <>) . decodeUtf8 . convertToBase Base16 . unHexString