@@ -10,6 +10,7 @@ module Development.IDE.Spans.AtPoint (
1010 atPoint
1111 , gotoDefinition
1212 , gotoTypeDefinition
13+ , gotoImplementation
1314 , documentHighlight
1415 , pointCommand
1516 , referencesAtPoint
@@ -66,6 +67,7 @@ import Development.IDE.Types.Shake (WithHieDb)
6667import HieDb hiding (pointCommand ,
6768 withHieDb )
6869import System.Directory (doesFileExist )
70+ import Data.Either.Extra (eitherToMaybe )
6971
7072-- | Gives a Uri for the module, given the .hie file location and the the module info
7173-- The Bool denotes if it is a boot module
@@ -214,6 +216,19 @@ gotoDefinition
214216gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
215217 = lift $ locationsAtPoint withHieDb getHieFile ideOpts imports pos srcSpans
216218
219+ -- | Locate the implementation definition of the name at a given position.
220+ -- Goto Implementation for an overloaded function.
221+ gotoImplementation
222+ :: MonadIO m
223+ => WithHieDb
224+ -> LookupModule m
225+ -> IdeOptions
226+ -> HieAstResult
227+ -> Position
228+ -> MaybeT m [Location ]
229+ gotoImplementation withHieDb getHieFile ideOpts srcSpans pos
230+ = lift $ instanceLocationsAtPoint withHieDb getHieFile ideOpts pos srcSpans
231+
217232-- | Synopsis for the name at a given position.
218233atPoint
219234 :: IdeOptions
@@ -228,7 +243,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
228243 -- Hover info for values/data
229244 hoverInfo :: HieAST hietype -> IO (Maybe Range , [T. Text ])
230245 hoverInfo ast = do
231- prettyNames <- mapM prettyName filteredNames
246+ prettyNames <- mapM prettyName names
232247 pure (Just range, prettyNames ++ pTypes)
233248 where
234249 pTypes :: [T. Text ]
@@ -245,27 +260,20 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
245260 info :: NodeInfo hietype
246261 info = nodeInfoH kind ast
247262
263+ -- We want evidence variables to be displayed last.
264+ -- Evidence trees contain information of secondary relevance.
248265 names :: [(Identifier , IdentifierDetails hietype )]
249266 names = sortOn (any isEvidenceUse . identInfo . snd ) $ M. assocs $ nodeIdentifiers info
250267
251- -- Check for evidence bindings
252- isInternal :: (Identifier , IdentifierDetails a ) -> Bool
253- isInternal (Right _, dets) =
254- any isEvidenceContext $ identInfo dets
255- isInternal (Left _, _) = False
256-
257- filteredNames :: [(Identifier , IdentifierDetails hietype )]
258- filteredNames = filter (not . isInternal) names
259-
260268 prettyName :: (Either ModuleName Name , IdentifierDetails hietype ) -> IO T. Text
261269 prettyName (Right n, dets)
262- | any isEvidenceUse (identInfo dets) =
263- pure $ maybe " " (printOutputable . renderEvidenceTree) (getEvidenceTree rf n) <> " \n "
270+ -- We want to print evidence variable using a readable tree structure.
271+ | any isEvidenceUse (identInfo dets) = pure $ maybe " " (printOutputable . renderEvidenceTree) (getEvidenceTree rf n) <> " \n "
264272 | otherwise = pure $ T. unlines $
265273 wrapHaskell (printOutputable n <> maybe " " (" :: " <> ) ((prettyType <$> identType dets) <|> maybeKind))
266274 : maybeToList (pretty (definedAt n) (prettyPackageName n))
267275 ++ catMaybes [ T. unlines . spanDocToMarkdown <$> lookupNameEnv dm n
268- ]
276+ ]
269277 where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
270278 pretty Nothing Nothing = Nothing
271279 pretty (Just define) Nothing = Just $ define <> " \n "
@@ -299,7 +307,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
299307 version = T. pack $ showVersion (unitPackageVersion conf)
300308 pure $ pkgName <> " -" <> version
301309
302- -- Type info for the current node, it may contains several symbols
310+ -- Type info for the current node, it may contain several symbols
303311 -- for one range, like wildcard
304312 types :: [hietype ]
305313 types = nodeType info
@@ -308,10 +316,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
308316 prettyTypes = map ((" _ :: " <> ) . prettyType) types
309317
310318 prettyType :: hietype -> T. Text
311- prettyType t = case kind of
312- HieFresh -> printOutputable t
313- HieFromDisk full_file -> printOutputable $ hieTypeToIface $ recoverFullType t (hie_types full_file)
314- -- prettyType = printOutputable . expandType
319+ prettyType = printOutputable . expandType
315320
316321 expandType :: a -> SDoc
317322 expandType t = case kind of
@@ -352,7 +357,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
352357 printDets ospn (Just (src,_,mspn)) = pprSrc
353358 $$ text " at" <+> ppr spn
354359 where
355- -- Use the bind span if we have one, else use the occurence span
360+ -- Use the bind span if we have one, else use the occurrence span
356361 spn = fromMaybe ospn mspn
357362 pprSrc = case src of
358363 -- Users don't know what HsWrappers are
@@ -419,15 +424,31 @@ locationsAtPoint
419424 -> m [(Location , Identifier )]
420425locationsAtPoint withHieDb lookupModule _ideOptions imports pos (HAR _ ast _rm _ _) =
421426 let ns = concat $ pointCommand ast pos (M. keys . getNodeIds)
422- evTrees = mapMaybe (either (const Nothing ) $ getEvidenceTree _rm) ns
423- evNs = concatMap (map (Right . evidenceVar) . T. flatten) evTrees
424427 zeroPos = Position 0 0
425428 zeroRange = Range zeroPos zeroPos
426429 modToLocation m = fmap (\ fs -> pure (Location (fromNormalizedUri $ filePathToUri' fs) zeroRange)) $ M. lookup m imports
427430 in fmap (nubOrd . concat ) $ mapMaybeM
428431 (either (\ m -> pure ((fmap $ fmap (,Left m)) (modToLocation m)))
429432 (\ n -> fmap (fmap $ fmap (,Right n)) (nameToLocation withHieDb lookupModule n)))
430- (ns ++ evNs)
433+ ns
434+
435+ -- | Find 'Location's of a implementation definition at a specific point.
436+ instanceLocationsAtPoint
437+ :: forall m
438+ . MonadIO m
439+ => WithHieDb
440+ -> LookupModule m
441+ -> IdeOptions
442+ -> Position
443+ -> HieAstResult
444+ -> m [Location ]
445+ instanceLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _rm _ _) =
446+ let ns = concat $ pointCommand ast pos (M. keys . getNodeIds)
447+ evTrees = mapMaybe (eitherToMaybe >=> getEvidenceTree _rm) ns
448+ evNs = concatMap (map (evidenceVar) . T. flatten) evTrees
449+ in fmap (nubOrd . concat ) $ mapMaybeM
450+ (nameToLocation withHieDb lookupModule)
451+ evNs
431452
432453-- | Given a 'Name' attempt to find the location where it is defined.
433454nameToLocation :: MonadIO m => WithHieDb -> LookupModule m -> Name -> m (Maybe [Location ])
0 commit comments