-- This Source Code Form is subject to the terms of the Mozilla Public -- License, v. 2.0. If a copy of the MPL was not distributed with this -- file, You can obtain one at http://mozilla.org/MPL/2.0/. {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} module Data.ByteString.From.Hex where import Control.Applicative import Data.Attoparsec.ByteString import Data.Attoparsec.ByteString.Char8 (signed, hexadecimal) import Data.ByteString.From import Data.Bits (Bits) import Data.ByteString (elem) import Prelude hiding (elem) import Text.Printf (PrintfArg) -- | Newtype wrapper to parse integral numbers in hexadecimal -- format, optionally with a @0x@ or @0X@ prefix. newtype Hex a = Hex { fromHex :: a } deriving ( Eq , Ord , Num , Read , Show , Bounded , Integral , Bits , PrintfArg , Enum , Real ) instance (Integral a, Bits a) => FromByteString (Hex a) where parser = Hex <$> signed (optional prefix *> hexadecimal) where prefix = word8 0x30 *> satisfy (`elem` "xX")