{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Snap.Internal.Http.Server.Address.Tests (tests) where ------------------------------------------------------------------------------ import Network.Socket (Family (AF_INET, AF_INET6), SockAddr (SockAddrInet, SockAddrInet6, SockAddrUnix), iN6ADDR_ANY, iNADDR_ANY) #if MIN_VERSION_network(2,6,0) import Network.Socket (SockAddr (SockAddrCan)) #endif ------------------------------------------------------------------------------ import Test.Framework (Test) import Test.Framework.Providers.HUnit (testCase) import Test.HUnit (assertEqual) ------------------------------------------------------------------------------ import Snap.Internal.Http.Server.Address (AddressNotSupportedException (..), getAddress, getAddressImpl, getHostAddrImpl, getSockAddr, getSockAddrImpl) import Snap.Test.Common (coverShowInstance, coverTypeableInstance, expectException) ------------------------------------------------------------------------------ tests :: [Test] tests = [ testGetNameInfoFails , testGetAddressUnix , testGetAddressCan , testGetAddressIPv6 , testGetSockAddr , testTrivials ] ------------------------------------------------------------------------------ testGetNameInfoFails :: Test testGetNameInfoFails = testCase "address/getNameInfo-fails" $ do x <- getHostAddrImpl (\_ _ _ _ -> return (Nothing, Nothing)) undefined assertEqual "when getNameInfo fails, getHostAddr should return empty" "" x ------------------------------------------------------------------------------ testGetAddressUnix :: Test testGetAddressUnix = testCase "address/getAddress-unix-socket" $ do (port, addr) <- getAddress $ SockAddrUnix "/foo/bar" assertEqual "unix port" (-1) port assertEqual "unix address" "unix:/foo/bar" addr ------------------------------------------------------------------------------ testGetAddressCan :: Test testGetAddressCan = testCase "address/getAddress-can" $ do #if MIN_VERSION_network(2,6,0) expectException $ getAddress $ SockAddrCan 0 #else return () #endif ------------------------------------------------------------------------------ testGetAddressIPv6 :: Test testGetAddressIPv6 = testCase "address/getAddress-IPv6" $ do let x = SockAddrInet6 10 undefined undefined undefined (y, _) <- getAddressImpl (const $ return "") x assertEqual "ipv6 port" 10 y ------------------------------------------------------------------------------ testGetSockAddr :: Test testGetSockAddr = testCase "address/getSockAddr" $ do (f1, a1) <- getSockAddr 10 "*" assertEqual "" f1 AF_INET assertEqual "" a1 $ SockAddrInet 10 iNADDR_ANY (f2, a2) <- getSockAddr 10 "::" assertEqual "" f2 AF_INET6 assertEqual "" a2 $ SockAddrInet6 10 0 iN6ADDR_ANY 0 expectException $ getSockAddrImpl (\_ _ _ -> return []) 10 "foo" ------------------------------------------------------------------------------ testTrivials :: Test testTrivials = testCase "address/trivials" $ do coverTypeableInstance (undefined :: AddressNotSupportedException) coverShowInstance (AddressNotSupportedException "ok")