Skip to content

Commit

Permalink
Tests: Use random ports for testing
Browse files Browse the repository at this point in the history
Previously ports were statically defined. When running more than one
build on travis-ci, the build was failing when two build/test jobs
were running on the machine at the same time.

Now each run chooses three unique numbers in the range (30000, 60000).
  • Loading branch information
erikd committed Aug 5, 2015
1 parent 31f4a3e commit af28de0
Show file tree
Hide file tree
Showing 7 changed files with 50 additions and 223 deletions.
4 changes: 2 additions & 2 deletions Test/Request.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,8 +59,8 @@ mkTestRequestBS method scheme path mbody = mkTestRequest method scheme path $ HC
mkTestRequest :: HT.Method -> UriScheme -> String -> Maybe HC.RequestBody -> IO HC.Request
mkTestRequest method scheme path mbody = do
let port = show $ case scheme of
Http -> httpTestPort
Https -> httpsTestPort
Http -> httpTestPort portsDef
Https -> httpsTestPort portsDef
url = map toLower (show scheme) ++ "://localhost:" ++ port ++ path
req <- HC.parseUrl url
return $ req
Expand Down
48 changes: 43 additions & 5 deletions Test/ServerDef.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,48 @@
module Test.ServerDef where
------------------------------------------------------------
-- Copyright : Erik de Castro Lopo <[email protected]>
-- License : BSD3
------------------------------------------------------------

httpTestPort, httpsTestPort, testProxyPort :: Int
httpTestPort = 31080
httpsTestPort = 31443
testProxyPort = 31088
module Test.ServerDef
( PortsDef (..)
, portsDef
) where

import Data.List (sort)
import System.IO.Unsafe (unsafePerformIO)
import System.Random

data PortsDef = PortsDef
{ httpTestPort :: Int
, httpsTestPort :: Int
, proxyTestPort :: Int
}
deriving Show


-- Yeah, yeah, unsafePerformIO! Worst thing that can happen is that the tests
-- fail.
portsDef :: PortsDef
portsDef = unsafePerformIO getPortsDef


-- Grab three unique Ints in the range (30000, 60000) and stick them in a
-- PortsDef constructor.
getPortsDef :: IO PortsDef
getPortsDef = do
vals <- randomRL []
case sort vals of
[a, b, c] -> return $ PortsDef a b c
_ -> getPortsDef
where
randomRL :: [Int] -> IO [Int]
randomRL xs
| length xs == 3 = return $ sort xs
| otherwise = do
x <- randomRIO portRange
if x `elem` xs
then randomRL xs
else randomRL (x:xs)

portRange :: (Int, Int)
portRange = (30000, 60000)
4 changes: 2 additions & 2 deletions Test/TestServer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,12 +39,12 @@ import Test.Util

runTestServer :: IO ()
runTestServer =
let settings = setPort httpTestPort $ setHost "*6" defaultSettings
let settings = setPort (httpTestPort portsDef) $ setHost "*6" defaultSettings
in catchAny (runSettings settings serverApp) print

runTestServerTLS :: IO ()
runTestServerTLS =
let settings = setPort httpsTestPort $ setHost "*6" defaultSettings
let settings = setPort (httpsTestPort portsDef) $ setHost "*6" defaultSettings
tlsSettings' = tlsSettings "Test/certificate.pem" "Test/key.pem"
in catchAny (runTLS tlsSettings' settings serverApp) print

Expand Down
2 changes: 1 addition & 1 deletion Test/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ compareResult (Result secure sa ha ba) (Result _ sb hb bb) = do
testSingleUrl :: Bool -> HC.Request -> IO ()
testSingleUrl debug request = do
direct <- httpRun request
proxy <- httpRun $ HC.addProxy "localhost" testProxyPort request
proxy <- httpRun $ HC.addProxy "localhost" (proxyTestPort portsDef) request
when debug $ do
printResult direct
printResult proxy
Expand Down
2 changes: 1 addition & 1 deletion Test/testsuite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,5 +137,5 @@ withProxy settings = around_ $
defaultProxySettings :: Settings
defaultProxySettings = defaultSettings
{ proxyHost = "*6"
, proxyPort = testProxyPort
, proxyPort = proxyTestPort portsDef
}
1 change: 1 addition & 0 deletions http-proxy.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ Test-Suite testsuite
, http-conduit
, http-types
, hspec >= 2.1
, random >= 1.1
, resourcet
, wai
, wai-conduit
Expand Down
212 changes: 0 additions & 212 deletions test/proxy-test.hs

This file was deleted.

0 comments on commit af28de0

Please sign in to comment.