Skip to content

Commit 9b76041

Browse files
committed
Fix doubtless HLint issues in Federator
1 parent 1e6843a commit 9b76041

File tree

9 files changed

+31
-25
lines changed

9 files changed

+31
-25
lines changed

services/federator/src/Federator/ExternalServer.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -107,14 +107,14 @@ parseRequestData req = do
107107
when (Wai.requestMethod req /= HTTP.methodPost) $
108108
throw InvalidRoute
109109
-- No query parameters are allowed
110-
when (not . BS.null . Wai.rawQueryString $ req) $
110+
unless (BS.null . Wai.rawQueryString $ req) $
111111
throw InvalidRoute
112112
-- check that the path has the expected form
113113
(componentSeg, rpcPath) <- case Wai.pathInfo req of
114114
["federation", comp, rpc] -> pure (comp, rpc)
115115
_ -> throw InvalidRoute
116116

117-
when (not (Text.all isAllowedRPCChar rpcPath)) $
117+
unless (Text.all isAllowedRPCChar rpcPath) $
118118
throw InvalidRoute
119119

120120
when (Text.null rpcPath) $

services/federator/src/Federator/InternalServer.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ parseRequestData req = do
9090
when (Wai.requestMethod req /= HTTP.methodPost) $
9191
throw InvalidRoute
9292
-- No query parameters are allowed
93-
when (not . BS.null . Wai.rawQueryString $ req) $
93+
unless (BS.null . Wai.rawQueryString $ req) $
9494
throw InvalidRoute
9595
-- check that the path has the expected form
9696
(domain, componentSeg, rpcPath) <- case Wai.pathInfo req of

services/federator/src/Federator/MockServer.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ import Wire.API.Federation.Domain
5353

5454
-- | Thrown in IO by mock federator if the server could not be started after 10
5555
-- seconds.
56-
data MockTimeout = MockTimeout Warp.Port
56+
newtype MockTimeout = MockTimeout Warp.Port
5757
deriving (Eq, Show, Typeable)
5858

5959
instance Exception MockTimeout
@@ -159,7 +159,7 @@ withTempMockFederator headers resp action = do
159159
frBody = rdBody
160160
}
161161
)
162-
embed @IO $ modifyIORef remoteCalls $ (<> [fedRequest])
162+
embed @IO $ modifyIORef remoteCalls (<> [fedRequest])
163163
body <-
164164
fromException @MockException
165165
. handle (throw . handleException)

services/federator/src/Federator/Monitor/Internal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ data WatchedPath
7272
deriving stock (Eq, Ord, Show, Generic)
7373
deriving (Arbitrary) via (GenericUniform WatchedPath)
7474

75-
mergePaths :: [WatchedPath] -> (Set WatchedPath)
75+
mergePaths :: [WatchedPath] -> Set WatchedPath
7676
mergePaths = Set.fromList . merge . sort
7777
where
7878
merge [] = []

services/federator/test/integration/Test/Federator/IngressSpec.hs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -62,13 +62,14 @@ spec env = do
6262
resp <-
6363
runTestSem
6464
. assertNoError @RemoteError
65-
$ inwardBrigCallViaIngress "get-user-by-handle" $
65+
$ inwardBrigCallViaIngress
66+
"get-user-by-handle"
6667
(Aeson.fromEncoding (Aeson.toEncoding hdl))
6768
liftIO $ do
6869
bdy <- streamingResponseStrictBody resp
6970
let actualProfile = Aeson.decode (toLazyByteString bdy)
7071
responseStatusCode resp `shouldBe` HTTP.status200
71-
actualProfile `shouldBe` (Just expectedProfile)
72+
actualProfile `shouldBe` Just expectedProfile
7273

7374
-- @SF.Federation @TSFI.RESTfulAPI @S2 @S3 @S7
7475
--
@@ -96,7 +97,9 @@ spec env = do
9697
r <-
9798
runTestSem
9899
. runError @RemoteError
99-
$ inwardBrigCallViaIngressWithSettings tlsSettings "get-user-by-handle" $
100+
$ inwardBrigCallViaIngressWithSettings
101+
tlsSettings
102+
"get-user-by-handle"
100103
(Aeson.fromEncoding (Aeson.toEncoding hdl))
101104
liftIO $ case r of
102105
Right _ -> expectationFailure "Expected client certificate error, got response"

