Skip to content

Commit 68c4b8a

Browse files
committed
more cleanup
1 parent f6b51d0 commit 68c4b8a

File tree

2 files changed

+20
-10
lines changed

2 files changed

+20
-10
lines changed

integration/test/Test/Demo.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,12 @@
11
{-# LANGUAGE FlexibleContexts #-}
22

3-
-- | This module is meant to show how the integration can be used
3+
-- | This module is meant to show how TestLib can be used
44
module Test.Demo where
55

66
import qualified API
77
import Imports
88
import TestLib.Prelude
99

10-
-- | Cannot delete a legalhold client
1110
testCantDeleteLHClient :: HasCallStack => App ()
1211
testCantDeleteLHClient = do
1312
user <- randomUser def
@@ -68,5 +67,5 @@ testWebSockets = do
6867
client <- bindResponse (API.addClient user def) $ \resp -> do
6968
resp.status `shouldMatchInt` 201
7069
resp.json
71-
n <- awaitMatch 3 (\n -> payload n %. "type" `isEqual` "user.client-add") ws
72-
payload n %. "client.id" `shouldMatch` (client %. "id")
70+
n <- awaitMatch 3 (\n -> nPayload n %. "type" `isEqual` "user.client-add") ws
71+
nPayload n %. "client.id" `shouldMatch` (client %. "id")

integration/test/TestLib/Cannon.hs

Lines changed: 17 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE ScopedTypeVariables #-}
3-
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
43

54
-- This file is part of the Wire Server implementation.
65
--
@@ -19,14 +18,27 @@
1918
-- You should have received a copy of the GNU Affero General Public License along
2019
-- with this program. If not, see <https://www.gnu.org/licenses/>.
2120

22-
module TestLib.Cannon where
21+
module TestLib.Cannon
22+
( WebSocket (..),
23+
WSConnect (..),
24+
ToWSConnect (..),
25+
withWebSocket,
26+
withWebSockets,
27+
awaitNMatchesResult,
28+
awaitNMatches,
29+
awaitMatch,
30+
nPayload,
31+
printAwaitResult,
32+
)
33+
where
2334

2435
import Control.Concurrent.Async
2536
import Control.Exception (throwIO)
2637
import Control.Monad.Catch hiding (bracket)
2738
import qualified Control.Monad.Catch as Catch
2839
import Data.Aeson (Value (..), decodeStrict')
29-
import Data.ByteString.Conversion (fromByteString, toByteString')
40+
import Data.ByteString.Conversion (fromByteString)
41+
import Data.ByteString.Conversion.To
3042
import Imports
3143
import qualified Network.HTTP.Client as Http
3244
import qualified Network.WebSockets as WS
@@ -112,7 +124,6 @@ run wsConnect app = do
112124
Nothing -> ""
113125
Just client -> fromJust . fromByteString $ Http.queryString (Http.setQueryString [("client", Just (toByteString' client))] Http.defaultRequest)
114126
)
115-
116127
caHdrs =
117128
[ ("Z-User", toByteString' (wsConnect.user)),
118129
("Z-Connection", toByteString' connId)
@@ -272,7 +283,7 @@ awaitMatch ::
272283
App Value
273284
awaitMatch tSecs checkMatch ws = head <$> awaitNMatches 1 tSecs checkMatch ws
274285

275-
payload :: ProducesJSON a => a -> App Value
276-
payload event = do
286+
nPayload :: ProducesJSON a => a -> App Value
287+
nPayload event = do
277288
payloads <- event %. "payload" & asList
278289
assertOne payloads

0 commit comments

Comments
 (0)