Skip to content

Commit 9f4d673

Browse files
jetjinsermichaelpjmergify[bot]
authored
Support Inlay hints for record wildcards (#4351)
* Provide explicit import in inlay hints * Filter explict imports inlay hints by visible range * Update lsp dep by source-repository-package to writing test before new release of haskell/lsp. * Add test for hls-explicit-imports-plugin inlay hints * Comment inlay hints start position * Use `isSubrangeOf` to test if the range is visible * Remove inlayHintsResolveProvider placeholder for now * Use explicit InlayHintKind_Type * Revert "Update lsp dep by source-repository-package" This reverts commit 245049a. * Combine InlayHints by sconcat them and remove `instance PluginRequestMethod Method_InlayHintResolve` since have not decide how to combine. * compress multiple spaces in abbr import tilte * update test to match inlay hints kind * rename squashedAbbreviateImportTitle to abbreviateImportTitleWithoutModule * Request inlay hints with testEdits * ExplicitImports fallback to codelens when inlay hints not support * fix explicitImports inlayHints test * simplify isInlayHintsSupported * comment fallback * empty list instead of null codeLens * clearify name `paddingLeft` * fix clientCapabilities * add test for inlay hints without its client caps * use codeActionNoInlayHintsCaps to avoid error * simplify isInlayHintSupported * comment about paddingLeft * use null as inlay hints kind * add tooltip for explicit imports inlay hints to improve UX * chore comments * refactor * comment InL [] to indicate no info * ignore refine inlay hints * add plcInlayHintsOn config * update func-test * keep order to make Parser works * always provide refine in code lens * init explicit record fields inlay hints * dotdot location in label part * update test for dotdot location in label part * get(Type)Definition with its Identifier * add flipped filterByRange * filter label with name * update test * re-generate schema * fix explict-record-fields plugin in GHC 910 * fix use correct currentPosition * comment * rename flippedFilterByRange to elementsInRange * refactor: lift * refactor: break pointfree * refactor * recover accidentally deleted macros --------- Co-authored-by: Michael Peyton Jones <me@michaelpj.com> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent cbc0cd6 commit 9f4d673

File tree

15 files changed

+547
-180
lines changed

15 files changed

+547
-180
lines changed

ghcide/src/Development/IDE/Core/Actions.hs

+36-33
Original file line numberDiff line numberDiff line change
@@ -66,56 +66,59 @@ getAtPoint file pos = runMaybeT $ do
6666
!pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
6767
MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<<)) <$> AtPoint.atPoint opts hf dkMap env pos'
6868

69-
-- | For each Location, determine if we have the PositionMapping
70-
-- for the correct file. If not, get the correct position mapping
71-
-- and then apply the position mapping to the location.
72-
toCurrentLocations
69+
-- | Converts locations in the source code to their current positions,
70+
-- taking into account changes that may have occurred due to edits.
71+
toCurrentLocation
7372
:: PositionMapping
7473
-> NormalizedFilePath
75-
-> [Location]
76-
-> IdeAction [Location]
77-
toCurrentLocations mapping file = mapMaybeM go
74+
-> Location
75+
-> IdeAction (Maybe Location)
76+
toCurrentLocation mapping file (Location uri range) =
77+
-- The Location we are going to might be in a different
78+
-- file than the one we are calling gotoDefinition from.
79+
-- So we check that the location file matches the file
80+
-- we are in.
81+
if nUri == normalizedFilePathToUri file
82+
-- The Location matches the file, so use the PositionMapping
83+
-- we have.
84+
then pure $ Location uri <$> toCurrentRange mapping range
85+
-- The Location does not match the file, so get the correct
86+
-- PositionMapping and use that instead.
87+
else do
88+
otherLocationMapping <- fmap (fmap snd) $ runMaybeT $ do
89+
otherLocationFile <- MaybeT $ pure $ uriToNormalizedFilePath nUri
90+
useWithStaleFastMT GetHieAst otherLocationFile
91+
pure $ Location uri <$> (flip toCurrentRange range =<< otherLocationMapping)
7892
where
79-
go :: Location -> IdeAction (Maybe Location)
80-
go (Location uri range) =
81-
-- The Location we are going to might be in a different
82-
-- file than the one we are calling gotoDefinition from.
83-
-- So we check that the location file matches the file
84-
-- we are in.
85-
if nUri == normalizedFilePathToUri file
86-
-- The Location matches the file, so use the PositionMapping
87-
-- we have.
88-
then pure $ Location uri <$> toCurrentRange mapping range
89-
-- The Location does not match the file, so get the correct
90-
-- PositionMapping and use that instead.
91-
else do
92-
otherLocationMapping <- fmap (fmap snd) $ runMaybeT $ do
93-
otherLocationFile <- MaybeT $ pure $ uriToNormalizedFilePath nUri
94-
useWithStaleFastMT GetHieAst otherLocationFile
95-
pure $ Location uri <$> (flip toCurrentRange range =<< otherLocationMapping)
96-
where
97-
nUri :: NormalizedUri
98-
nUri = toNormalizedUri uri
93+
nUri :: NormalizedUri
94+
nUri = toNormalizedUri uri
9995

