Skip to content

Commit

Permalink
Delete tests that refer to functions that have been removed
Browse files Browse the repository at this point in the history
  • Loading branch information
andrewthad committed Feb 26, 2024
1 parent 9f5a76f commit 11f4ee0
Showing 1 changed file with 0 additions and 203 deletions.
203 changes: 0 additions & 203 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,20 +39,11 @@ tests =
, testCase "B" testSocketsB
, testCase "C" testSocketsC
, testCase "D" testSocketsD
, testCase "E" testSocketsE
, testCase "F" testSocketsF
, testCase "G" testSocketsG
]
]
, testGroup
"linux"
[ testGroup
"sockets"
[ testCase "A" testLinuxSocketsA
, testCase "B" testLinuxSocketsB
, testCase "C" testLinuxSocketsC
]
, testGroup
"epoll"
[ testCase "A" testLinuxEpollA
]
Expand Down Expand Up @@ -120,200 +111,6 @@ testSocketsD = do
actual <- demand =<< S.receiveByteArray a 5 mempty
sample @=? actual

testSocketsE :: Assertion
testSocketsE = do
(a, b) <- demand =<< S.uninterruptibleSocketPair S.Unix S.datagram S.defaultProtocol
_ <- forkIO $ do
threadWaitWrite b
bytesSent <- demand =<< S.uninterruptibleSendByteArray b sample 0 5 mempty
when (bytesSent /= 5) (fail "testSocketsE: bytesSent was wrong")
threadWaitRead a
actual <- demand =<< S.uninterruptibleReceiveMessageA a 3 10 mempty
(5, E.fromList [E.fromList [1, 2, 3], E.fromList [4, 5]]) @=? actual

testSocketsF :: Assertion
testSocketsF = do
a <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand =<< S.uninterruptibleBind a (S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = 0, S.address = localhost}))
(expectedSzA, expectedSockAddrA) <- demand =<< S.uninterruptibleGetSocketName a 128
when (expectedSzA > 128) (fail "testSocketsF: bad socket address size for socket A")
portA <- case S.decodeSocketAddressInternet expectedSockAddrA of
Nothing -> fail "testSocketsF: not a sockaddr_in"
Just (S.SocketAddressInternet {S.port}) -> pure port
b <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand =<< S.uninterruptibleBind b (S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = 0, S.address = localhost}))
threadWaitWrite b
bytesSent <- demand =<< S.uninterruptibleSendToByteArray b sample 0 5 mempty (S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = portA, S.address = localhost}))
when (bytesSent /= 5) (fail "testSocketsF: bytesSent was wrong")
threadWaitRead a
actual <- demand =<< S.uninterruptibleReceiveMessageB a 5 2 mempty 128
(expectedSzB, expectedSockAddrB) <- demand =<< S.uninterruptibleGetSocketName b 128
when (expectedSzB > 128) (fail "testSocketsF: bad socket address size for socket B")
(expectedSzB, expectedSockAddrB, 5, E.fromList [sample]) @=? actual

testSocketsG :: Assertion
testSocketsG = do
(a, b) <- demand =<< S.uninterruptibleSocketPair S.Unix S.datagram S.defaultProtocol
_ <- forkIO $ do
bytesSent <-
demand
=<< S.writeVector
b
( E.fromList
[ E.fromList (enumFromTo (1 :: Word8) 6)
, E.fromList (enumFromTo (7 :: Word8) 9)
]
)
when (bytesSent /= 9) (fail "testSocketsG: bytesSent was wrong")
actual <- demand =<< S.receiveByteArray a 9 mempty
E.fromList (enumFromTo (1 :: Word8) 9) @=? actual

testLinuxSocketsA :: Assertion
testLinuxSocketsA = do
(a, b) <- demand =<< S.uninterruptibleSocketPair S.Unix S.datagram S.defaultProtocol
threadWaitWrite b
bytesSent1 <- demand =<< S.uninterruptibleSendByteArray b sample 0 5 mempty
threadWaitWrite b
bytesSent2 <- demand =<< S.uninterruptibleSendByteArray b sample2 0 4 mempty
when (bytesSent1 /= 5) (fail "testLinuxSocketsA: bytesSent1 was wrong")
when (bytesSent2 /= 4) (fail "testLinuxSocketsA: bytesSent2 was wrong")
threadWaitRead a
actual <- demand =<< L.uninterruptibleReceiveMultipleMessageA a 6 3 L.dontWait
(5, E.fromList [sample, sample2]) @=? actual

