Skip to content

Commit e084f13

Browse files
authored
Added linting scripts. (#2663)
1 parent 21805c2 commit e084f13

File tree

44 files changed

+157
-98
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

44 files changed

+157
-98
lines changed

.hlint.yaml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,10 @@
88
# Left for the programmer to decide. See discussion at https://github.com/wireapp/wire-server/pull/2382#discussion_r871194424
99
- ignore: { name: Avoid lambda }
1010
- ignore: { name: Avoid lambda using `infix` }
11-
11+
- ignore: { name: Eta reduce }
1212
- ignore: { name: Use section }
13+
- ignore: { name: Use underscore }
14+
1315
# custom rules:
1416
- hint: { lhs: (() <$), rhs: void }
1517
- hint: { lhs: return, rhs: pure }

Makefile

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,22 @@ cabal-fmt:
117117
ghcid:
118118
ghcid -l=hlint --command "cabal repl $(target)"
119119

120+
.PHONY: hlint-check-all
121+
hlint-check-all:
122+
./tools/hlint.sh -f all -m check
123+
124+
.PHONY: hlint-inplace-all
125+
hlint-inplace-all:
126+
./tools/hlint.sh -f all -m inplace
127+
128+
.PHONY: hlint-check
129+
hlint-check:
130+
./tools/hlint.sh -f changeset -m check
131+
132+
.PHONY: hlint-inplace
133+
hlint-inplace:
134+
./tools/hlint.sh -f changeset -m inplace
135+
120136
# reset db using cabal
121137
.PHONY: db-reset-package
122138
db-reset-package: c

libs/api-bot/src/Network/Wire/Bot/Assert.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE LambdaCase #-}
2-
{-# LANGUAGE OverloadedStrings #-}
32

43
-- This file is part of the Wire Server implementation.
54
--

libs/api-bot/src/Network/Wire/Bot/Cache.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE LambdaCase #-}
12
{-# LANGUAGE OverloadedStrings #-}
23

34
-- This file is part of the Wire Server implementation.
@@ -64,13 +65,12 @@ empty :: IO Cache
6465
empty = Cache <$> newIORef []
6566

6667
get :: (MonadIO m, HasCallStack) => Cache -> m CachedUser
67-
get c = liftIO . atomicModifyIORef (cache c) $ \u ->
68-
case u of
69-
[] ->
70-
error
71-
"Cache.get: an account was requested from the cache, \
72-
\but the cache of available user accounts is empty"
73-
(x : xs) -> (xs, x)
68+
get c = liftIO . atomicModifyIORef (cache c) $ \case
69+
[] ->
70+
error
71+
"Cache.get: an account was requested from the cache, \
72+
\but the cache of available user accounts is empty"
73+
(x : xs) -> (xs, x)
7474

7575
put :: MonadIO m => Cache -> CachedUser -> m ()
7676
put c a = liftIO . atomicModifyIORef (cache c) $ \u -> (a : u, ())

libs/api-client/src/Network/Wire/Client/Monad.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
22
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3-
{-# LANGUAGE OverloadedStrings #-}
43

54
-- This file is part of the Wire Server implementation.
65
--

libs/bilge/src/Bilge/Request.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -156,7 +156,7 @@ expectStatus property r = r {Rq.checkResponse = check}
156156
| property (HTTP.statusCode (Rq.responseStatus res)) = pure ()
157157
| otherwise = do
158158
some <- Lazy.toStrict <$> brReadSome (Rq.responseBody res) 1024
159-
throwHttp $ Rq.StatusCodeException (() <$ res) some
159+
throwHttp $ Rq.StatusCodeException (void res) some
160160

161161
checkStatus :: (Status -> ResponseHeaders -> CookieJar -> Maybe SomeException) -> Request -> Request
162162
checkStatus f r = r {Rq.checkResponse = check}

libs/brig-types/src/Brig/Types/Common.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ isValidPhonePrefix = isRight . parseOnly e164Prefix
8080
-- | get all valid prefixes of a phone number or phone number prefix
8181
-- e.g. from +123456789 get prefixes ["+1", "+12", "+123", ..., "+123456789" ]
8282
allPrefixes :: Text -> [PhonePrefix]
83-
allPrefixes t = catMaybes $ parsePhonePrefix <$> Text.inits t
83+
allPrefixes t = mapMaybe parsePhonePrefix (Text.inits t)
8484

8585
instance FromJSON PhonePrefix where
8686
parseJSON = withText "PhonePrefix" $ \s ->

libs/extended/src/Servant/API/Extended.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,18 +94,18 @@ instance
9494
requestHeaders request
9595
case canHandleCTypeH (Proxy :: Proxy list) (cs contentTypeH) :: Maybe (BL.ByteString -> Either String a) of
9696
Nothing -> delayedFail err415
97-
Just f -> return f
97+
Just f -> pure f
9898
-- Body check, we get a body parsing functions as the first argument.
9999
bodyCheck ::
100100
(BL.ByteString -> Either String a) ->
101101
DelayedIO (If (FoldLenient mods) (Either ServerError a) a)
102102
bodyCheck f = withRequest $ \request -> do
103103
mrqbody <- fmapL (makeCustomError @tag @a) . f <$> liftIO (lazyRequestBody request)
104104
case sbool :: SBool (FoldLenient mods) of
105-
STrue -> return mrqbody
105+
STrue -> pure mrqbody
106106
SFalse -> case mrqbody of
107107
Left e -> delayedFailFatal e
108-
Right v -> return v
108+
Right v -> pure v
109109

110110
instance
111111
HasSwagger (ReqBody' '[Required, Strict] cts a :> api) =>

libs/hscim/src/Web/Scim/Client.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ type HasScimClient tag =
7575
)
7676

7777
scimClients :: HasScimClient tag => ClientEnv -> Site tag (AsClientT IO)
78-
scimClients env = genericClientHoist $ \x -> runClientM x env >>= either throwIO return
78+
scimClients env = genericClientHoist $ \x -> runClientM x env >>= either throwIO pure
7979

8080
-- config
8181

@@ -130,7 +130,7 @@ postUser ::
130130
HasScimClient tag =>
131131
ClientEnv ->
132132
Maybe (AuthData tag) ->
133-
(User tag) ->
133+
User tag ->
134134
IO (StoredUser tag)
135135
postUser env tok = case users (scimClients env) tok of ((_ :<|> (_ :<|> r)) :<|> (_ :<|> (_ :<|> _))) -> r
136136

@@ -139,7 +139,7 @@ putUser ::
139139
ClientEnv ->
140140
Maybe (AuthData tag) ->
141141
UserId tag ->
142-
(User tag) ->
142+
User tag ->
143143
IO (StoredUser tag)
144144
putUser env tok = case users (scimClients env) tok of ((_ :<|> (_ :<|> _)) :<|> (r :<|> (_ :<|> _))) -> r
145145

libs/hscim/src/Web/Scim/ContentType.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,9 @@
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+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
18+
19+
{-# HLINT ignore "Use list literal" #-}
1720

1821
-- | SCIM defines its own content type (application/scim+json). It's
1922
-- intended to be used for all requests and responses; see the first

0 commit comments

Comments
 (0)