10096
-- | Goto Definition.
101-
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
97+
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location, Identifier)])
10298
getDefinition file pos = runMaybeT $ do
10399
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
104100
opts <- liftIO $ getIdeOptionsIO ide
105101
(HAR _ hf _ _ _, mapping) <- useWithStaleFastMT GetHieAst file
106102
(ImportMap imports, _) <- useWithStaleFastMT GetImportMap file
107103
!pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
108-
locations <- AtPoint.gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
109-
MaybeT $ Just <$> toCurrentLocations mapping file locations
104+
locationsWithIdentifier <- AtPoint.gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
105+
mapMaybeM (\(location, identifier) -> do
106+
fixedLocation <- MaybeT $ toCurrentLocation mapping file location
107+
pure $ Just (fixedLocation, identifier)
108+
) locationsWithIdentifier
110109

111-
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
110+
111+
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location, Identifier)])
112112
getTypeDefinition file pos = runMaybeT $ do
113113
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
114114
opts <- liftIO $ getIdeOptionsIO ide
115115
(hf, mapping) <- useWithStaleFastMT GetHieAst file
116116
!pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
117-
locations <- AtPoint.gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
118-
MaybeT $ Just <$> toCurrentLocations mapping file locations
117+
locationsWithIdentifier <- AtPoint.gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
118+
mapMaybeM (\(location, identifier) -> do
119+
fixedLocation <- MaybeT $ toCurrentLocation mapping file location
120+
pure $ Just (fixedLocation, identifier)
121+
) locationsWithIdentifier
119122

120123
highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight])
121124
highlightAtPoint file pos = runMaybeT $ do

ghcide/src/Development/IDE/GHC/Compat/Core.hs

