Haskell 언어 소스:

{-
    Filename: testHexView_02.hs

      Purpose: Show hexadecimal values of the given file.
 
    Compile: ghc testHexView_02.hs
    Execute: testHexView_02 [filename]
 
    Date: 2013. 8. 20.
-}

module Main where

import System.Directory
import System.Exit
import System.IO
import System.Environment
import Text.Printf
import Data.Bits
import Data.Char (ord)
import Data.Char (chr)
import Data.Array
import Data.List


printUsage :: IO()
printUsage = putStrLn "Usage: testHexView_02 [filename]"


strDupLoop :: String -> Integer -> String -> String
strDupLoop s n t = case n == 0 of
        True -> t
        _ -> strDupLoop s (n - 1) (t ++ s)

strDup :: String -> Integer -> String
strDup s n = strDupLoop s n ""

getHexStr :: String -> Integer -> Integer -> Integer -> String -> String
getHexStr s offset k cnt t = case k == cnt of
        True -> t
        _ -> getHexStr s offset (k + 1) cnt (t ++ c0 ++ (printf "%s" (toHex (ord (s !! (fromInteger (offset + k)))))))
                       where c0 = if k == 8 then "-" else " "

getDumStr :: String -> Integer -> Integer -> Integer -> String -> String
getDumStr s offset k cnt t = case k == cnt of
        True -> t
        _ -> getDumStr s offset (k + 1) cnt (t ++ (printf "%c" a))
                 where x = (s !! (fromInteger (offset + k)))
                       a = if (ord x) < (ord ' ') || (ord x) > 0x7F
                              then '.'
                              else x

printHexTable :: String -> Integer -> Integer -> IO()
printHexTable s offset size = case offset + 16 <= size of
    True -> do putStr $ printf "%s: " (toHex8 $ fromInteger offset)
               putStr (getHexStr s offset 0 16 "")
               putStrLn $ "  |" ++ (getDumStr s offset 0 16 "") ++ "|"
               printHexTable s (offset + 16) size
    _    -> do putStr $ printf "%s: " (toHex8 $ fromInteger offset)
               putStr (getHexStr s offset 0 (size - offset) "")
               putStr (strDup "   " (16 - size + offset))
               putStr $ "  |" ++ (getDumStr s offset 0 (size - offset) "")
               putStrLn $ (strDup " " (16 - size + offset)) ++ "|"
   

toHex :: Int -> [Char]
toHex n = printf "%c%c" sx1 sx2
          where x1 = shiftR (n .&. 0xF0) 4
                x2 = n .&. 0xF
                -- sx1 = show ((ord '0') + x1)
                -- sx2 = show ((ord 'A') + x2)
                sx1  = if x1 > 9
                       then
                            ((ord 'A') + (x1 - 10))
                       else
                            ((ord '0') + x1)
                sx2 = if x2 > 9
                      then
                            ((ord 'A') + (x2 - 10))
                      else
                            ((ord '0') + x2)


toHex8 :: Int -> [Char]
toHex8 n = printf "%c%c%c%c %c%c%c%c" sx1 sx2 sx3 sx4 sx5 sx6 sx7 sx8
          where x1 = shiftR (n .&. 0xF0000000) 28
                x2 = shiftR (n .&. 0xF000000) 24
                x3 = shiftR (n .&. 0xF00000) 20
                x4 = shiftR (n .&. 0xF0000) 16
                x5 = shiftR (n .&. 0xF000) 12
                x6 = shiftR (n .&. 0xF00) 8
                x7 = shiftR (n .&. 0xF0) 4
                x8 = n .&. 0xF
                sx1  = if x1 > 9
                       then
                            ((ord 'A') + (x1 - 10))
                       else
                            ((ord '0') + x1)
                sx2 = if x2 > 9
                      then
                            ((ord 'A') + (x2 - 10))
                      else
                            ((ord '0') + x2)
                sx3 = if x3 > 9
                      then
                            ((ord 'A') + (x3 - 10))
                      else
                            ((ord '0') + x3)
                sx4 = if x4 > 9
                      then
                            ((ord 'A') + (x4 - 10))
                      else
                            ((ord '0') + x4)
                sx5 = if x5 > 9
                      then
                            ((ord 'A') + (x5 - 10))
                      else
                            ((ord '0') + x5)
                sx6 = if x6 > 9
                      then
                            ((ord 'A') + (x6 - 10))
                      else
                            ((ord '0') + x6)
                sx7 = if x7 > 9
                      then
                            ((ord 'A') + (x7 - 10))
                      else
                            ((ord '0') + x7)
                sx8 = if x8 > 9
                      then
                            ((ord 'A') + (x8 - 10))
                      else
                            ((ord '0') + x8)


       
main :: IO ()
main = do
    args <- getArgs

    if (length args == 0)
       then do printUsage
               exitWith (ExitFailure 1)
       else do

    let fname = args !! 0

    dirExist <- doesDirectoryExist fname
    if dirExist
       then do putStrLn $ printf "%s is a directory." fname
               exitWith (ExitFailure 1)
       else do

    fileExist <- doesFileExist fname
    if not fileExist
       then do putStrLn $ printf "The file \"%s\" does not exist." fname
               exitWith (ExitFailure 1)
       else do
    inh <- openFile fname ReadMode
    fsize <- hFileSize inh
    inpStr <- hGetContents inh

    putStrLn $ printf "The size of the file \"%s\" is %d." fname fsize
    putStrLn ""

    printHexTable inpStr 0 fsize

    putStrLn ""
    putStrLn $ printf "Read %d bytes." fsize

    hClose inh

 

 

실행 예 1> testHexView_02 temp_1.bin
The size of the file "temp_1.bin" is 12.

0000 0000:  48 65 6C 6C 6F 20 74 68-65 72 65 0A              |Hello there.    |

Read 12 bytes.

실행 예 2> testHexView_02 myFile.ser
The size of the file "myFile.ser" is 130.

0000 0000:  AC ED 00 05 73 72 00 06-50 65 72 73 6F 6E 07 31  |....sr..Person.1|
0000 0010:  46 DB A5 1D 44 AB 02 00-03 49 00 03 61 67 65 4C  |F...D....I..ageL|
0000 0020:  00 09 66 69 72 73 74 4E-61 6D 65 74 00 12 4C 6A  |..firstNamet..Lj|
0000 0030:  61 76 61 2F 6C 61 6E 67-2F 53 74 72 69 6E 67 3B  |ava/lang/String;|
0000 0040:  4C 00 08 6C 61 73 74 4E-61 6D 65 71 00 7E 00 01  |L..lastNameq.~..|
0000 0050:  78 70 00 00 00 13 74 00-05 4A 61 6D 65 73 74 00  |xp....t..Jamest.|
0000 0060:  04 52 79 61 6E 73 71 00-7E 00 00 00 00 00 1E 74  |.Ryansq.~......t|
0000 0070:  00 07 4F 62 69 2D 77 61-6E 74 00 06 4B 65 6E 6F  |..Obi-want..Keno|
0000 0080:  62 69                                            |bi              |

Read 130 bytes.

 

 

Posted by Scripter
,