summaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-23 03:28:54 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-23 03:28:54 +0400
commit857988ceb7c9d73926c07bb1522ce86a1669f4c5 (patch)
tree8f769769ff6fca061249635c4ee6c7f1ae47cc1b /tests
parent12a07d236274d154846100d27e8d3a33e430ad12 (diff)
Add spec for Message module
Diffstat (limited to 'tests')
-rw-r--r--tests/Network/KRPC/MessageSpec.hs71
-rw-r--r--tests/Spec.hs1
2 files changed, 72 insertions, 0 deletions
diff --git a/tests/Network/KRPC/MessageSpec.hs b/tests/Network/KRPC/MessageSpec.hs
new file mode 100644
index 00000000..7aca4489
--- /dev/null
+++ b/tests/Network/KRPC/MessageSpec.hs
@@ -0,0 +1,71 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-# OPTIONS_GHC -fno-warn-orphans #-}
3module Network.KRPC.MessageSpec (spec) where
4import Control.Applicative
5import Data.ByteString.Lazy as BL
6import Test.Hspec
7import Test.QuickCheck
8import Test.QuickCheck.Instances ()
9
10import Data.BEncode as BE
11import Network.KRPC.Message
12
13instance Arbitrary ErrorCode where
14 arbitrary = arbitraryBoundedEnum
15
16instance Arbitrary KError where
17 arbitrary = KError <$> arbitrary <*> arbitrary <*> arbitrary
18
19instance Arbitrary KQuery where
20 arbitrary = KQuery <$> pure (BInteger 0) <*> arbitrary <*> arbitrary
21
22instance Arbitrary KResponse where
23 arbitrary = KResponse <$> pure (BList []) <*> arbitrary
24
25instance Arbitrary KMessage where
26 arbitrary = frequency
27 [ (1, Q <$> arbitrary)
28 , (1, R <$> arbitrary)
29 , (1, E <$> arbitrary)
30 ]
31
32spec :: Spec
33spec = do
34 describe "error message" $ do
35 it "properly bencoded (iso)" $ property $ \ ke ->
36 BE.decode (BL.toStrict (BE.encode ke)) `shouldBe` Right (ke :: KError)
37
38 it "properly bencoded" $ do
39 BE.decode "d1:eli201e23:A Generic Error Ocurrede1:t2:aa1:y1:ee"
40 `shouldBe` Right (KError GenericError "A Generic Error Ocurred" "aa")
41
42 BE.decode "d1:eli202e22:A Server Error Ocurrede1:t2:bb1:y1:ee"
43 `shouldBe` Right (KError ServerError "A Server Error Ocurred" "bb")
44
45 BE.decode "d1:eli203e24:A Protocol Error Ocurrede1:t2:cc1:y1:ee"
46 `shouldBe` Right (KError ProtocolError "A Protocol Error Ocurred" "cc")
47
48 BE.decode "d1:eli204e30:Attempt to call unknown methode1:t2:dd1:y1:ee"
49 `shouldBe` Right
50 (KError MethodUnknown "Attempt to call unknown method" "dd")
51
52 describe "query message" $ do
53 it "properly bencoded (iso)" $ property $ \ kq ->
54 BE.decode (BL.toStrict (BE.encode kq)) `shouldBe` Right (kq :: KQuery)
55
56 it "properly bencoded" $ do
57 BE.decode "d1:ale1:q4:ping1:t2:aa1:y1:qe" `shouldBe`
58 Right (KQuery (BList []) "ping" "aa")
59
60
61 describe "response message" $ do
62 it "properly bencoded (iso)" $ property $ \ kr ->
63 BE.decode (BL.toStrict (BE.encode kr)) `shouldBe` Right (kr :: KResponse)
64
65 it "properly bencoded" $ do
66 BE.decode "d1:rle1:t2:aa1:y1:re" `shouldBe`
67 Right (KResponse (BList []) "aa")
68
69 describe "generic message" $ do
70 it "properly bencoded (iso)" $ property $ \ km ->
71 BE.decode (BL.toStrict (BE.encode km)) `shouldBe` Right (km :: KMessage) \ No newline at end of file
diff --git a/tests/Spec.hs b/tests/Spec.hs
new file mode 100644
index 00000000..52ef578f
--- /dev/null
+++ b/tests/Spec.hs
@@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover #-} \ No newline at end of file