diff options
author | joe <joe@jerkface.net> | 2017-11-19 13:19:13 -0500 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-11-19 13:19:13 -0500 |
commit | fc9ed0a8f3d71b529fb4277ce55c761f1df737ee (patch) | |
tree | 5343b9ae82aecaf7c8b55ed98d6402767c2a99ad | |
parent | 9fefcd6aaa2093e52b344af7d24106bb159fe206 (diff) |
Simplified xxd hex-dump code.
-rw-r--r-- | src/Text/XXD.hs | 49 |
1 files changed, 21 insertions, 28 deletions
diff --git a/src/Text/XXD.hs b/src/Text/XXD.hs index 04c458a7..b73a1ea2 100644 --- a/src/Text/XXD.hs +++ b/src/Text/XXD.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | {-# LANGUAGE RankNTypes #-} | ||
1 | {-# LANGUAGE ScopedTypeVariables #-} | 2 | {-# LANGUAGE ScopedTypeVariables #-} |
2 | module Text.XXD where | 3 | module Text.XXD (xxd, xxd2) where |
3 | 4 | ||
4 | import qualified Data.ByteString.Base16 as Base16 | 5 | import qualified Data.ByteString.Base16 as Base16 |
5 | import Data.ByteString (ByteString) | 6 | import Data.ByteString (ByteString) |
@@ -15,45 +16,37 @@ import Text.Printf | |||
15 | nibble :: Word8 -> Char | 16 | nibble :: Word8 -> Char |
16 | nibble b = intToDigit (fromIntegral (b .&. 0x0F)) | 17 | nibble b = intToDigit (fromIntegral (b .&. 0x0F)) |
17 | 18 | ||
18 | xxd :: (ByteArrayAccess ba) => Int -> ba -> [String] | 19 | nibbles :: ByteArrayAccess ba => ba -> String |
19 | xxd offset bs | BA.null bs = [] | 20 | nibbles xs = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte]) |
20 | xxd offset bs = printf "%03x: %s" offset ds : xxd (offset + BA.length xs) bs' | 21 | $ BA.unpack xs |
22 | |||
23 | xxd0 :: (ByteArrayAccess ba) => (forall b. ByteArrayAccess b => b -> String) -> Int -> ba -> [String] | ||
24 | xxd0 tr offset bs | BA.null bs = [] | ||
25 | xxd0 tr offset bs = printf "%03x: %s%s" offset (nibbles xs) (tr xs) | ||
26 | : xxd0 tr (offset + BA.length xs) bs' | ||
21 | where | 27 | where |
22 | ds = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte]) | ||
23 | $ BA.unpack xs | ||
24 | (xs,bs') = splitAtView 16 bs | 28 | (xs,bs') = splitAtView 16 bs |
25 | 29 | ||
26 | splitAtView :: (ByteArrayAccess ba) => Int -> ba -> (BA.View ba, BA.View ba) | 30 | splitAtView :: (ByteArrayAccess ba) => Int -> ba -> (BA.View ba, BA.View ba) |
27 | splitAtView n bs = (BA.takeView bs n, BA.dropView bs n) | 31 | splitAtView n bs = (BA.takeView bs n, BA.dropView bs n) |
28 | 32 | ||
33 | xxd :: ByteArrayAccess a => Int -> a -> [String] | ||
34 | xxd = xxd0 (const "") | ||
35 | |||
29 | -- | like xxd, but also shows ascii | 36 | -- | like xxd, but also shows ascii |
30 | xxd2 :: forall a. ByteArrayAccess a => Int -> a -> String | 37 | xxd2 :: ByteArrayAccess a => Int -> a -> [String] |
31 | xxd2 offset bs | BA.null bs = [] | 38 | xxd2 = xxd0 withAscii |
32 | xxd2 offset bs | 39 | |
33 | = let xs = xxd offset bs | 40 | withAscii :: ByteArrayAccess a => a -> [Char] |
34 | as = map myunpack $ every16Bytes bs -- (BA.view bs 0 (BA.length bs)) | 41 | withAscii row = replicate (50 - 3 * BA.length row) ' ' ++ myunpack row |
35 | cs = zipWith (\x y -> [x,y]) xs as | ||
36 | in showColumns cs | ||
37 | where | 42 | where |
38 | myunpack s = map word8tochar (BA.unpack s) | 43 | myunpack s = map word8tochar (BA.unpack s) |
39 | where word8tochar w = let c = chr (fromIntegral w) | 44 | where word8tochar w | (w .&. 0x80 /= 0) = '.' |
45 | word8tochar w = let c = chr (fromIntegral w) | ||
40 | in if isPrint c then c else '.' | 46 | in if isPrint c then c else '.' |
41 | every16Bytes :: a -> [BA.View a] | ||
42 | every16Bytes bs = let l = BA.length bs | ||
43 | (ld,lm) = l `divMod` 16 | ||
44 | offsets = [0 .. ld ] | ||
45 | lens = replicate (ld ) 16 ++ [lm] | ||
46 | in zipWith (\o l -> BA.view bs (o*16) l) offsets lens | ||
47 | showColumns :: [[String]] -> String | ||
48 | showColumns rows = do | ||
49 | let cols = transpose rows | ||
50 | ws = map (maximum . map (succ . length)) cols | ||
51 | fs <- rows | ||
52 | _ <- take 1 fs -- Guard against empty rows so that 'last' is safe. | ||
53 | " " ++ concat (zipWith (printf "%-*s") (init ws) (init fs)) ++ last fs ++ "\n" | ||
54 | 47 | ||
55 | {- | 48 | {- |
56 | main = do | 49 | main = do |
57 | bs <- B.getContents | 50 | bs <- B.getContents |
58 | mapM_ putStrLn $ xxd 0 bs | 51 | mapM_ putStrLn $ xxd2 0 bs |
59 | -} | 52 | -} |