summaryrefslogtreecommitdiff
path: root/tests/suite.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/suite.hs')
-rw-r--r--tests/suite.hs160
1 files changed, 160 insertions, 0 deletions
diff --git a/tests/suite.hs b/tests/suite.hs
new file mode 100644
index 0000000..cb4f4aa
--- /dev/null
+++ b/tests/suite.hs
@@ -0,0 +1,160 @@
1{-# LANGUAGE CPP #-}
2import Test.Framework (defaultMain, testGroup, Test)
3import Test.Framework.Providers.HUnit
4import Test.Framework.Providers.QuickCheck2
5import Test.HUnit hiding (Test)
6
7import Data.Word
8import Data.OpenPGP.Arbitrary ()
9import qualified Data.OpenPGP as OpenPGP
10import qualified Data.OpenPGP.Internal as OpenPGP
11
12#ifdef CEREAL
13import Data.Serialize
14import qualified Data.ByteString as B
15
16decode' :: (Serialize a) => B.ByteString -> a
17decode' x = let Right v = decode x in v
18#else
19import Data.Binary
20import qualified Data.ByteString.Lazy as B
21
22decode' :: (Binary a) => B.ByteString -> a
23decode' = decode
24#endif
25
26testSerialization :: FilePath -> Assertion
27testSerialization fp = do
28 bs <- B.readFile $ "tests/data/" ++ fp
29 nullShield "First" (decode' bs) (\firstpass ->
30 nullShield "Second" (decode' $ encode firstpass) (
31 assertEqual ("for " ++ fp) firstpass
32 )
33 )
34 where
35 nullShield pass (OpenPGP.Message []) _ =
36 assertFailure $ pass ++ " pass of " ++ fp ++ " decoded to nothing."
37 nullShield _ m f = f m
38
39prop_s2k_count :: Word8 -> Bool
40prop_s2k_count c =
41 c == OpenPGP.encode_s2k_count (OpenPGP.decode_s2k_count c)
42
43prop_MPI_serialization_loop :: OpenPGP.MPI -> Bool
44prop_MPI_serialization_loop mpi =
45 mpi == decode' (encode mpi)
46
47prop_S2K_serialization_loop :: OpenPGP.S2K -> Bool
48prop_S2K_serialization_loop s2k =
49 s2k == decode' (encode s2k)
50
51prop_SignatureSubpacket_serialization_loop :: OpenPGP.SignatureSubpacket -> Bool
52prop_SignatureSubpacket_serialization_loop packet =
53 packet == decode' (encode packet)
54
55tests :: [Test]
56tests =
57 [
58 testGroup "Serialization" [
59 testCase "000001-006.public_key" (testSerialization "000001-006.public_key"),
60 testCase "000002-013.user_id" (testSerialization "000002-013.user_id"),
61 testCase "000003-002.sig" (testSerialization "000003-002.sig"),
62 testCase "000004-012.ring_trust" (testSerialization "000004-012.ring_trust"),
63 testCase "000005-002.sig" (testSerialization "000005-002.sig"),
64 testCase "000006-012.ring_trust" (testSerialization "000006-012.ring_trust"),
65 testCase "000007-002.sig" (testSerialization "000007-002.sig"),
66 testCase "000008-012.ring_trust" (testSerialization "000008-012.ring_trust"),
67 testCase "000009-002.sig" (testSerialization "000009-002.sig"),
68 testCase "000010-012.ring_trust" (testSerialization "000010-012.ring_trust"),
69 testCase "000011-002.sig" (testSerialization "000011-002.sig"),
70 testCase "000012-012.ring_trust" (testSerialization "000012-012.ring_trust"),
71 testCase "000013-014.public_subkey" (testSerialization "000013-014.public_subkey"),
72 testCase "000014-002.sig" (testSerialization "000014-002.sig"),
73 testCase "000015-012.ring_trust" (testSerialization "000015-012.ring_trust"),
74 testCase "000016-006.public_key" (testSerialization "000016-006.public_key"),
75 testCase "000017-002.sig" (testSerialization "000017-002.sig"),
76 testCase "000018-012.ring_trust" (testSerialization "000018-012.ring_trust"),
77 testCase "000019-013.user_id" (testSerialization "000019-013.user_id"),
78 testCase "000020-002.sig" (testSerialization "000020-002.sig"),
79 testCase "000021-012.ring_trust" (testSerialization "000021-012.ring_trust"),
80 testCase "000022-002.sig" (testSerialization "000022-002.sig"),
81 testCase "000023-012.ring_trust" (testSerialization "000023-012.ring_trust"),
82 testCase "000024-014.public_subkey" (testSerialization "000024-014.public_subkey"),
83 testCase "000025-002.sig" (testSerialization "000025-002.sig"),
84 testCase "000026-012.ring_trust" (testSerialization "000026-012.ring_trust"),
85 testCase "000027-006.public_key" (testSerialization "000027-006.public_key"),
86 testCase "000028-002.sig" (testSerialization "000028-002.sig"),
87 testCase "000029-012.ring_trust" (testSerialization "000029-012.ring_trust"),
88 testCase "000030-013.user_id" (testSerialization "000030-013.user_id"),
89 testCase "000031-002.sig" (testSerialization "000031-002.sig"),
90 testCase "000032-012.ring_trust" (testSerialization "000032-012.ring_trust"),
91 testCase "000033-002.sig" (testSerialization "000033-002.sig"),
92 testCase "000034-012.ring_trust" (testSerialization "000034-012.ring_trust"),
93 testCase "000035-006.public_key" (testSerialization "000035-006.public_key"),
94 testCase "000036-013.user_id" (testSerialization "000036-013.user_id"),
95 testCase "000037-002.sig" (testSerialization "000037-002.sig"),
96 testCase "000038-012.ring_trust" (testSerialization "000038-012.ring_trust"),
97 testCase "000039-002.sig" (testSerialization "000039-002.sig"),
98 testCase "000040-012.ring_trust" (testSerialization "000040-012.ring_trust"),
99 testCase "000041-017.attribute" (testSerialization "000041-017.attribute"),
100 testCase "000042-002.sig" (testSerialization "000042-002.sig"),
101 testCase "000043-012.ring_trust" (testSerialization "000043-012.ring_trust"),
102 testCase "000044-014.public_subkey" (testSerialization "000044-014.public_subkey"),
103 testCase "000045-002.sig" (testSerialization "000045-002.sig"),
104 testCase "000046-012.ring_trust" (testSerialization "000046-012.ring_trust"),
105 testCase "000047-005.secret_key" (testSerialization "000047-005.secret_key"),
106 testCase "000048-013.user_id" (testSerialization "000048-013.user_id"),
107 testCase "000049-002.sig" (testSerialization "000049-002.sig"),
108 testCase "000050-012.ring_trust" (testSerialization "000050-012.ring_trust"),
109 testCase "000051-007.secret_subkey" (testSerialization "000051-007.secret_subkey"),
110 testCase "000052-002.sig" (testSerialization "000052-002.sig"),
111 testCase "000053-012.ring_trust" (testSerialization "000053-012.ring_trust"),
112 testCase "000054-005.secret_key" (testSerialization "000054-005.secret_key"),
113 testCase "000055-002.sig" (testSerialization "000055-002.sig"),
114 testCase "000056-012.ring_trust" (testSerialization "000056-012.ring_trust"),
115 testCase "000057-013.user_id" (testSerialization "000057-013.user_id"),
116 testCase "000058-002.sig" (testSerialization "000058-002.sig"),
117 testCase "000059-012.ring_trust" (testSerialization "000059-012.ring_trust"),
118 testCase "000060-007.secret_subkey" (testSerialization "000060-007.secret_subkey"),
119 testCase "000061-002.sig" (testSerialization "000061-002.sig"),
120 testCase "000062-012.ring_trust" (testSerialization "000062-012.ring_trust"),
121 testCase "000063-005.secret_key" (testSerialization "000063-005.secret_key"),
122 testCase "000064-002.sig" (testSerialization "000064-002.sig"),
123 testCase "000065-012.ring_trust" (testSerialization "000065-012.ring_trust"),
124 testCase "000066-013.user_id" (testSerialization "000066-013.user_id"),
125 testCase "000067-002.sig" (testSerialization "000067-002.sig"),
126 testCase "000068-012.ring_trust" (testSerialization "000068-012.ring_trust"),
127 testCase "000069-005.secret_key" (testSerialization "000069-005.secret_key"),
128 testCase "000070-013.user_id" (testSerialization "000070-013.user_id"),
129 testCase "000071-002.sig" (testSerialization "000071-002.sig"),
130 testCase "000072-012.ring_trust" (testSerialization "000072-012.ring_trust"),
131 testCase "000073-017.attribute" (testSerialization "000073-017.attribute"),
132 testCase "000074-002.sig" (testSerialization "000074-002.sig"),
133 testCase "000075-012.ring_trust" (testSerialization "000075-012.ring_trust"),
134 testCase "000076-007.secret_subkey" (testSerialization "000076-007.secret_subkey"),
135 testCase "000077-002.sig" (testSerialization "000077-002.sig"),
136 testCase "000078-012.ring_trust" (testSerialization "000078-012.ring_trust"),
137 testCase "002182-002.sig" (testSerialization "002182-002.sig"),
138 testCase "pubring.gpg" (testSerialization "pubring.gpg"),
139 testCase "secring.gpg" (testSerialization "secring.gpg"),
140 testCase "compressedsig.gpg" (testSerialization "compressedsig.gpg"),
141 testCase "compressedsig-zlib.gpg" (testSerialization "compressedsig-zlib.gpg"),
142 testCase "compressedsig-bzip2.gpg" (testSerialization "compressedsig-bzip2.gpg"),
143 testCase "onepass_sig" (testSerialization "onepass_sig"),
144 testCase "symmetrically_encrypted" (testSerialization "symmetrically_encrypted"),
145 testCase "uncompressed-ops-dsa.gpg" (testSerialization "uncompressed-ops-dsa.gpg"),
146 testCase "uncompressed-ops-dsa-sha384.txt.gpg" (testSerialization "uncompressed-ops-dsa-sha384.txt.gpg"),
147 testCase "uncompressed-ops-rsa.gpg" (testSerialization "uncompressed-ops-rsa.gpg"),
148 testCase "3F5BBA0B0694BEB6000005-002.sig" (testSerialization "3F5BBA0B0694BEB6000005-002.sig"),
149 testCase "3F5BBA0B0694BEB6000017-002.sig" (testSerialization "3F5BBA0B0694BEB6000017-002.sig"),
150 testProperty "MPI encode/decode" prop_MPI_serialization_loop,
151 testProperty "S2K encode/decode" prop_S2K_serialization_loop,
152 testProperty "SignatureSubpacket encode/decode" prop_SignatureSubpacket_serialization_loop
153 ],
154 testGroup "S2K count" [
155 testProperty "S2K count encode reverses decode" prop_s2k_count
156 ]
157 ]
158
159main :: IO ()
160main = defaultMain tests