From d14b1a34e1c9cee50a7e15eda917e414e62e6ed3 Mon Sep 17 00:00:00 2001 From: joe Date: Sun, 19 Nov 2017 13:19:13 -0500 Subject: Updated xxd hex-dump code. --- src/Text/XXD.hs | 42 ++++++++++++++++++++++++++++++++++-------- 1 file changed, 34 insertions(+), 8 deletions(-) (limited to 'src') diff --git a/src/Text/XXD.hs b/src/Text/XXD.hs index d835b238..b73a1ea2 100644 --- a/src/Text/XXD.hs +++ b/src/Text/XXD.hs @@ -1,26 +1,52 @@ -module Text.XXD where +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +module Text.XXD (xxd, xxd2) where import qualified Data.ByteString.Base16 as Base16 import Data.ByteString (ByteString) import qualified Data.ByteString as B +import Data.ByteArray (ByteArrayAccess,ByteArray) +import qualified Data.ByteArray as BA import Data.Word import Data.Bits import Data.Char +import Data.List import Text.Printf nibble :: Word8 -> Char nibble b = intToDigit (fromIntegral (b .&. 0x0F)) -xxd :: Int -> ByteString -> [String] -xxd offset bs | B.null bs = [] -xxd offset bs = printf "%03x: %s" offset ds : xxd (offset + B.length xs) bs' +nibbles :: ByteArrayAccess ba => ba -> String +nibbles xs = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte]) + $ BA.unpack xs + +xxd0 :: (ByteArrayAccess ba) => (forall b. ByteArrayAccess b => b -> String) -> Int -> ba -> [String] +xxd0 tr offset bs | BA.null bs = [] +xxd0 tr offset bs = printf "%03x: %s%s" offset (nibbles xs) (tr xs) + : xxd0 tr (offset + BA.length xs) bs' where - ds = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte]) - $ B.unpack xs - (xs,bs') = B.splitAt 16 bs + (xs,bs') = splitAtView 16 bs + +splitAtView :: (ByteArrayAccess ba) => Int -> ba -> (BA.View ba, BA.View ba) +splitAtView n bs = (BA.takeView bs n, BA.dropView bs n) + +xxd :: ByteArrayAccess a => Int -> a -> [String] +xxd = xxd0 (const "") + +-- | like xxd, but also shows ascii +xxd2 :: ByteArrayAccess a => Int -> a -> [String] +xxd2 = xxd0 withAscii + +withAscii :: ByteArrayAccess a => a -> [Char] +withAscii row = replicate (50 - 3 * BA.length row) ' ' ++ myunpack row + where + myunpack s = map word8tochar (BA.unpack s) + where word8tochar w | (w .&. 0x80 /= 0) = '.' + word8tochar w = let c = chr (fromIntegral w) + in if isPrint c then c else '.' {- main = do bs <- B.getContents - mapM_ putStrLn $ xxd 0 bs + mapM_ putStrLn $ xxd2 0 bs -} -- cgit v1.2.3