]> gitweb.michael.orlitzky.com - dead/htnef.git/blob - src/tnef/file.hs
Initial commit.
[dead/htnef.git] / src / tnef / file.hs
1 --
2 -- Copyright Michael Orlitzky
3 --
4 -- http://michael.orlitzky.com/
5 --
6 -- This program is free software: you can redistribute it and/or modify
7 -- it under the terms of the GNU General Public License as published by
8 -- the Free Software Foundation, either version 3 of the License, or
9 -- (at your option) any later version.
10 --
11 -- This program is distributed in the hope that it will be useful,
12 -- but WITHOUT ANY WARRANTY; without even the implied warranty of
13 -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14 -- GNU General Public License for more details.
15 --
16 -- http://www.fsf.org/licensing/licenses/gpl.html
17 --
18
19 module Tnef.File where
20
21 import Data.Binary
22 import qualified Data.Binary.Get as BinaryGet
23 import qualified Data.Binary.Put as BinaryPut
24 import Data.Int (Int64)
25 import Tnef.Attachment
26 import Tnef.Object
27
28
29 -- A TNEF "file" has a signature at the top which should be the same
30 -- for all TNEF files. There's also a "key," which probably does
31 -- something, and looks to be unique. After that, there's a variable
32 -- number of objects (whose structure can be seen in TnefObject). The
33 -- "total bytes" thing is not part of the file. I'm just using it to
34 -- keep track of the bytes read for now (to make sure it equals the
35 -- size of the file when we're done).
36 data TnefFile = TnefFile { signature :: Word32,
37 key :: Word16,
38 first_object :: TnefObject,
39 total_bytes :: Int64 }
40
41
42 -- Magicest of numbers
43 -- Important: Int doesn't guarantee 32 bits, so we
44 -- need to use the Integer type here.
45 tnef_signature :: Integer
46 tnef_signature = 0x223e9f78
47
48
49
50 instance Show TnefFile where
51 show x = "Signature: " ++ (show (signature x)) ++ " (Correct: " ++ (show tnef_signature) ++ ")\n" ++
52 "Key: " ++ (show (key x)) ++ "\n" ++
53 concat (map show (get_object_list x)) -- Show the objects, one at a time
54
55
56 -- Recursively collect an array of objects. It dies
57 -- on the last one, which has no next_object property.
58 -- Help?
59 get_object_list :: TnefFile -> [TnefObject]
60 get_object_list x = get_successive_objects (first_object x)
61
62
63 get_successive_objects :: TnefObject -> [TnefObject]
64 get_successive_objects Nil = [Nil]
65 get_successive_objects x = (x : (get_successive_objects (next_object x)))
66
67
68 instance Binary TnefFile where
69 put _ = do BinaryPut.putWord8 0
70 get = do
71 signature_word <- BinaryGet.getWord32host
72 key_word <- BinaryGet.getWord16host
73 first_object_word <- get :: Get TnefObject
74 total_bytes_word <- BinaryGet.bytesRead
75 return (TnefFile { signature = signature_word,
76 key = key_word,
77 first_object = first_object_word,
78 total_bytes = total_bytes_word })
79
80
81 write_tnef_file :: TnefFile -> [IO ()]
82 write_tnef_file x = do
83 let objects = get_object_list x
84 let attachments = get_attachment_list objects
85 map write_attachment attachments