+2
Original file line numberDiff line numberDiff line change
@@ -633,6 +633,8 @@ instance HasSrcSpan (EpAnn a) where
633633
#if MIN_VERSION_ghc(9,9,0)
634634
instance HasSrcSpan (SrcLoc.GenLocated (EpAnn ann) a) where
635635
getLoc (L l _) = getLoc l
636+
instance HasSrcSpan (SrcLoc.GenLocated (GHC.EpaLocation) a) where
637+
getLoc = GHC.getHasLoc
636638
#else
637639
instance HasSrcSpan (SrcSpanAnn' ann) where
638640
getLoc = GHC.locA

ghcide/src/Development/IDE/GHC/Orphans.hs

+6
Original file line numberDiff line numberDiff line change
@@ -226,6 +226,12 @@ instance NFData (HsExpr (GhcPass Renamed)) where
226226
instance NFData (Pat (GhcPass Renamed)) where
227227
rnf = rwhnf
228228

229+
instance NFData (HsExpr (GhcPass Typechecked)) where
230+
rnf = rwhnf
231+
232+
instance NFData (Pat (GhcPass Typechecked)) where
233+
rnf = rwhnf
234+
229235
instance NFData Extension where
230236
rnf = rwhnf
231237

ghcide/src/Development/IDE/LSP/HoverDefinition.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -47,8 +47,8 @@ gotoDefinition :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPos
4747
hover :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (Hover |? Null)
4848
gotoTypeDefinition :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (MessageResult Method_TextDocumentTypeDefinition)
4949
documentHighlight :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) ([DocumentHighlight] |? Null)
50-
gotoDefinition = request "Definition" getDefinition (InR $ InR Null) (InL . Definition. InR)
51-
gotoTypeDefinition = request "TypeDefinition" getTypeDefinition (InR $ InR Null) (InL . Definition. InR)
50+
gotoDefinition = request "Definition" getDefinition (InR $ InR Null) (InL . Definition. InR . map fst)
51+
gotoTypeDefinition = request "TypeDefinition" getTypeDefinition (InR $ InR Null) (InL . Definition. InR . map fst)
5252
hover = request "Hover" getAtPoint (InR Null) foundHover
5353
documentHighlight = request "DocumentHighlight" highlightAtPoint (InR Null) InL
5454

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

+14-8
Original file line numberDiff line numberDiff line change
@@ -179,14 +179,15 @@ documentHighlight hf rf pos = pure highlights
179179
then DocumentHighlightKind_Write
180180
else DocumentHighlightKind_Read
181181

182+
-- | Locate the type definition of the name at a given position.
182183
gotoTypeDefinition
183184
:: MonadIO m
184185
=> WithHieDb
185186
-> LookupModule m
186187
-> IdeOptions
187188
-> HieAstResult
188189
-> Position
189-
-> MaybeT m [Location]
190+
-> MaybeT m [(Location, Identifier)]
190191
gotoTypeDefinition withHieDb lookupModule ideOpts srcSpans pos
191192
= lift $ typeLocationsAtPoint withHieDb lookupModule ideOpts pos srcSpans
192193

@@ -199,7 +200,7 @@ gotoDefinition
199200
-> M.Map ModuleName NormalizedFilePath
200201
-> HieASTs a
201202
-> Position
202-
-> MaybeT m [Location]
203+
-> MaybeT m [(Location, Identifier)]
203204
gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
204205
= lift $ locationsAtPoint withHieDb getHieFile ideOpts imports pos srcSpans
205206

@@ -306,6 +307,7 @@ atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env
306307
UnhelpfulLoc {} | isInternalName name || isSystemName name -> Nothing
307308
_ -> Just $ "*Defined " <> printOutputable (pprNameDefnLoc name) <> "*"
308309