services/federator/test/unit/Test/Federator/Client.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
--
1515
-- You should have received a copy of the GNU Affero General Public License along
1616
-- with this program. If not, see <https://www.gnu.org/licenses/>.
17+
{-# LANGUAGE LambdaCase #-}
1718

1819
module Test.Federator.Client (tests) where
1920

@@ -131,13 +132,12 @@ testClientStreaming = withInfiniteMockServer $ \port -> do
131132
ceFederator = Endpoint "127.0.0.1" (fromIntegral port)
132133
}
133134
let c = clientIn (Proxy @StreamingAPI) (Proxy @(FederatorClient 'Brig))
134-
runCodensity (runFederatorClientToCodensity env c) $ \eout ->
135-
case eout of
136-
Left err -> assertFailure $ "Unexpected error: " <> displayException err
137-
Right out -> do
138-
let expected = mconcat (replicate 500 "Hello")
139-
actual <- takeSourceT (fromIntegral (LBS.length expected)) (fmap Text.encodeUtf8 out)
140-
actual @?= expected
135+
runCodensity (runFederatorClientToCodensity env c) $ \case
136+
Left err -> assertFailure $ "Unexpected error: " <> displayException err
137+
Right out -> do
138+
let expected = mconcat (replicate 500 "Hello")
139+
actual <- takeSourceT (fromIntegral (LBS.length expected)) (fmap Text.encodeUtf8 out)
140+
actual @?= expected
141141

142142
testClientFailure :: IO ()
143143
testClientFailure = do
@@ -232,7 +232,7 @@ withInfiniteMockServer k = bracket (startMockServer Nothing app) fst (k . snd)
232232
app _ respond = respond $
233233
Wai.responseStream HTTP.ok200 mempty $ \write flush ->
234234
let go n = do
235-
when (n == 0) $ flush
235+
when (n == 0) flush
236236
write (byteString "Hello\n") *> go (if n == 0 then 100 else n - 1)
237237
in go (1000 :: Int)
238238

services/federator/test/unit/Test/Federator/InternalServer.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,8 @@ tests :: TestTree
4949
tests =
5050
testGroup
5151
"Federate"
52-
[ testGroup "with remote" $
52+
[ testGroup
53+
"with remote"
5354
[ federatedRequestSuccess,
5455
federatedRequestFailureAllowList
5556
]

services/federator/test/unit/Test/Federator/Util.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,10 +62,9 @@ testRequest tr = do
6262
pure . flip Wai.setPath (trPath tr) $
6363
Wai.defaultRequest
6464
{ Wai.requestMethod = trMethod tr,
65-
Wai.requestBody = atomicModifyIORef refChunks $ \bss ->
66-
case bss of
67-
[] -> ([], mempty)
68-
x : y -> (y, x),
65+
Wai.requestBody = atomicModifyIORef refChunks $ \case
66+
[] -> ([], mempty)
67+
x : y -> (y, x),
6968
Wai.requestHeaders =
7069
[("X-SSL-Certificate", HTTP.urlEncode True h) | h <- toList (trCertificateHeader tr)]
7170
<> [(originDomainHeaderName, h) | h <- toList (trDomainHeader tr)]

services/federator/test/unit/Test/Federator/Validation.hs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -60,12 +60,15 @@ mockDiscoveryFailure = Polysemy.interpret $ \case
6060

6161
tests :: TestTree
6262
tests =
63-
testGroup "Validation" $
64-
[ testGroup "federateWith" $
63+
testGroup
64+
"Validation"
65+
[ testGroup
66+
"federateWith"
6567
[ federateWithAllowListSuccess,
6668
federateWithAllowListFail
6769
],
68-
testGroup "validateDomain" $
70+
testGroup
71+
"validateDomain"
6972
[ validateDomainAllowListFailSemantic,
7073
validateDomainAllowListFail,
7174
validateDomainAllowListSuccess,

0 commit comments

Comments
 (0)