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