Now making use of Binary instead of manual convert
This commit is contained in:
parent
76de2b04ce
commit
5acf1b0193
3 changed files with 40 additions and 29 deletions
|
@ -28,6 +28,7 @@ library
|
||||||
exposed-modules: Data.HexString
|
exposed-modules: Data.HexString
|
||||||
|
|
||||||
build-depends: base >= 4.3 && < 5
|
build-depends: base >= 4.3 && < 5
|
||||||
|
, binary
|
||||||
, text
|
, text
|
||||||
, bytestring
|
, bytestring
|
||||||
, base16-bytestring
|
, base16-bytestring
|
||||||
|
@ -48,6 +49,8 @@ test-suite test-suite
|
||||||
, text
|
, text
|
||||||
|
|
||||||
, bytestring
|
, bytestring
|
||||||
|
, binary
|
||||||
|
|
||||||
, hexstring
|
, hexstring
|
||||||
|
|
||||||
source-repository head
|
source-repository head
|
||||||
|
|
|
@ -1,45 +1,51 @@
|
||||||
module Data.HexString where
|
module Data.HexString where
|
||||||
|
|
||||||
import qualified Data.ByteString as BS
|
import Control.Applicative ((<$>))
|
||||||
import qualified Data.ByteString.Char8 as BS8
|
|
||||||
import qualified Data.ByteString.Base16 as BS16
|
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.ByteString.Base16.Lazy as BS16L (decode, encode)
|
||||||
import qualified Data.Text.Encoding as TE
|
import qualified Data.ByteString.Lazy.Char8 as BSL8
|
||||||
|
import qualified Data.ByteString.Lazy as BSL
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import qualified Data.Text.Encoding as TE
|
||||||
|
|
||||||
|
import qualified Data.Binary as B (Binary, decode, encode, get,
|
||||||
|
put)
|
||||||
|
import qualified Data.Binary.Get as B (getRemainingLazyByteString)
|
||||||
|
import qualified Data.Binary.Put as B (putLazyByteString)
|
||||||
|
|
||||||
-- | Data type representing a HexString.
|
-- | Data type representing a HexString.
|
||||||
data HexString
|
data HexString
|
||||||
= HexString !BS.ByteString
|
= HexString BSL.ByteString
|
||||||
deriving ( Show, Eq, Ord )
|
deriving ( Show, Eq, Ord )
|
||||||
|
|
||||||
-- | Access to the raw binary data this HexString represents
|
-- | Allows us to convert to and from a `B.Binary` representation. Always
|
||||||
getBinary :: HexString -> BS.ByteString
|
-- assumes that the entire binary string that is fed to `Binary.decode`
|
||||||
getBinary (HexString bs) = bs
|
-- represents the hex string.
|
||||||
|
instance B.Binary HexString where
|
||||||
|
get = HexString <$> B.getRemainingLazyByteString
|
||||||
|
put (HexString bs) = B.putLazyByteString bs
|
||||||
|
|
||||||
-- | Create new HexString based on raw binary data
|
-- | Converts `BSL.ByteString` to a `HexString`
|
||||||
setBinary :: BS.ByteString -> HexString
|
decodeByteString :: BSL.ByteString -> HexString
|
||||||
setBinary = HexString
|
decodeByteString = B.decode . fst . BS16L.decode
|
||||||
|
|
||||||
-- | Converts `BS.ByteString` to a `HexString`
|
|
||||||
decodeByteString :: BS.ByteString -> HexString
|
|
||||||
decodeByteString = HexString . fst . BS16.decode
|
|
||||||
|
|
||||||
-- | Converts a `T.Text` representation to a `HexString`
|
-- | Converts a `T.Text` representation to a `HexString`
|
||||||
decodeText :: T.Text -> HexString
|
decodeText :: T.Text -> HexString
|
||||||
decodeText = decodeByteString . TE.encodeUtf8
|
decodeText = decodeByteString . BSL.fromStrict . TE.encodeUtf8
|
||||||
|
|
||||||
-- | Converts a `String` representation to a `HexString`
|
-- | Converts a `String` representation to a `HexString`
|
||||||
decodeString :: String -> HexString
|
decodeString :: String -> HexString
|
||||||
decodeString = decodeByteString . BS8.pack
|
decodeString = decodeByteString . BSL8.pack
|
||||||
|
|
||||||
-- | Converts a `HexString` to a `BS.ByteString`
|
-- | Converts a `HexString` to a `BSL.ByteString`
|
||||||
encodeByteString :: HexString -> BS.ByteString
|
encodeByteString :: HexString -> BSL.ByteString
|
||||||
encodeByteString = BS16.encode . getBinary
|
encodeByteString = BS16L.encode . B.encode
|
||||||
|
|
||||||
-- | Converts a `HexString` to a `T.Text` representation
|
-- | Converts a `HexString` to a `T.Text` representation
|
||||||
encodeText :: HexString -> T.Text
|
encodeText :: HexString -> T.Text
|
||||||
encodeText = TE.decodeUtf8 . encodeByteString
|
encodeText = TE.decodeUtf8 . BSL.toStrict . encodeByteString
|
||||||
|
|
||||||
-- | Converts a `HexString` to a `String` representation
|
-- | Converts a `HexString` to a `String` representation
|
||||||
encodeString :: HexString -> String
|
encodeString :: HexString -> String
|
||||||
encodeString = BS8.unpack . encodeByteString
|
encodeString = BSL8.unpack . encodeByteString
|
||||||
|
|
|
@ -2,22 +2,24 @@ module Data.HexStringSpec where
|
||||||
|
|
||||||
import Data.HexString
|
import Data.HexString
|
||||||
|
|
||||||
import qualified Data.ByteString.Char8 as BS8
|
import qualified Data.ByteString.Lazy.Char8 as BSL8
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
import qualified Data.Binary as B ( encode )
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
describe "when decoding hex data" $ do
|
describe "when decoding hex data" $ do
|
||||||
it "should be able to parse basic hex data" $ do
|
it "should be able to parse basic hex data" $ do
|
||||||
(getBinary . decodeByteString) (BS8.pack "ffff") `shouldBe` BS8.pack "\255\255"
|
(B.encode . decodeByteString) (BSL8.pack "ffff") `shouldBe` BSL8.pack "\255\255"
|
||||||
(getBinary . decodeString) "ffff" `shouldBe` BS8.pack "\255\255"
|
(B.encode . decodeString) "ffff" `shouldBe` BSL8.pack "\255\255"
|
||||||
(getBinary . decodeText) (T.pack "ffff") `shouldBe` BS8.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" $
|
it "should be able to recode basic hex data to different formats" $
|
||||||
let hex = BS8.pack "ffff"
|
let hex = BSL8.pack "ffff"
|
||||||
in do
|
in do
|
||||||
(encodeText . decodeByteString) hex `shouldBe` T.pack "ffff"
|
(encodeText . decodeByteString) hex `shouldBe` T.pack "ffff"
|
||||||
(encodeString . decodeByteString) hex `shouldBe` "ffff"
|
(encodeString . decodeByteString) hex `shouldBe` "ffff"
|
||||||
(encodeByteString . decodeByteString) hex `shouldBe` BS8.pack "ffff"
|
(encodeByteString . decodeByteString) hex `shouldBe` BSL8.pack "ffff"
|
||||||
|
|
Loading…
Reference in a new issue