binrep-0.3.1: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Extra.HexByteString

Description

Pretty bytestrings via printing each byte as two hex digits.

This is primarily for aeson and when we want better showing 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...

Synopsis

Documentation

newtype Hex a Source #

Constructors

Hex 

Fields

Instances

Instances details
FromJSON (Hex ByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

FromJSON (Hex ShortByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

ToJSON (Hex ByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

ToJSON (Hex ShortByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Data a => Data (Hex a) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Hex a -> c (Hex a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Hex a) #

toConstr :: Hex a -> Constr #

dataTypeOf :: Hex a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Hex a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Hex a)) #

gmapT :: (forall b. Data b => b -> b) -> Hex a -> Hex a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hex a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Hex a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Hex a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Hex a -> m (Hex a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Hex a -> m (Hex a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Hex a -> m (Hex a) #

Generic (Hex a) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Associated Types

type Rep (Hex a) :: Type -> Type #

Methods

from :: Hex a -> Rep (Hex a) x #

to :: Rep (Hex a) x -> Hex a #

Show (Hex ByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Show (Hex ShortByteString) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Eq a => Eq (Hex a) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

Methods

(==) :: Hex a -> Hex a -> Bool #

(/=) :: Hex a -> Hex a -> Bool #

type Rep (Hex a) Source # 
Instance details

Defined in Binrep.Extra.HexByteString

type Rep (Hex a) = D1 ('MetaData "Hex" "Binrep.Extra.HexByteString" "binrep-0.3.1-inplace" 'True) (C1 ('MetaCons "Hex" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

parseHexByteString :: (MonadParsec e s m, Token s ~ Char) => ([Word8] -> a) -> m a Source #

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.

parseHexByte :: (MonadParsec e s m, Token s ~ Char, Num a) => m a Source #

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.

prettyHexByteString :: (a -> [Word8]) -> a -> Text Source #

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).

prettyHexByteStringCompact :: (a -> [Word8]) -> a -> Text Source #

Pretty print to "compact" format 0012abff (often output by hashers).