Skip to content

Commit 1872dc4

Browse files
Fix a few more hints and some mistakes made during merge.
1 parent 41b8bf9 commit 1872dc4

File tree

17 files changed

+30
-91
lines changed

17 files changed

+30
-91
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ setInitialDynFlags = do
120120
hPutStrLn stderr $ "Couldn't load cradle for libdir: " ++ show (err,dir,hieYaml,cradle)
121121
pure Nothing
122122
CradleNone -> do
123-
hPutStrLn stderr $ "Couldn't load cradle (CradleNone)"
123+
hPutStrLn stderr "Couldn't load cradle (CradleNone)"
124124
pure Nothing
125125
dynFlags <- mapM dynFlagsForPrinting libdir
126126
mapM_ setUnsafeGlobalDynFlags dynFlags

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -266,12 +266,12 @@ typeLocationsAtPoint hiedb lookupModule _ideOptions pos (HAR _ ast _ _ hieKind)
266266
HQualTy a b -> getTypes [a,b]
267267
HCastTy a -> getTypes [a]
268268
_ -> []
269-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
269+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
270270
HieFresh ->
271271
let ts = concat $ pointCommand ast pos getts
272272
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
273273
where ni = nodeInfo x
274-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
274+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
275275

276276
namesInType :: Type -> [Name]
277277
namesInType (TyVarTy n) = [Var.varName n]