testLinuxSocketsB :: Assertion
testLinuxSocketsB = do
a <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand =<< S.uninterruptibleBind a (S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = 0, S.address = localhost}))
(expectedSzA, expectedSockAddrA) <-
demand
=<< S.uninterruptibleGetSocketName a 128
when
(expectedSzA /= S.sizeofSocketAddressInternet)
(fail "testLinixSocketsB: bad socket address size for socket A")
portA <- case S.decodeSocketAddressInternet expectedSockAddrA of
Nothing -> fail "testLinixSocketsB: not a sockaddr_in"
Just (S.SocketAddressInternet {S.port}) -> pure port
b <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand
=<< S.uninterruptibleBind
b
( S.encodeSocketAddressInternet $
S.SocketAddressInternet
{ S.port = 0
, S.address = localhost
}
)
threadWaitWrite b
bytesSent1 <-
demand
=<< S.uninterruptibleSendToByteArray
b
sample
0
5
mempty
(S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = portA, S.address = localhost}))
when
(bytesSent1 /= 5)
(fail "testLinixSocketsB: bytesSent1 was wrong")
threadWaitWrite b
bytesSent2 <-
demand
=<< S.uninterruptibleSendToByteArray
b
sample2
0
4
mempty
(S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = portA, S.address = localhost}))
when
(bytesSent2 /= 4)
(fail "testLinixSocketsB: bytesSent2 was wrong")
threadWaitRead a
actual <-
demand
=<< L.uninterruptibleReceiveMultipleMessageB a S.sizeofSocketAddressInternet 6 3 L.dontWait
(expectedSzB, S.SocketAddress sabytesB) <- demand =<< S.uninterruptibleGetSocketName b 128
when
(expectedSzB /= S.sizeofSocketAddressInternet)
(fail "testLinixSocketsB: bad socket address size for socket B")
(0, sabytesB <> sabytesB, 5, E.fromList [sample, sample2]) @=? actual

testLinuxSocketsC :: Assertion
testLinuxSocketsC = do
a <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand =<< S.uninterruptibleBind a (S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = 0, S.address = localhost}))
(expectedSzA, expectedSockAddrA) <-
demand
=<< S.uninterruptibleGetSocketName a 128
when
(expectedSzA /= S.sizeofSocketAddressInternet)
(fail "testLinuxSocketsC: bad socket address size for socket A")
portA <- case S.decodeSocketAddressInternet expectedSockAddrA of
Nothing -> fail "testLinuxSocketsC: not a sockaddr_in"
Just (S.SocketAddressInternet {S.port}) -> pure port
b <- demand =<< S.uninterruptibleSocket S.Internet S.datagram S.defaultProtocol
demand
=<< S.uninterruptibleBind
b
( S.encodeSocketAddressInternet $
S.SocketAddressInternet
{ S.port = 0
, S.address = localhost
}
)
threadWaitWrite b
bytesSent1 <-
demand
=<< S.uninterruptibleSendToByteArray
b
sample
0
5
mempty
(S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = portA, S.address = localhost}))
when
(bytesSent1 /= 5)
(fail "testLinuxSocketsC: bytesSent1 was wrong")
threadWaitWrite b
bytesSent2 <-
demand
=<< S.uninterruptibleSendToByteArray
b
sample2
0
4
mempty
(S.encodeSocketAddressInternet (S.SocketAddressInternet {S.port = portA, S.address = localhost}))
when
(bytesSent2 /= 4)
(fail "testLinuxSocketsC: bytesSent2 was wrong")
threadWaitRead a
lens <- PM.newPrimArray 2
addrs <- PM.newPrimArray 2
payloadsMut <- PM.unsafeNewUnliftedArray 2
PM.newByteArray 6 >>= PM.writeUnliftedArray payloadsMut 0
PM.newByteArray 6 >>= PM.writeUnliftedArray payloadsMut 1
msgCount <- demand =<< L.uninterruptibleReceiveMultipleMessageC a lens addrs payloadsMut 2 L.dontWait
when (msgCount /= 2) (fail "wrong number of messages")
addrsFrozen <- PM.unsafeFreezePrimArray addrs
payloads <- PM.unsafeFreezeUnliftedArray payloadsMut
len0 <- PM.readPrimArray lens 0
len1 <- PM.readPrimArray lens 1
buf0 <-
PM.unsafeFreezeByteArray
=<< PM.resizeMutableByteArray (PM.indexUnliftedArray payloads 0) (fromIntegral @CInt @Int len0)
buf1 <-
PM.unsafeFreezeByteArray
=<< PM.resizeMutableByteArray (PM.indexUnliftedArray payloads 1) (fromIntegral @CInt @Int len1)
(expectedSzB, S.SocketAddress sabytesB) <- demand =<< S.uninterruptibleGetSocketName b 128
when
(expectedSzB /= S.sizeofSocketAddressInternet)
(fail "testLinuxSocketsC: bad socket address size for socket B")
let primSockAddr = case sabytesB of PM.ByteArray x -> PM.PrimArray x
(primSockAddr <> primSockAddr, E.fromList [sample, sample2]) @=? (addrsFrozen, [buf0, buf1])

-- This test opens two datagram sockets and send a message from each
-- one to the other. Then it checks that epoll's event-triggered
-- interface correctly notifies the user about the read-readiness
Expand Down

0 comments on commit 11f4ee0

Please sign in to comment.