+--
+-- Copyright Michael Orlitzky
+--
+-- http://michael.orlitzky.com/
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU General Public License as published by
+-- the Free Software Foundation, either version 3 of the License, or
+-- (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+-- GNU General Public License for more details.
+--
+-- http://www.fsf.org/licensing/licenses/gpl.html
+--
+
+module Tnef.Object where
+
+import Control.Monad (replicateM)
+import Data.Binary
+import qualified Data.Binary.Get as BinaryGet
+import qualified Data.Binary.Put as BinaryPut
+import qualified Data.ByteString.Lazy as BS
+import Data.Char
+import Data.Word
+import Tnef.ObjectName
+import Tnef.ObjectLvl
+
+
+-- The only tricky part here is the "chained" TnefObjects.
+-- Each object contains the next one. It's like that because
+-- I couldn't figure out how to parse an unknown number of
+-- objects using Binary.Get.
+data TnefObject = TnefObject { obj_lvl :: TnefObjectLvl,
+ obj_name :: TnefObjectName,
+ obj_type :: Word16,
+ obj_length :: Word32,
+ obj_data :: [Word8],
+ obj_checksum :: Word16,
+ next_object :: TnefObject }
+ | Nil
+
+
+instance Show TnefObject where
+ show Nil = "Nil"
+ show x = "<object>" ++ "\n" ++
+ " Level: " ++ (show (obj_lvl x)) ++ "\n" ++
+ " Name: " ++ (show (obj_name x)) ++ "\n" ++
+ " Type: " ++ (show (obj_type x)) ++ "\n" ++
+ " Data: " ++ (show_data x) ++ "\n" ++
+ " Checksum: " ++ (show (obj_checksum x)) ++ " (Actual: " ++ (show (checksum (obj_data x))) ++ ")\n" ++
+ "</object>\n"
+
+drop_null_byte :: [Word8] -> [Word8]
+drop_null_byte = takeWhile (/= 0)
+
+show_data :: TnefObject -> String
+show_data Nil = ""
+show_data x
+ | ((show n) == "Attachment Data") = "(Binary)"
+ | ((show n) == "Date Sent") = show (obj_data x)
+ | ((show n) == "Date Received") = show (obj_data x)
+ | ((show n) == "Date Modified") = show (obj_data x)
+ | ((show n) == "Attachment Modification Date") = show (obj_data x)
+ | otherwise = t
+ where
+ n = (obj_name x)
+ t = (map (chr . word8_to_int) (drop_null_byte (obj_data x)))
+
+
+-- Just sum up the values of the bytes, and take that
+-- value mod 65536 at the end. (checksum obj_data) should
+-- equal the value of obj_checksum for each TnefObject.
+checksum :: [Word8] -> Int
+checksum x = (foldr (+) 0 (map word8_to_int x)) `mod` 0x10000
+
+
+-- Just for convenience
+word8_to_int :: Word8 -> Int
+word8_to_int x = (fromIntegral x)
+
+
+instance Binary TnefObject where
+ put _ = do BinaryPut.putWord8 0
+ get = do
+ obj_lvl_word <- BinaryGet.getWord8
+ obj_name_word <- BinaryGet.getWord16host
+ obj_type_word <- BinaryGet.getWord16host
+ obj_length_word <- BinaryGet.getWord32host
+ -- This pulls in obj_length bytes of data as a [Word8]
+ obj_data_word <- replicateM (fromIntegral obj_length_word) BinaryGet.getWord8
+ obj_checksum_word <- BinaryGet.getWord16host
+ next_object_word <- get_next_tnef_object
+ return (TnefObject { obj_lvl = (word_to_lvl obj_lvl_word),
+ obj_name = (word_to_name obj_name_word),
+ obj_type = obj_type_word,
+ obj_length = obj_length_word,
+ obj_data = obj_data_word,
+ obj_checksum = obj_checksum_word,
+ next_object = next_object_word })
+
+
+-- If there's no more data, return Nil as the "next" object.
+get_next_tnef_object :: Get TnefObject
+get_next_tnef_object = do
+ is_empty <- BinaryGet.isEmpty
+ if is_empty
+ then return Nil
+ else (get :: Get TnefObject)
+
+
+write_tnef_object :: String -> TnefObject -> IO ()
+write_tnef_object _ Nil = return ()
+write_tnef_object path x
+ | ((show n) == "Attachment Data") = BS.writeFile path (BS.pack (obj_data x))
+ | otherwise = return ()
+ where n = (obj_name x)