diff options
author | joe <joe@jerkface.net> | 2017-01-18 21:24:38 -0500 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-01-18 21:24:38 -0500 |
commit | 1d7dd944e0a13d3f09b65f7629d1f96098ea7974 (patch) | |
tree | 6c02f4d9d6e95f9a2d596c1854d5938daeeeddcc /tests | |
parent | 3c9e37d4f349ba2b4395cb10b5a3671decf89d68 (diff) | |
parent | a8498921ddf37e864968a3865e3e254352b5d285 (diff) |
Merge branch 'krpc' into dht-only
Diffstat (limited to 'tests')
-rw-r--r-- | tests/Network/KRPC/MessageSpec.hs | 72 | ||||
-rw-r--r-- | tests/Network/KRPC/MethodSpec.hs | 52 | ||||
-rw-r--r-- | tests/Network/KRPCSpec.hs | 59 |
3 files changed, 183 insertions, 0 deletions
diff --git a/tests/Network/KRPC/MessageSpec.hs b/tests/Network/KRPC/MessageSpec.hs new file mode 100644 index 00000000..498ef679 --- /dev/null +++ b/tests/Network/KRPC/MessageSpec.hs | |||
@@ -0,0 +1,72 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# OPTIONS_GHC -fno-warn-orphans #-} | ||
3 | module Network.KRPC.MessageSpec (spec) where | ||
4 | import Control.Applicative | ||
5 | import Data.ByteString.Lazy as BL | ||
6 | import Test.Hspec | ||
7 | import Test.QuickCheck | ||
8 | import Test.QuickCheck.Instances () | ||
9 | |||
10 | import Data.BEncode as BE | ||
11 | import Network.KRPC.Message | ||
12 | |||
13 | instance Arbitrary ErrorCode where | ||
14 | arbitrary = arbitraryBoundedEnum | ||
15 | |||
16 | instance Arbitrary KError where | ||
17 | arbitrary = KError <$> arbitrary <*> arbitrary <*> arbitrary | ||
18 | |||
19 | instance Arbitrary KQuery where | ||
20 | arbitrary = KQuery <$> pure (BInteger 0) <*> arbitrary <*> arbitrary | ||
21 | |||
22 | instance Arbitrary KResponse where | ||
23 | -- TODO: Abitrary instance for ReflectedIP | ||
24 | arbitrary = KResponse <$> pure (BList []) <*> arbitrary <*> pure Nothing | ||
25 | |||
26 | instance Arbitrary KMessage where | ||
27 | arbitrary = frequency | ||
28 | [ (1, Q <$> arbitrary) | ||
29 | , (1, R <$> arbitrary) | ||
30 | , (1, E <$> arbitrary) | ||
31 | ] | ||
32 | |||
33 | spec :: Spec | ||
34 | spec = do | ||
35 | describe "error message" $ do | ||
36 | it "properly bencoded (iso)" $ property $ \ ke -> | ||
37 | BE.decode (BL.toStrict (BE.encode ke)) `shouldBe` Right (ke :: KError) | ||
38 | |||
39 | it "properly bencoded" $ do | ||
40 | BE.decode "d1:eli201e23:A Generic Error Ocurrede1:t2:aa1:y1:ee" | ||
41 | `shouldBe` Right (KError GenericError "A Generic Error Ocurred" "aa") | ||
42 | |||
43 | BE.decode "d1:eli202e22:A Server Error Ocurrede1:t2:bb1:y1:ee" | ||
44 | `shouldBe` Right (KError ServerError "A Server Error Ocurred" "bb") | ||
45 | |||
46 | BE.decode "d1:eli203e24:A Protocol Error Ocurrede1:t2:cc1:y1:ee" | ||
47 | `shouldBe` Right (KError ProtocolError "A Protocol Error Ocurred" "cc") | ||
48 | |||
49 | BE.decode "d1:eli204e30:Attempt to call unknown methode1:t2:dd1:y1:ee" | ||
50 | `shouldBe` Right | ||
51 | (KError MethodUnknown "Attempt to call unknown method" "dd") | ||
52 | |||
53 | describe "query message" $ do | ||
54 | it "properly bencoded (iso)" $ property $ \ kq -> | ||
55 | BE.decode (BL.toStrict (BE.encode kq)) `shouldBe` Right (kq :: KQuery) | ||
56 | |||
57 | it "properly bencoded" $ do | ||
58 | BE.decode "d1:ale1:q4:ping1:t2:aa1:y1:qe" `shouldBe` | ||
59 | Right (KQuery (BList []) "ping" "aa") | ||
60 | |||
61 | |||
62 | describe "response message" $ do | ||
63 | it "properly bencoded (iso)" $ property $ \ kr -> | ||
64 | BE.decode (BL.toStrict (BE.encode kr)) `shouldBe` Right (kr :: KResponse) | ||
65 | |||
66 | it "properly bencoded" $ do | ||
67 | BE.decode "d1:rle1:t2:aa1:y1:re" `shouldBe` | ||
68 | Right (KResponse (BList []) "aa" Nothing) | ||
69 | |||
70 | describe "generic message" $ do | ||
71 | it "properly bencoded (iso)" $ property $ \ km -> | ||
72 | BE.decode (BL.toStrict (BE.encode km)) `shouldBe` Right (km :: KMessage) | ||
diff --git a/tests/Network/KRPC/MethodSpec.hs b/tests/Network/KRPC/MethodSpec.hs new file mode 100644 index 00000000..c1c58282 --- /dev/null +++ b/tests/Network/KRPC/MethodSpec.hs | |||
@@ -0,0 +1,52 @@ | |||
1 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
2 | {-# LANGUAGE FlexibleInstances #-} | ||
3 | {-# LANGUAGE OverloadedStrings #-} | ||
4 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
5 | {-# LANGUAGE DeriveDataTypeable #-} | ||
6 | {-# OPTIONS_GHC -fno-warn-orphans #-} | ||
7 | module Network.KRPC.MethodSpec where | ||
8 | import Control.Applicative | ||
9 | import Data.BEncode | ||
10 | import Data.ByteString as BS | ||
11 | import Data.Typeable | ||
12 | import Network.KRPC | ||
13 | import Test.Hspec | ||
14 | |||
15 | |||
16 | data Ping = Ping | ||
17 | deriving (Show, Eq, Typeable) | ||
18 | |||
19 | instance BEncode Ping where | ||
20 | toBEncode Ping = toBEncode () | ||
21 | fromBEncode b = Ping <$ (fromBEncode b :: Result ()) | ||
22 | |||
23 | instance KRPC Ping Ping | ||
24 | |||
25 | ping :: Monad h => Handler h | ||
26 | ping = handler $ \ _ Ping -> return Ping | ||
27 | |||
28 | newtype Echo a = Echo a | ||
29 | deriving (Show, Eq, BEncode, Typeable) | ||
30 | |||
31 | echo :: Monad h => Handler h | ||
32 | echo = handler $ \ _ (Echo a) -> return (Echo (a :: ByteString)) | ||
33 | |||
34 | instance (Typeable a, BEncode a) => KRPC (Echo a) (Echo a) | ||
35 | |||
36 | spec :: Spec | ||
37 | spec = do | ||
38 | describe "ping method" $ do | ||
39 | it "name is ping" $ do | ||
40 | (method :: Method Ping Ping) `shouldBe` "ping" | ||
41 | |||
42 | it "has pretty Show instance" $ do | ||
43 | show (method :: Method Ping Ping) `shouldBe` "ping :: Ping -> Ping" | ||
44 | |||
45 | describe "echo method" $ do | ||
46 | it "is overloadable" $ do | ||
47 | (method :: Method (Echo Int ) (Echo Int )) `shouldBe` "echo int" | ||
48 | (method :: Method (Echo Bool) (Echo Bool)) `shouldBe` "echo bool" | ||
49 | |||
50 | it "has pretty Show instance" $ do | ||
51 | show (method :: Method (Echo Int) (Echo Int)) | ||
52 | `shouldBe` "echo int :: Echo Int -> Echo Int" \ No newline at end of file | ||
diff --git a/tests/Network/KRPCSpec.hs b/tests/Network/KRPCSpec.hs new file mode 100644 index 00000000..eabcc817 --- /dev/null +++ b/tests/Network/KRPCSpec.hs | |||
@@ -0,0 +1,59 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# OPTIONS_GHC -fno-warn-orphans #-} | ||
3 | module Network.KRPCSpec (spec) where | ||
4 | import Control.Monad.Logger | ||
5 | import Control.Monad.Reader | ||
6 | import Network.KRPC | ||
7 | import Network.KRPC.MethodSpec hiding (spec) | ||
8 | import Test.Hspec | ||
9 | |||
10 | servAddr :: SockAddr | ||
11 | servAddr = SockAddrInet 6000 (256 * 256 * 256 + 127) | ||
12 | |||
13 | handlers :: [Handler IO] | ||
14 | handlers = | ||
15 | [ handler $ \ _ Ping -> return Ping | ||
16 | , handler $ \ _ (Echo a) -> return (Echo (a :: Bool)) | ||
17 | , handler $ \ _ (Echo a) -> return (Echo (a :: Int)) | ||
18 | ] | ||
19 | |||
20 | instance MonadLogger IO where | ||
21 | monadLoggerLog _ _ _ _ = return () | ||
22 | |||
23 | opts :: Options | ||
24 | opts = def { optQueryTimeout = 1 } | ||
25 | |||
26 | spec :: Spec | ||
27 | spec = do | ||
28 | let qr :: MonadKRPC h m => SockAddr -> Echo Int -> m (Echo Int) | ||
29 | qr = query | ||
30 | |||
31 | describe "manager" $ do | ||
32 | it "is active until closeManager called" $ do | ||
33 | m <- newManager opts servAddr [] | ||
34 | isActive m `shouldReturn` True | ||
35 | closeManager m | ||
36 | isActive m `shouldReturn` False | ||
37 | |||
38 | describe "query" $ do | ||
39 | it "run handlers" $ do | ||
40 | let int = 0xabcd :: Int | ||
41 | (withManager opts servAddr handlers $ runReaderT $ do | ||
42 | listen | ||
43 | query servAddr (Echo int)) | ||
44 | `shouldReturn` Echo int | ||
45 | |||
46 | it "count transactions properly" $ do | ||
47 | (withManager opts servAddr handlers $ runReaderT $ do | ||
48 | listen | ||
49 | _ <- qr servAddr (Echo 0xabcd) | ||
50 | _ <- qr servAddr (Echo 0xabcd) | ||
51 | getQueryCount | ||
52 | ) | ||
53 | `shouldReturn` 2 | ||
54 | |||
55 | it "throw timeout exception" $ do | ||
56 | (withManager opts servAddr handlers $ runReaderT $ do | ||
57 | qr servAddr (Echo 0xabcd) | ||
58 | ) | ||
59 | `shouldThrow` (== TimeoutExpired) | ||