-- This file is part of htalkat -- Copyright (C) 2021 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module HexString where import Data.ByteString (ByteString, pack, unpack) parseHexString :: String -> Maybe ByteString parseHexString s = pack <$> parseHexString' s where parseHexString' (a:b:c) = do ha <- fromHex a hb <- fromHex b (16 * ha + hb :) <$> parseHexString' c where fromHex '0' = Just 0 fromHex '1' = Just 1 fromHex '2' = Just 2 fromHex '3' = Just 3 fromHex '4' = Just 4 fromHex '5' = Just 5 fromHex '6' = Just 6 fromHex '7' = Just 7 fromHex '8' = Just 8 fromHex '9' = Just 9 fromHex 'a' = Just 10 fromHex 'b' = Just 11 fromHex 'c' = Just 12 fromHex 'd' = Just 13 fromHex 'e' = Just 14 fromHex 'f' = Just 15 fromHex 'A' = Just 10 fromHex 'B' = Just 11 fromHex 'C' = Just 12 fromHex 'D' = Just 13 fromHex 'E' = Just 14 fromHex 'F' = Just 15 fromHex _ = Nothing parseHexString' [] = Just [] parseHexString' _ = Nothing showHexString :: ByteString -> String showHexString = concat . (showHexWord8 <$>) . unpack where showHexWord8 w = let (a,b) = quotRem w 16 hex = ("0123456789abcdef" !!) . fromIntegral in hex a : hex b : ""