310+
-- | Find 'Location's of type definition at a specific point and return them along with their 'Identifier's.
309311
typeLocationsAtPoint
310312
:: forall m
311313
. MonadIO m
@@ -314,7 +316,7 @@ typeLocationsAtPoint
314316
-> IdeOptions
315317
-> Position
316318
-> HieAstResult
317-
-> m [Location]
319+
-> m [(Location, Identifier)]
318320
typeLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _ _ hieKind) =
319321
case hieKind of
320322
HieFromDisk hf ->
@@ -332,12 +334,12 @@ typeLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _ _ hieKi
332334
HQualTy a b -> getTypes' [a,b]
333335
HCastTy a -> getTypes' [a]
334336
_ -> []
335-
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation withHieDb lookupModule) (getTypes' ts)
337+
in fmap nubOrd $ concatMapM (\n -> fmap (maybe [] (fmap (,Right n))) (nameToLocation withHieDb lookupModule n)) (getTypes' ts)
336338
HieFresh ->
337339
let ts = concat $ pointCommand ast pos getts
338340
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
339341
where ni = nodeInfo x
340-
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation withHieDb lookupModule) (getTypes ts)
342+
in fmap nubOrd $ concatMapM (\n -> fmap (maybe [] (fmap (,Right n))) (nameToLocation withHieDb lookupModule n)) (getTypes ts)
341343

342344
namesInType :: Type -> [Name]
343345
namesInType (TyVarTy n) = [varName n]
@@ -352,6 +354,7 @@ namesInType _ = []
352354
getTypes :: [Type] -> [Name]
353355
getTypes ts = concatMap namesInType ts
354356

357+
-- | Find 'Location's of definition at a specific point and return them along with their 'Identifier's.
355358
locationsAtPoint
356359
:: forall m a
357360
. MonadIO m
@@ -361,13 +364,16 @@ locationsAtPoint
361364
-> M.Map ModuleName NormalizedFilePath
362365
-> Position
363366
-> HieASTs a
364-
-> m [Location]
367+
-> m [(Location, Identifier)]
365368
locationsAtPoint withHieDb lookupModule _ideOptions imports pos ast =
366369
let ns = concat $ pointCommand ast pos (M.keys . getNodeIds)
367370
zeroPos = Position 0 0
368371
zeroRange = Range zeroPos zeroPos
369-
modToLocation m = fmap (\fs -> pure $ Location (fromNormalizedUri $ filePathToUri' fs) zeroRange) $ M.lookup m imports
370-
in fmap (nubOrd . concat) $ mapMaybeM (either (pure . modToLocation) $ nameToLocation withHieDb lookupModule) ns
372+
modToLocation m = fmap (\fs -> pure (Location (fromNormalizedUri $ filePathToUri' fs) zeroRange)) $ M.lookup m imports
373+
in fmap (nubOrd . concat) $ mapMaybeM
374+
(either (\m -> pure ((fmap $ fmap (,Left m)) (modToLocation m)))
375+
(\n -> fmap (fmap $ fmap (,Right n)) (nameToLocation withHieDb lookupModule n)))
376+
ns
371377

372378
-- | Given a 'Name' attempt to find the location where it is defined.
373379
nameToLocation :: MonadIO m => WithHieDb -> LookupModule m -> Name -> m (Maybe [Location])

haskell-language-server.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -1360,6 +1360,7 @@ test-suite hls-explicit-record-fields-plugin-tests
13601360
, base
13611361
, filepath
13621362
, text
1363+
, ghcide
13631364
, haskell-language-server:hls-explicit-record-fields-plugin
13641365
, hls-test-utils == 2.9.0.1
13651366

hls-plugin-api/src/Ide/Plugin/RangeMap.hs

+9
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Ide.Plugin.RangeMap
1313
fromList,
1414
fromList',
1515
filterByRange,
16+
elementsInRange,
1617
) where
1718

1819
import Development.IDE.Graph.Classes (NFData)
@@ -67,6 +68,14 @@ filterByRange range = map snd . IM.dominators (rangeToInterval range) . unRangeM
6768
filterByRange range = map snd . filter (isSubrangeOf range . fst) . unRangeMap
6869
#endif
6970

71+
-- | Extracts all elements from a 'RangeMap' that fall within a given 'Range'.
72+
elementsInRange :: Range -> RangeMap a -> [a]
73+
#ifdef USE_FINGERTREE
74+
elementsInRange range = map snd . IM.intersections (rangeToInterval range) . unRangeMap
75+
#else
76+
elementsInRange range = map snd . filter (flip isSubrangeOf range . fst) . unRangeMap
77+
#endif
78+
7079
#ifdef USE_FINGERTREE
7180
-- NOTE(ozkutuk): In itself, this conversion is wrong. As Michael put it:
7281
-- "LSP Ranges have exclusive upper bounds, whereas the intervals here are

0 commit comments

Comments
 (0)