Skip to content

Commit 5436ef0

Browse files
authored
Show package name and its version while hovering on import statements (#3691)
* Show package name and its version while hovering on import statements * Add the missing test after merged master * Track remote
1 parent 9effc56 commit 5436ef0

File tree

5 files changed

+104
-35
lines changed

5 files changed

+104
-35
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ getAtPoint file pos = runMaybeT $ do
6565
dkMap <- lift $ maybe (DKMap mempty mempty) fst <$> runMaybeT (useWithStaleFastMT GetDocMap file)
6666

6767
!pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
68-
MaybeT $ pure $ first (toCurrentRange mapping =<<) <$> AtPoint.atPoint opts hf dkMap env pos'
68+
MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<<)) <$> AtPoint.atPoint opts hf dkMap env pos'
6969

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

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

Lines changed: 47 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -50,63 +50,78 @@ module Development.IDE.GHC.Compat.Units (
5050
filterInplaceUnits,
5151
FinderCache,
5252
showSDocForUser',
53+
findImportedModule,
5354
) where
5455

5556
import Control.Monad
56-
import qualified Data.List.NonEmpty as NE
57-
import qualified Data.Map.Strict as Map
57+
import qualified Data.List.NonEmpty as NE
58+
import qualified Data.Map.Strict as Map
5859
#if MIN_VERSION_ghc(9,3,0)
5960
import GHC.Unit.Home.ModInfo
6061
#endif
6162
#if MIN_VERSION_ghc(9,0,0)
6263
#if MIN_VERSION_ghc(9,2,0)
63-
import qualified GHC.Data.ShortText as ST
64+
import qualified GHC.Data.ShortText as ST
6465
#if !MIN_VERSION_ghc(9,3,0)
65-
import GHC.Driver.Env (hsc_unit_dbs)
66+
import GHC.Driver.Env (hsc_unit_dbs)
6667
#endif
6768
import GHC.Driver.Ppr
6869
import GHC.Unit.Env
6970
import GHC.Unit.External
70-
import GHC.Unit.Finder
71+
import GHC.Unit.Finder hiding
72+
(findImportedModule)
7173
#else
7274
import GHC.Driver.Types
7375
#endif
7476
import GHC.Data.FastString
75-
import qualified GHC.Driver.Session as DynFlags
77+
import qualified GHC.Driver.Session as DynFlags
7678
import GHC.Types.Unique.Set
77-
import qualified GHC.Unit.Info as UnitInfo
78-
import GHC.Unit.State (LookupResult, UnitInfo,
79-
UnitState (unitInfoMap))
80-
import qualified GHC.Unit.State as State
81-
import GHC.Unit.Types hiding (moduleUnit, toUnitId)
82-
import qualified GHC.Unit.Types as Unit
79+
import qualified GHC.Unit.Info as UnitInfo
80+
import GHC.Unit.State (LookupResult, UnitInfo,
81+
UnitState (unitInfoMap))
82+
import qualified GHC.Unit.State as State
83+
import GHC.Unit.Types hiding (moduleUnit,
84+
toUnitId)
85+
import qualified GHC.Unit.Types as Unit
8386
import GHC.Utils.Outputable
8487
#else
8588
import qualified DynFlags
8689
import FastString
87-
import GhcPlugins (SDoc, showSDocForUser)
90+
import GhcPlugins (SDoc, showSDocForUser)
8891
import HscTypes
89-
import Module hiding (moduleUnitId)
92+
import Module hiding (moduleUnitId)
9093
import qualified Module
91-
import Packages (InstalledPackageInfo (haddockInterfaces, packageName),
92-
LookupResult, PackageConfig,
93-
PackageConfigMap,
94-
PackageState,
95-
getPackageConfigMap,
96-
lookupPackage')
94+
import Packages (InstalledPackageInfo (haddockInterfaces, packageName),
95+
LookupResult,
96+
PackageConfig,
97+
PackageConfigMap,
98+
PackageState,
99+
getPackageConfigMap,
100+
lookupPackage')
97101
import qualified Packages
98102
#endif
99103

100104
import Development.IDE.GHC.Compat.Core
101105
import Development.IDE.GHC.Compat.Env
102106
import Development.IDE.GHC.Compat.Outputable
103107
#if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,2,0)
104-
import Data.Map (Map)
108+
import Data.Map (Map)
105109
#endif
106110
import Data.Either
107111
import Data.Version
108112
import qualified GHC
109113

114+
#if MIN_VERSION_ghc(9,3,0)
115+
import GHC.Types.PkgQual (PkgQual (NoPkgQual))
116+
#endif
117+
#if MIN_VERSION_ghc(9,1,0)
118+
import qualified GHC.Unit.Finder as GHC
119+
#elif MIN_VERSION_ghc(9,0,0)
120+
import qualified GHC.Driver.Finder as GHC
121+
#else
122+
import qualified Finder as GHC
123+
#endif
124+
110125
#if MIN_VERSION_ghc(9,0,0)
111126
type PreloadUnitClosure = UniqSet UnitId
112127
#if MIN_VERSION_ghc(9,2,0)
@@ -407,3 +422,14 @@ showSDocForUser' env = showSDocForUser (hsc_dflags env) (unitState env)
407422
#else
408423
showSDocForUser' env = showSDocForUser (hsc_dflags env)
409424
#endif
425+
426+
findImportedModule :: HscEnv -> ModuleName -> IO (Maybe Module)
427+
findImportedModule env mn = do
428+
#if MIN_VERSION_ghc(9,3,0)
429+
res <- GHC.findImportedModule env mn NoPkgQual
430+
#else
431+
res <- GHC.findImportedModule env mn Nothing
432+
#endif
433+
case res of
434+
Found _ mod -> pure . pure $ mod
435+
_ -> pure Nothing

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

Lines changed: 53 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,10 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4-
{-# LANGUAGE CPP #-}
5-
{-# LANGUAGE GADTs #-}
6-
{-# LANGUAGE RankNTypes #-}
4+
{-# LANGUAGE CPP #-}
5+
{-# LANGUAGE GADTs #-}
6+
{-# LANGUAGE RankNTypes #-}
7+
{-# LANGUAGE ScopedTypeVariables #-}
78

89
-- | Gives information about symbols at a given point in DAML files.
910
-- These are all pure functions that should execute quickly.
@@ -213,21 +214,33 @@ atPoint
213214
-> DocAndKindMap
214215
-> HscEnv
215216
-> Position
216-
-> Maybe (Maybe Range, [T.Text])
217-
atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ pointCommand hf pos hoverInfo
217+
-> IO (Maybe (Maybe Range, [T.Text]))
218+
atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env pos =
219+
listToMaybe <$> sequence (pointCommand hf pos hoverInfo)
218220
where
219221
-- Hover info for values/data
220-
hoverInfo ast = (Just range, prettyNames ++ pTypes)
222+
hoverInfo :: HieAST hietype -> IO (Maybe Range, [T.Text])
223+
hoverInfo ast = do
224+
prettyNames <- mapM prettyName filteredNames
225+
pure (Just range, prettyNames ++ pTypes)
221226
where
227+
pTypes :: [T.Text]
222228
pTypes
223229
| Prelude.length names == 1 = dropEnd1 $ map wrapHaskell prettyTypes
224230
| otherwise = map wrapHaskell prettyTypes
225231

232+
range :: Range
226233
range = realSrcSpanToRange $ nodeSpan ast
227234

235+
wrapHaskell :: T.Text -> T.Text
228236
wrapHaskell x = "\n```haskell\n"<>x<>"\n```\n"
237+
238+
info :: NodeInfo hietype
229239
info = nodeInfoH kind ast
240+
241+
names :: [(Identifier, IdentifierDetails hietype)]
230242
names = M.assocs $ nodeIdentifiers info
243+
231244
-- Check for evidence bindings
232245
isInternal :: (Identifier, IdentifierDetails a) -> Bool
233246
isInternal (Right _, dets) =
@@ -237,11 +250,12 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
237250
False
238251
#endif
239252
isInternal (Left _, _) = False
253+
254+
filteredNames :: [(Identifier, IdentifierDetails hietype)]
240255
filteredNames = filter (not . isInternal) names
241-
types = nodeType info
242-
prettyNames :: [T.Text]
243-
prettyNames = map prettyName filteredNames
244-
prettyName (Right n, dets) = T.unlines $
256+
257+
prettyName :: (Either ModuleName Name, IdentifierDetails hietype) -> IO T.Text
258+
prettyName (Right n, dets) = pure $ T.unlines $
245259
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
246260
: maybeToList (pretty (definedAt n) (prettyPackageName n))
247261
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
@@ -251,21 +265,48 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
251265
pretty (Just define) Nothing = Just $ define <> "\n"
252266
pretty Nothing (Just pkgName) = Just $ pkgName <> "\n"
253267
pretty (Just define) (Just pkgName) = Just $ define <> " " <> pkgName <> "\n"
254-
prettyName (Left m,_) = printOutputable m
268+
prettyName (Left m,_) = packageNameForImportStatement m
255269

270+
prettyPackageName :: Name -> Maybe T.Text
256271
prettyPackageName n = do
257272
m <- nameModule_maybe n
273+
pkgTxt <- packageNameWithVersion m env
274+
pure $ "*(" <> pkgTxt <> ")*"
275+
276+
-- Return the module text itself and
277+
-- the package(with version) this `ModuleName` belongs to.
278+
packageNameForImportStatement :: ModuleName -> IO T.Text
279+
packageNameForImportStatement mod = do
280+
mpkg <- findImportedModule env mod :: IO (Maybe Module)
281+
let moduleName = printOutputable mod
282+
case mpkg >>= flip packageNameWithVersion env of
283+
Nothing -> pure moduleName
284+
Just pkgWithVersion -> pure $ moduleName <> "\n\n" <> pkgWithVersion
285+
286+
-- Return the package name and version of a module.
287+
-- For example, given module `Data.List`, it should return something like `base-4.x`.
288+
packageNameWithVersion :: Module -> HscEnv -> Maybe T.Text
289+
packageNameWithVersion m env = do
258290
let pid = moduleUnit m
259291
conf <- lookupUnit env pid
260292
let pkgName = T.pack $ unitPackageNameString conf
261293
version = T.pack $ showVersion (unitPackageVersion conf)
262-
pure $ "*(" <> pkgName <> "-" <> version <> ")*"
294+
pure $ pkgName <> "-" <> version
295+
296+
-- Type info for the current node, it may contains several symbols
297+
-- for one range, like wildcard
298+
types :: [hietype]
299+
types = nodeType info
263300

301+
prettyTypes :: [T.Text]
264302
prettyTypes = map (("_ :: "<>) . prettyType) types
303+
304+
prettyType :: hietype -> T.Text
265305
prettyType t = case kind of
266306
HieFresh -> printOutputable t
267307
HieFromDisk full_file -> printOutputable $ hieTypeToIface $ recoverFullType t (hie_types full_file)
268308

309+
definedAt :: Name -> Maybe T.Text
269310
definedAt name =
270311
-- do not show "at <no location info>" and similar messages
271312
-- see the code of 'pprNameDefnLoc' for more information

ghcide/test/exe/FindDefinitionAndHoverTests.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,7 @@ tests = let
173173
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], mkL bar 3 (if ghcVersion >= GHC94 then 5 else 0) 3 (if ghcVersion >= GHC94 then 8 else 14)]
174174
thLocL57 = Position 59 10 ; thLoc = [ExpectHoverText ["Identity"]]
175175
cmtL68 = Position 67 0 ; lackOfdEq = [ExpectHoverExcludeText ["$dEq"]]
176+
import310 = Position 3 10; pkgTxt = [ExpectHoverText ["Data.Text\n\ntext-"]]
176177
in
177178
mkFindTests
178179
-- def hover look expect
@@ -236,6 +237,7 @@ tests = let
236237
test no broken thLocL57 thLoc "TH Splice Hover"
237238
| otherwise ->
238239
test no yes thLocL57 thLoc "TH Splice Hover"
240+
, test yes yes import310 pkgTxt "show package name and its version"
239241
]
240242
where yes, broken :: (TestTree -> Maybe TestTree)
241243
yes = Just -- test should run and pass

ghcide/test/exe/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,4 +124,4 @@ main = do
124124
, GarbageCollectionTests.tests
125125
, HieDbRetry.tests
126126
, ExceptionTests.tests recorder logger
127-
]
127+
]

0 commit comments

Comments
 (0)