Updates interface to make a lot more generic

We now make use of the Binary interface, instead of relying on the
caller to provide ByteString objects himself.
This commit is contained in:
Leon Mergen 2015-04-20 16:26:56 +07:00
parent 6eea89845d
commit ff3cab38d9
2 changed files with 51 additions and 55 deletions

View file

@ -1,57 +1,48 @@
module Data.HexString ( HexString (..) module Data.HexString ( HexString
, decodeText , hexString
, decodeString , toHex
, encodeText , fromHex
, encodeString ) where , asText ) where
import Control.Applicative ((<$>)) import Data.Word (Word8)
import qualified Data.ByteString.Base16.Lazy as BS16L (decode, encode) import qualified Data.ByteString.Base16 as BS16 (decode, encode)
import qualified Data.ByteString.Lazy.Char8 as BSL8 import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as TE import qualified Data.Text.Encoding as TE
import qualified Data.Binary as B (Binary, decode, encode, get, import qualified Data.Binary as B (Binary, decode, encode)
put)
import qualified Data.Binary.Get as B (getRemainingLazyByteString)
import qualified Data.Binary.Put as B (putLazyByteString)
-- | Data type representing a HexString. -- | Represents a Hex string. Guarantees that all characters it contains
data HexString -- are valid hex characters.
= HexString BSL.ByteString data HexString =
HexString BS.ByteString
deriving ( Show, Eq, Ord ) deriving ( Show, Eq, Ord )
-- | Allows us to convert to and from a `B.Binary` representation. Always -- | Smart constructor which validates that all the text are actually
-- assumes that the entire binary string that is fed to `Binary.decode` -- hexadecimal characters.
-- represents the hex string. hexString :: BS.ByteString -> HexString
instance B.Binary HexString where hexString bs =
get = HexString <$> B.getRemainingLazyByteString let isValidHex :: Word8 -> Bool
put (HexString bs) = B.putLazyByteString bs isValidHex c
| (48 <= c) && (c < 58) = True
| (97 <= c) && (c < 103) = True
| otherwise = False
-- | Converts a `T.Text` representation to a `HexString` in if BS.all isValidHex bs
decodeText :: T.Text -> HexString then (HexString bs)
decodeText = decodeByteString . BSL.fromStrict . TE.encodeUtf8 else error ("Not a valid hex string: " ++ show bs)
-- | Converts a `String` representation to a `HexString` -- | Converts a 'B.Binary' to a 'HexString' value
decodeString :: String -> HexString toHex :: B.Binary a => a -> HexString
decodeString = decodeByteString . BSL8.pack toHex = hexString . BS16.encode . BSL.toStrict . B.encode
-- | Converts a `HexString` to a `T.Text` representation -- | Converts a 'HexString' to a 'B.Binary' value
encodeText :: HexString -> T.Text fromHex :: B.Binary a => HexString -> a
encodeText = TE.decodeUtf8 . BSL.toStrict . encodeByteString fromHex (HexString bs) = B.decode . BSL.fromStrict . fst . BS16.decode $ bs
-- | Converts a `HexString` to a `String` representation -- | Access to a 'T.Text' representation of the 'HexString'
encodeString :: HexString -> String asText :: HexString -> T.Text
encodeString = BSL8.unpack . encodeByteString asText (HexString bs) = TE.decodeUtf8 bs
-- | Internal function that converts a `HexString` to a `BSL.ByteString`
encodeByteString :: HexString -> BSL.ByteString
encodeByteString = BS16L.encode . B.encode
-- | Internal funcion that converts `BSL.ByteString` to a `HexString`
decodeByteString :: BSL.ByteString -> HexString
decodeByteString = B.decode . fst . BS16L.decode

View file

@ -1,8 +1,12 @@
module Data.HexStringSpec where module Data.HexStringSpec where
import Data.HexString import Data.HexString ( hexString
, toHex
, fromHex
, asText )
import qualified Data.ByteString.Lazy.Char8 as BSL8 import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Binary as B ( encode ) import qualified Data.Binary as B ( encode )
@ -11,11 +15,12 @@ import Test.Hspec
spec :: Spec spec :: Spec
spec = do spec = do
describe "when decoding hex data" $ do describe "when constructing a hex string" $ do
it "should be able to parse basic hex data" $ do it "should accept strings that fall within a valid range" $
(B.encode . decodeString) "ffff" `shouldBe` BSL8.pack "\255\255" hexString (BS8.pack "0123456789abcdef") `shouldBe` hexString (BS8.pack "0123456789abcdef")
(B.encode . decodeText) (T.pack "ffff") `shouldBe` BSL8.pack "\255\255"
it "should be able to recode basic hex data to different formats" $ do it "should reject strings outside the range" $ do
(encodeText . decodeString) "ffff" `shouldBe` T.pack "ffff" putStrLn (show (hexString (BS8.pack "/"))) `shouldThrow` anyErrorCall
(encodeString . decodeString) "ffff" `shouldBe` "ffff" putStrLn (show (hexString (BS8.pack ":"))) `shouldThrow` anyErrorCall
putStrLn (show (hexString (BS8.pack "`"))) `shouldThrow` anyErrorCall
putStrLn (show (hexString (BS8.pack "g"))) `shouldThrow` anyErrorCall