Skip to content

Commit 33e03d2

Browse files
committed
Make hover work in dependency files
1 parent b0af06f commit 33e03d2

File tree

3 files changed

+37
-22
lines changed

3 files changed

+37
-22
lines changed

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

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -124,11 +124,15 @@ getAtPoint file pos = runMaybeT $ do
124124
opts <- liftIO $ getIdeOptionsIO ide
125125

126126
(hf, mapping) <- useE GetHieAst file
127-
env <- hscEnv . fst <$> useE GhcSession file
128-
dkMap <- lift $ maybe (DKMap mempty mempty) fst <$> runMaybeT (useE GetDocMap file)
127+
(mEnv, mDkMap) <- case getSourceFileOrigin file of
128+
FromDependency -> pure (Nothing, Nothing)
129+
FromProject -> do
130+
env <- hscEnv . fst <$> useE GhcSession file
131+
dkMap <- lift $ maybe (DKMap mempty mempty) fst <$> runMaybeT (useE GetDocMap file)
132+
pure (Just env, Just dkMap)
129133

130134
!pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
131-
MaybeT $ pure $ first (toCurrentRange mapping =<<) <$> AtPoint.atPoint opts hf dkMap env pos'
135+
MaybeT $ pure $ first (toCurrentRange mapping =<<) <$> AtPoint.atPoint opts hf mDkMap mEnv pos'
132136

133137
-- | For each Loacation, determine if we have the PositionMapping
134138
-- for the correct file. If not, get the correct position mapping

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

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -570,19 +570,18 @@ reportImportCyclesRule recorder =
570570
getHieAstsRule :: Recorder (WithPriority Log) -> Rules ()
571571
getHieAstsRule recorder =
572572
define (cmapWithPrio LogShake recorder) $ \GetHieAst f -> do
573-
isFoi <- use_ IsFileOfInterest f
574-
case isFoi of
575-
IsFOI ReadOnly -> do
573+
case getSourceFileOrigin f of
574+
FromDependency -> do
576575
se <- getShakeExtras
577576
mHieFile <- liftIO
578577
$ runIdeAction "GetHieAst" se
579578
$ runMaybeT
580579
$ readHieFileForSrcFromDisk recorder f
581580
pure ([], makeHieAstResult <$> mHieFile)
582-
_ -> do
581+
FromProject -> do
583582
tmr <- use_ TypeCheck f
584583
hsc <- hscEnv <$> use_ GhcSessionDeps f
585-
getHieAstRuleDefinition f isFoi hsc tmr
584+
getHieAstRuleDefinition f hsc tmr
586585
where
587586
makeHieAstResult :: Compat.HieFile -> HieAstResult
588587
makeHieAstResult hieFile =
@@ -605,11 +604,12 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe
605604
del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource
606605
pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver)
607606

608-
getHieAstRuleDefinition :: NormalizedFilePath -> IsFileOfInterestResult -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult)
609-
getHieAstRuleDefinition f isFoi hsc tmr = do
607+
getHieAstRuleDefinition :: NormalizedFilePath -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult)
608+
getHieAstRuleDefinition f hsc tmr = do
610609
(diags, masts) <- liftIO $ generateHieAsts hsc tmr
611610
se <- getShakeExtras
612611

612+
isFoi <- use_ IsFileOfInterest f
613613
diagsWrite <- case isFoi of
614614
IsFOI Modified{firstOpen = False} -> do
615615
when (coerce $ ideTesting se) $ liftIO $ mRunLspT (lspEnv se) $

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

Lines changed: 23 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -211,11 +211,11 @@ gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
211211
atPoint
212212
:: IdeOptions
213213
-> HieAstResult
214-
-> DocAndKindMap
215-
-> HscEnv
214+
-> Maybe DocAndKindMap
215+
-> Maybe HscEnv
216216
-> Position
217217
-> Maybe (Maybe Range, [T.Text])
218-
atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ pointCommand hf pos hoverInfo
218+
atPoint IdeOptions{} (HAR _ hf _ _ kind) mDkMap mEnv pos = listToMaybe $ pointCommand hf pos hoverInfo
219219
where
220220
-- Hover info for values/data
221221
hoverInfo ast = (Just range, prettyNames ++ pTypes)
@@ -245,22 +245,33 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
245245
prettyName (Right n, dets) = T.unlines $
246246
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
247247
: maybeToList (pretty (definedAt n) (prettyPackageName n))
248-
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
248+
++ catMaybes [ T.unlines . spanDocToMarkdown <$> maybeDoc
249249
]
250-
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
250+
where maybeKind = do
251+
(DKMap _ km) <- mDkMap
252+
nameEnv <- lookupNameEnv km n
253+
printOutputable <$> safeTyThingType nameEnv
254+
maybeDoc = do
255+
(DKMap dm _) <- mDkMap
256+
lookupNameEnv dm n
251257
pretty Nothing Nothing = Nothing
252258
pretty (Just define) Nothing = Just $ define <> "\n"
253259
pretty Nothing (Just pkgName) = Just $ pkgName <> "\n"
254260
pretty (Just define) (Just pkgName) = Just $ define <> " " <> pkgName <> "\n"
255261
prettyName (Left m,_) = printOutputable m
256262

257-
prettyPackageName n = do
258-
m <- nameModule_maybe n
259-
let pid = moduleUnit m
260-
conf <- lookupUnit env pid
261-
let pkgName = T.pack $ unitPackageNameString conf
262-
version = T.pack $ showVersion (unitPackageVersion conf)
263-
pure $ "*(" <> pkgName <> "-" <> version <> ")*"
263+
prettyPackageName n = case mEnv of
264+
Just env -> do
265+
pid <- getUnit n
266+
conf <- lookupUnit env pid
267+
let pkgName = T.pack $ unitPackageNameString conf
268+
version = T.pack $ showVersion (unitPackageVersion conf)
269+
pure $ "*(" <> pkgName <> "-" <> version <> ")*"
270+
Nothing -> do
271+
u <- getUnit n
272+
let pkgStr = takeWhile (/= ':') $ show $ toUnitId u
273+
pure $ "*(" <> T.pack pkgStr <> ")*"
274+
getUnit n = moduleUnit <$> nameModule_maybe n
264275

265276
prettyTypes = map (("_ :: "<>) . prettyType) types
266277
prettyType t = case kind of

0 commit comments

Comments
 (0)