-
Notifications
You must be signed in to change notification settings - Fork 3
/
bin2block.hs
58 lines (48 loc) · 1.62 KB
/
bin2block.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
{-# LANGUAGE DeriveDataTypeable #-}
module Main (main) where
import System.Environment
import Text.Read
import Data.Word
import Data.Bits
import Data.Char
import Data.Typeable
import Control.Exception
import qualified Data.ByteString as BS
import System.Posix
-- Split an unsigned 16 bit int into a pair) of unsigned 8 bit ints
splitWord16_8 :: Word16 -> [Word8]
splitWord16_8 a = [fromIntegral a, fromIntegral (shiftR a 8)]
-- Calculates the block's checksum byte
checkSum :: [Word8] -> Word8
checkSum = foldl xor 0
-- Takes a block of data, adds the flag (for header or data) and prepends
-- the .tap format length field
block :: [Word8] -> BS.ByteString
block blockData = let payload = [255] ++ blockData ++ [checkSum ([255] ++ blockData)] in
BS.pack (splitWord16_8 (fromIntegral (length payload)) ++ payload)
-- for parsing all the command line arguments
parseArgs :: [String] -> Maybe (String)
parseArgs args = let l = length args in
if l /= 1 then Nothing
else Just (args !! 0)
data Bin2TapException
= InvalidArgs
deriving (Eq, Typeable)
instance Show Bin2TapException where
show InvalidArgs =
"Usage: bin2block <filename>\n"
instance Exception Bin2TapException
-- Main conversion function
tapeConversion :: String -> IO ()
tapeConversion filename = do
-- get the contents of the binary
filedata <- BS.readFile filename;
-- save a new file that contains...
BS.writeFile outfilename ( block (BS.unpack filedata))
where outfilename = filename ++ ".tap"
main :: IO ()
main = do
args <- getArgs
case parseArgs args of
Nothing -> throw InvalidArgs
Just file -> tapeConversion file