Skip to content

Commit

Permalink
Implements first test cases
Browse files Browse the repository at this point in the history
Implements two test cases that validate whether a connection can be
opened with SAM
  • Loading branch information
solatis committed Feb 14, 2015
1 parent 564d3cb commit e0448e9
Show file tree
Hide file tree
Showing 5 changed files with 32 additions and 10 deletions.
7 changes: 7 additions & 0 deletions network-anonymous-i2p.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,10 @@ library
exposed-modules: Network.Anonymous.I2P,
Network.Anonymous.I2P.Types

other-modules: Network.Anonymous.I2P.Internal.Network.Protocol,
Network.Anonymous.I2P.Internal.Network.Socket,
Network.Anonymous.I2P.Internal.Debug

build-depends: base == 4.*,
network,
binary,
Expand All @@ -57,6 +61,9 @@ test-suite network-anonymous-i2p-test

build-depends: base,
hspec,
resourcet,
mtl,
network,

network-anonymous-i2p

Expand Down
4 changes: 0 additions & 4 deletions src/Network/Anonymous/I2P/Internal.hs

This file was deleted.

5 changes: 0 additions & 5 deletions src/Network/Anonymous/I2P/Internal/Debug.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,4 @@ import Debug.Trace

-- | Alias to Debug.Trace(trace), but disabled in non-debug builds
log :: String -> a -> a

#ifdef DEBUG
log = trace
#else
log _ ret = ret
#endif
4 changes: 3 additions & 1 deletion test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@ module Main where
import Test.Hspec.Runner
import qualified Spec

import Network (withSocketsDo)

main :: IO ()
main =
hspecWith defaultConfig Spec.spec
withSocketsDo $ hspecWith defaultConfig Spec.spec
22 changes: 22 additions & 0 deletions test/Network/Anonymous/I2P/ConnectSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
module Network.Anonymous.I2P.ConnectSpec where

import Control.Monad.Trans.Resource
import Control.Monad.Error

import Data.Either (isRight, isLeft)

import Network.Anonymous.I2P (initialize)
import Network.Anonymous.I2P.Types

import Test.Hspec

spec :: Spec
spec = do
describe "when initializing a context" $ do
it "SAM should be listening at its default port" $ do
result <- runResourceT $ runErrorT $ initialize "127.0.0.1" 7656 VirtualStream
isRight result `shouldBe` True

it "SAM should not be listening at another port" $ do
result <- runResourceT $ runErrorT $ initialize "127.0.0.1" 1234 VirtualStream
isLeft result `shouldBe` True

0 comments on commit e0448e9

Please sign in to comment.