Don't expose the ByteString encode/decode anymore

By exposing a ByteString functions we actually make this library more
confusing; we will now only represent the hex string representation as
either Text or String, and any ByteString that goes in or out is always
the binary representation.
This commit is contained in:
Leon Mergen 2015-04-20 13:30:58 +07:00
parent 5acf1b0193
commit 6eea89845d
2 changed files with 20 additions and 18 deletions

View file

@ -1,4 +1,8 @@
module Data.HexString where
module Data.HexString ( HexString (..)
, decodeText
, decodeString
, encodeText
, encodeString ) where
import Control.Applicative ((<$>))
@ -26,10 +30,6 @@ instance B.Binary HexString where
get = HexString <$> B.getRemainingLazyByteString
put (HexString bs) = B.putLazyByteString bs
-- | Converts `BSL.ByteString` to a `HexString`
decodeByteString :: BSL.ByteString -> HexString
decodeByteString = B.decode . fst . BS16L.decode
-- | Converts a `T.Text` representation to a `HexString`
decodeText :: T.Text -> HexString
decodeText = decodeByteString . BSL.fromStrict . TE.encodeUtf8
@ -38,10 +38,6 @@ decodeText = decodeByteString . BSL.fromStrict . TE.encodeUtf8
decodeString :: String -> HexString
decodeString = decodeByteString . BSL8.pack
-- | Converts a `HexString` to a `BSL.ByteString`
encodeByteString :: HexString -> BSL.ByteString
encodeByteString = BS16L.encode . B.encode
-- | Converts a `HexString` to a `T.Text` representation
encodeText :: HexString -> T.Text
encodeText = TE.decodeUtf8 . BSL.toStrict . encodeByteString
@ -49,3 +45,13 @@ encodeText = TE.decodeUtf8 . BSL.toStrict . encodeByteString
-- | Converts a `HexString` to a `String` representation
encodeString :: HexString -> String
encodeString = BSL8.unpack . encodeByteString
-- | 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

@ -13,13 +13,9 @@ spec :: Spec
spec = do
describe "when decoding hex data" $ do
it "should be able to parse basic hex data" $ do
(B.encode . decodeByteString) (BSL8.pack "ffff") `shouldBe` BSL8.pack "\255\255"
(B.encode . decodeString) "ffff" `shouldBe` BSL8.pack "\255\255"
(B.encode . decodeText) (T.pack "ffff") `shouldBe` BSL8.pack "\255\255"
it "should be able to recode basic hex data to different formats" $
let hex = BSL8.pack "ffff"
in do
(encodeText . decodeByteString) hex `shouldBe` T.pack "ffff"
(encodeString . decodeByteString) hex `shouldBe` "ffff"
(encodeByteString . decodeByteString) hex `shouldBe` BSL8.pack "ffff"
it "should be able to recode basic hex data to different formats" $ do
(encodeText . decodeString) "ffff" `shouldBe` T.pack "ffff"
(encodeString . decodeString) "ffff" `shouldBe` "ffff"