hls-plugin-api/src/Ide/Types.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE GADTs #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
4-
{-# LANGUAGE TupleSections #-}
54
{-# LANGUAGE FlexibleContexts #-}
65
{-# LANGUAGE PolyKinds #-}
76
{-# LANGUAGE ViewPatterns #-}

plugins/default/src/Ide/Plugin/Pragmas.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,3 @@
1-
{-# LANGUAGE DeriveAnyClass #-}
2-
{-# LANGUAGE DeriveGeneric #-}
31
{-# LANGUAGE DuplicateRecordFields #-}
42
{-# LANGUAGE OverloadedStrings #-}
53
{-# LANGUAGE ViewPatterns #-}

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,6 @@
11
{-# LANGUAGE TypeApplications #-}
22
{-# LANGUAGE ViewPatterns #-}
33
{-# LANGUAGE LambdaCase #-}
4-
{-# LANGUAGE DeriveAnyClass #-}
5-
{-# LANGUAGE DeriveGeneric #-}
64
{-# LANGUAGE DuplicateRecordFields #-}
75
{-# LANGUAGE ExtendedDefaultRules #-}
86
{-# LANGUAGE FlexibleContexts #-}

plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
278278
in LSP.CodeAction "Apply all hints" (Just LSP.CodeActionQuickFix) Nothing Nothing Nothing Nothing (Just cmd)
279279

280280
applyOneActions :: [LSP.CodeAction]
281-
applyOneActions = catMaybes $ map mkHlintAction (filter validCommand diags)
281+
applyOneActions = mapMaybe mkHlintAction (filter validCommand diags)
282282

283283
-- |Some hints do not have an associated refactoring
284284
validCommand (LSP.Diagnostic _ _ (Just (InR code)) (Just "hlint") _ _ _) =

plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -147,14 +147,14 @@ extractImports ModSummary{ms_mod} topLevelBinds (Unfold thing)
147147
, names <- listify p fun_matches
148148
=
149149
[ AddImport {..}
150-
| name <- names,
151-
Just ideclNameString <-
152-
[moduleNameString . GHC.moduleName <$> nameModule_maybe name],
153-
let ideclSource = False,
150+
| let ideclSource = False,
151+
name <- names,
154152
let r = nameRdrName name,
155153
let ideclQualifiedBool = isQual r,
156154
let ideclAsString = moduleNameString . fst <$> isQual_maybe r,
157-
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r)
155+
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r),
156+
Just ideclNameString <-
157+
[moduleNameString . GHC.moduleName <$> nameModule_maybe name]
158158
]
159159
where
160160
p name = nameModule_maybe name /= Just ms_mod
@@ -179,8 +179,8 @@ provider state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) range ca)
179179
++ [ r
180180
| TyClGroup {group_tyclds} <- hs_tyclds,
181181
L l g <- group_tyclds,
182-
r <- suggestTypeRewrites uri ms_mod g,
183-
pos `isInsideSrcSpan` l
182+
pos `isInsideSrcSpan` l,
183+
r <- suggestTypeRewrites uri ms_mod g
184184

185185
]
186186

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -235,7 +235,7 @@ filterBindingType p tp dflags plId uri range jdg =
235235
g = jGoal jdg
236236
in fmap join $ for (unHypothesis hy) $ \hi ->
237237
let ty = unCType $ hi_type hi
238-
in if $ p (unCType g) ty
238+
in if p (unCType g) ty
239239
then tp (hi_name hi) ty dflags plId uri range jdg
240240
else pure []
241241

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/CodeGen.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE FlexibleContexts #-}
22
{-# LANGUAGE TupleSections #-}
33
{-# LANGUAGE TypeApplications #-}
4-
{-# LANGUAGE ViewPatterns #-}
54

65
module Ide.Plugin.Tactic.CodeGen
76
( module Ide.Plugin.Tactic.CodeGen
@@ -202,4 +201,3 @@ buildDataCon jdg dc tyapps = do
202201
pure
203202
. (rose (show dc) $ pure tr,)
204203
$ mkCon dc sgs
205-

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Judgements.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -273,7 +273,7 @@ introducingPat scrutinee dc ns jdg
273273
disallowing :: DisallowReason -> [OccName] -> Judgement' a -> Judgement' a
274274
disallowing reason (S.fromList -> ns) =
275275
field @"_jHypothesis" %~ (\z -> Hypothesis . flip fmap (unHypothesis z) $ \hi ->
276-
if $ hi_name hi `S.member` ns
276+
if hi_name hi `S.member` ns
277277
then overProvenance (DisallowedPrv reason) hi
278278
else hi
279279
)

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Naming.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -71,9 +71,9 @@ mkGoodName
7171
-> OccName
7272
mkGoodName in_scope t =
7373
let tn = mkTyName t
74-
in if $ mkVarOcc $ case S.member (mkVarOcc tn) in_scope
75-
then tn ++ show (length in_scope)
76-
else tn
74+
in mkVarOcc $ if S.member (mkVarOcc tn) in_scope
75+
then tn ++ show (length in_scope)
76+
else tn
7777

7878

7979
------------------------------------------------------------------------------

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Simplify.hs

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,7 @@ pattern Lambda pats body <-
4141
-- | Simlify an expression.
4242
simplify :: LHsExpr GhcPs -> LHsExpr GhcPs
4343
simplify
44-
= head
45-
. drop 3 -- Do three passes; this should be good enough for the limited
44+
= (!! 3) -- Do three passes; this should be good enough for the limited
4645
-- amount of gas we give to auto
4746
. iterate (everywhere $ foldEndo
4847
[ simplifyEtaReduce
@@ -78,7 +77,7 @@ simplifyEtaReduce = mkT $ \case
7877
(HsVar _ (L _ a)) | pat == a ->
7978
var "id"
8079
Lambda
81-
(unsnoc -> Just (pats, (VarPat _ (L _ pat))))
80+
(unsnoc -> Just (pats, VarPat _ (L _ pat)))
8281
(HsApp _ (L _ f) (L _ (HsVar _ (L _ a))))
8382
| pat == a
8483
-- We can only perform this simplifiation if @pat@ is otherwise unused.
@@ -93,8 +92,8 @@ simplifyEtaReduce = mkT $ \case
9392
simplifyCompose :: GenericT
9493
simplifyCompose = mkT $ \case
9594
Lambda
96-
(unsnoc -> Just (pats, (VarPat _ (L _ pat))))
97-
(unroll -> (fs@(_:_), (HsVar _ (L _ a))))
95+
(unsnoc -> Just (pats, VarPat _ (L _ pat)))
96+
(unroll -> (fs@(_:_), HsVar _ (L _ a)))
9897
| pat == a
9998
-- We can only perform this simplifiation if @pat@ is otherwise unused.
10099
, not (containsHsVar pat fs) ->
@@ -119,4 +118,3 @@ unroll (HsApp _ (L _ f) (L _ a)) =
119118
let (fs, r) = unroll a
120119
in (f : fs, r)
121120
unroll x = ([], x)
122-

plugins/hls-tactics-plugin/test/AutoTupleSpec.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
module AutoTupleSpec where
44

55
import Data.Either (isRight)
6-
import qualified Data.Map as M
76
import Ide.Plugin.Tactic.Debug
87
import Ide.Plugin.Tactic.Judgements (mkFirstJudgement)
98
import Ide.Plugin.Tactic.Machinery
@@ -48,11 +47,8 @@ spec = describe "auto for tuple" $ do
4847
(auto' $ n * 2) `shouldSatisfy` isRight
4948

5049

51-
{- HLINT ignore randomGroups "Redundant <$>"-}
52-
5350
randomGroups :: [a] -> Gen [[a]]
5451
randomGroups [] = pure []
5552
randomGroups as = do
5653
n <- choose (1, length as)
57-
(:) <$> pure (take n as)
58-
<*> randomGroups (drop n as)
54+
(take n as:) <$> randomGroups (drop n as)

src/Ide/Main.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,10 +5,7 @@
55
{-# LANGUAGE OverloadedStrings #-}
66
{-# LANGUAGE RecordWildCards #-}
77
{-# LANGUAGE ScopedTypeVariables #-}
8-
{-# LANGUAGE TupleSections #-}
98
{-# LANGUAGE TypeFamilies #-}
10-
{-# LANGUAGE ViewPatterns #-}
11-
{-# LANGUAGE NamedFieldPuns #-}
129

1310
module Ide.Main(defaultMain, runLspMode) where
1411

stack.yaml

Lines changed: 6 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
resolver: lts-14.27 # Last 8.6.5
1+
resolver: nightly-2020-12-09
22

33
packages:
44
- .
@@ -18,79 +18,37 @@ packages:
1818
ghc-options:
1919
"$everything": -haddock
2020

21-
22-
2321
extra-deps:
24-
- aeson-1.5.2.0
2522
- apply-refact-0.9.0.0
26-
- ansi-terminal-0.10.3
27-
- base-compat-0.10.5
2823
- brittany-0.13.1.0
29-
- butcher-1.3.3.1
3024
- Cabal-3.0.2.0
31-
- cabal-plan-0.6.2.0
3225
- clock-0.7.2
33-
- Diff-0.4.0
26+
- data-tree-print-0.1.0.2@rev:2
3427
- floskell-0.10.4
3528
- fourmolu-0.3.0.0
36-
- fuzzy-0.1.0.0
37-
- ghc-check-0.5.0.1
38-
- ghc-events-0.13.0
3929
- ghc-exactprint-0.6.3.4
4030
- ghc-lib-8.10.3.20201220
4131
- ghc-lib-parser-8.10.3.20201220
42-
- ghc-lib-parser-ex-8.10.0.17
43-
- ghc-source-gen-0.4.0.0
44-
- ghc-trace-events-0.1.2.1
45-
- haddock-api-2.22.0@rev:1
46-
- haddock-library-1.8.0
47-
- hashable-1.3.0.0
32+
- lsp-1.1.0.0
33+
- lsp-types-1.1.0.0
34+
- lsp-test-0.13.0.0
4835
- heapsize-0.3.0
49-
- hie-bios-0.7.1
50-
- hlint-3.2.3
51-
- HsYAML-0.2.1.0@rev:1
52-
- HsYAML-aeson-0.2.0.0@rev:2
5336
- implicit-hie-cradle-0.3.0.2
5437
- implicit-hie-0.1.2.5
55-
- indexed-profunctors-0.1
56-
- lens-4.18
57-
- megaparsec-9.0.1
5838
- monad-dijkstra-0.1.1.2
59-
- opentelemetry-0.6.1
60-
- opentelemetry-extra-0.6.1
61-
- optics-core-0.2
62-
- optparse-applicative-0.15.1.0
63-
- ormolu-0.1.4.1
64-
- parser-combinators-1.2.1
65-
- primitive-0.7.1.0
6639
- refinery-0.3.0.0
67-
- regex-base-0.94.0.0
68-
- regex-pcre-builtin-0.95.1.1.8.43
69-
- regex-tdfa-1.3.1.0
7040
- retrie-0.1.1.1
71-
- semialign-1.1
7241
- stylish-haskell-0.12.2.0
73-
- tasty-rerun-1.1.17
42+
- semigroups-0.18.5
7443
- temporary-1.2.1.1
75-
- these-1.1.1.1
76-
- type-equality-1
77-
- topograph-1
78-
- uniplate-1.6.13
79-
- with-utf8-1.0.2.1@sha256:95c02fffa643ddbeb092359802a512007c3e644cd509809f4716ad54592c437b,3057
80-
- th-env-0.1.0.2@sha256:d8f1f37f42a8f1a22404d7d0579528af18f5dac7232cca6bdbd5117c115a0ad5,1370
8144
- bytestring-encoding-0.1.0.0@sha256:460b49779fbf0112e8e2f1753c1ed9131eb18827600c298f4d6bb51c4e8c1c0d,1727
8245
- hiedb-0.3.0.1
83-
- extra-1.7.9@sha256:f1dec740f0f2025790c540732bfd52c556ec55bde4f5dfd7cf18e22bd44ff3d0,2683
84-
- lsp-1.1.0.0
85-
- lsp-types-1.1.0.0
86-
- lsp-test-0.13.0.0
8746
- dependent-map-0.4.0.0@sha256:ca2b131046f4340a1c35d138c5a003fe4a5be96b14efc26291ed35fd08c62221,1657
8847
- dependent-sum-0.7.1.0@sha256:5599aa89637db434431b1dd3fa7c34bc3d565ee44f0519bfbc877be1927c2531,2068
8948
- dependent-sum-template-0.1.0.3@sha256:0bbbacdfbd3abf2a15aaf0cf2c27e5bdd159b519441fec39e1e6f2f54424adde,1682
9049
- constraints-extras-0.3.0.2@sha256:013b8d0392582c6ca068e226718a4fe8be8e22321cc0634f6115505bf377ad26,1853
9150
- some-1.0.1@sha256:26e5bab7276f48b25ea8660d3fd1166c0f20fd497dac879a40f408e23211f93e,2055
9251
- unliftio-core-0.2.0.1@sha256:9b3e44ea9aacacbfc35b3b54015af450091916ac3618a41868ebf6546977659a,1082
93-
- resourcet-1.2.3
9452

9553
configure-options:
9654
ghcide:
@@ -106,8 +64,6 @@ flags:
10664
retrie:
10765
BuildExecutable: false
10866

109-
# allow-newer: true
110-
11167
nix:
11268
packages: [icu libcxx zlib]
11369

test/functional/Progress.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
{-# LANGUAGE OverloadedStrings #-}
44
{-# LANGUAGE DuplicateRecordFields #-}
55
{-# LANGUAGE DataKinds #-}
6-
{-# LANGUAGE TypeOperators #-}
76
{-# LANGUAGE GADTs #-}
87

98
module Progress (tests) where
@@ -106,9 +105,9 @@ expectProgressReports xs = expectProgressReports' [] xs
106105
EndM msg -> do
107106
liftIO $ token msg `expectElem` tokens
108107
expectProgressReports' (delete (token msg) tokens) expectedTitles
109-
title msg = msg ^. L.value ^. L.title
108+
title msg = msg ^. L.value . L.title
110109
token msg = msg ^. L.token
111-
create = CreateM . view L.params <$> (message SWindowWorkDoneProgressCreate)
110+
create = CreateM . view L.params <$> message SWindowWorkDoneProgressCreate
112111
begin = BeginM <$> satisfyMaybe (\case
113112
FromServerMess SProgress (NotificationMessage _ _ (ProgressParams t (Begin x))) -> Just (ProgressParams t x)
114113
_ -> Nothing)

test/functional/Reference.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ tests = testGroup "references" [
2525
, mkRange 4 14 4 17
2626
, mkRange 4 0 4 3
2727
, mkRange 2 6 2 9
28-
] `isInfixOf` (coerce refs) @? "Contains references"
28+
] `isInfixOf` coerce refs @? "Contains references"
2929
-- TODO: Respect withDeclaration parameter
3030
-- ignoreTestBecause "Broken" $ testCase "works without definitions" $ runSession hlsCommand fullCaps "test/testdata" $ do
3131
-- doc <- openDoc "References.hs" "haskell"

0 commit comments

Comments
 (0)