summaryrefslogtreecommitdiff
path: root/src/Text/XXD.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/XXD.hs')
-rw-r--r--src/Text/XXD.hs48
1 files changed, 48 insertions, 0 deletions
diff --git a/src/Text/XXD.hs b/src/Text/XXD.hs
new file mode 100644
index 0000000..77606bf
--- /dev/null
+++ b/src/Text/XXD.hs
@@ -0,0 +1,48 @@
1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE ScopedTypeVariables #-}
3module Text.XXD (xxd, xxd2) where
4
5import Data.ByteArray (ByteArrayAccess)
6import qualified Data.ByteArray as BA
7import Data.Word
8import Data.Bits
9import Data.Char
10import Text.Printf
11
12nibble :: Word8 -> Char
13nibble b = intToDigit (fromIntegral (b .&. 0x0F))
14
15nibbles :: ByteArrayAccess ba => ba -> String
16nibbles xs = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte])
17 $ BA.unpack xs
18
19xxd0 :: (ByteArrayAccess ba) => (forall b. ByteArrayAccess b => b -> String) -> Int -> ba -> [String]
20xxd0 tr offset bs | BA.null bs = []
21xxd0 tr offset bs = printf "%03x: %s%s" offset (nibbles xs) (tr xs)
22 : xxd0 tr (offset + BA.length xs) bs'
23 where
24 (xs,bs') = splitAtView 16 bs
25
26splitAtView :: (ByteArrayAccess ba) => Int -> ba -> (BA.View ba, BA.View ba)
27splitAtView n bs = (BA.takeView bs n, BA.dropView bs n)
28
29xxd :: ByteArrayAccess a => Int -> a -> [String]
30xxd = xxd0 (const "")
31
32-- | like xxd, but also shows ascii
33xxd2 :: ByteArrayAccess a => Int -> a -> [String]
34xxd2 = xxd0 withAscii
35
36withAscii :: ByteArrayAccess a => a -> [Char]
37withAscii row = replicate (50 - 3 * BA.length row) ' ' ++ myunpack row
38 where
39 myunpack s = map word8tochar (BA.unpack s)
40 where word8tochar w | (w .&. 0x80 /= 0) = '.'
41 word8tochar w = let c = chr (fromIntegral w)
42 in if isPrint c then c else '.'
43
44{-
45main = do
46 bs <- B.getContents
47 mapM_ putStrLn $ xxd2 0 bs
48 -}