summaryrefslogtreecommitdiff
path: root/tests/Network
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Network')
-rw-r--r--tests/Network/KRPC/MethodSpec.hs52
-rw-r--r--tests/Network/KRPCSpec.hs33
2 files changed, 85 insertions, 0 deletions
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 #-}
7module Network.KRPC.MethodSpec where
8import Control.Applicative
9import Data.BEncode
10import Data.ByteString as BS
11import Data.Typeable
12import Network.KRPC
13import Test.Hspec
14
15
16data Ping = Ping
17 deriving (Show, Eq, Typeable)
18
19instance BEncode Ping where
20 toBEncode Ping = toBEncode ()
21 fromBEncode b = Ping <$ (fromBEncode b :: Result ())
22
23instance KRPC Ping Ping
24
25ping :: Monad h => Handler h
26ping = handler $ \ _ Ping -> return Ping
27
28newtype Echo a = Echo a
29 deriving (Show, Eq, BEncode, Typeable)
30
31echo :: Monad h => Handler h
32echo = handler $ \ _ (Echo a) -> return (Echo (a :: ByteString))
33
34instance (Typeable a, BEncode a) => KRPC (Echo a) (Echo a)
35
36spec :: Spec
37spec = 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..27148682
--- /dev/null
+++ b/tests/Network/KRPCSpec.hs
@@ -0,0 +1,33 @@
1{-# LANGUAGE OverloadedStrings #-}
2module Network.KRPCSpec (spec) where
3import Control.Monad.Reader
4import Network.Socket (SockAddr (..))
5import Network.KRPC
6import Network.KRPC.MethodSpec hiding (spec)
7import Test.Hspec
8
9servAddr :: SockAddr
10servAddr = SockAddrInet 6000 (256 * 256 * 256 + 127)
11
12handlers :: [Handler IO]
13handlers =
14 [ handler $ \ _ Ping -> return Ping
15 , handler $ \ _ (Echo a) -> return (Echo (a :: Bool))
16 , handler $ \ _ (Echo a) -> return (Echo (a :: Int))
17 ]
18
19spec :: Spec
20spec = do
21 describe "query" $ do
22 it "run handlers" $ do
23 let int = 0xabcd :: Int
24 (withManager servAddr handlers $ runReaderT $ do
25 listen
26 query servAddr (Echo int))
27 `shouldReturn` Echo int
28
29 it "throw timeout exception" $ do
30 (withManager servAddr handlers $ runReaderT $ do
31 query servAddr (Echo (0xabcd :: Int))
32 )
33 `shouldThrow` (== KError GenericError "timeout expired" "0")