Skip to content

Commit 859edfb

Browse files
authored
Fix hover format (#2911)
* Fix hover format * Test with regex * Add comments about inserting a new line in Markdown
1 parent 9b3f3bf commit 859edfb

File tree

3 files changed

+18
-10
lines changed

3 files changed

+18
-10
lines changed

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

+9-6
Original file line numberDiff line numberDiff line change
@@ -32,9 +32,9 @@ import Development.IDE.Core.PositionMapping
3232
import Development.IDE.Core.RuleTypes
3333
import Development.IDE.GHC.Compat
3434
import qualified Development.IDE.GHC.Compat.Util as Util
35+
import Development.IDE.GHC.Util (printOutputable)
3536
import Development.IDE.Spans.Common
3637
import Development.IDE.Types.Options
37-
import Development.IDE.GHC.Util (printOutputable)
3838

3939
import Control.Applicative
4040
import Control.Monad.Extra
@@ -231,11 +231,14 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
231231
prettyNames = map prettyName names
232232
prettyName (Right n, dets) = T.unlines $
233233
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
234-
: definedAt n
235-
++ maybeToList (prettyPackageName n)
234+
: maybeToList (pretty (definedAt n) (prettyPackageName n))
236235
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
237236
]
238237
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
238+
pretty Nothing Nothing = Nothing
239+
pretty (Just define) Nothing = Just $ define <> "\n"
240+
pretty Nothing (Just pkgName) = Just $ pkgName <> "\n"
241+
pretty (Just define) (Just pkgName) = Just $ define <> " " <> pkgName <> "\n"
239242
prettyName (Left m,_) = printOutputable m
240243

241244
prettyPackageName n = do
@@ -244,7 +247,7 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
244247
conf <- lookupUnit env pid
245248
let pkgName = T.pack $ unitPackageNameString conf
246249
version = T.pack $ showVersion (unitPackageVersion conf)
247-
pure $ " *(" <> pkgName <> "-" <> version <> ")*"
250+
pure $ "*(" <> pkgName <> "-" <> version <> ")*"
248251

249252
prettyTypes = map (("_ :: "<>) . prettyType) types
250253
prettyType t = case kind of
@@ -255,8 +258,8 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
255258
-- do not show "at <no location info>" and similar messages
256259
-- see the code of 'pprNameDefnLoc' for more information
257260
case nameSrcLoc name of
258-
UnhelpfulLoc {} | isInternalName name || isSystemName name -> []
259-
_ -> ["*Defined " <> printOutputable (pprNameDefnLoc name) <> "*"]
261+
UnhelpfulLoc {} | isInternalName name || isSystemName name -> Nothing
262+
_ -> Just $ "*Defined " <> printOutputable (pprNameDefnLoc name) <> "*"
260263

261264
typeLocationsAtPoint
262265
:: forall m

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

+5-2
Original file line numberDiff line numberDiff line change
@@ -51,9 +51,7 @@ safeTyThingId _ = Nothing
5151
-- Possible documentation for an element in the code
5252
data SpanDoc
5353
= SpanDocString HsDocString SpanDocUris
54-
-- ^ Extern module doc
5554
| SpanDocText [T.Text] SpanDocUris
56-
-- ^ Local module doc
5755
deriving stock (Eq, Show, Generic)
5856
deriving anyclass NFData
5957

@@ -80,6 +78,11 @@ emptySpanDoc = SpanDocText [] (SpanDocUris Nothing Nothing)
8078
-- it will result "xxxx---\nyyyy" and can't be rendered as a normal doc.
8179
-- Therefore we check every item in the value to make sure they all end with '\\n',
8280
-- this makes "xxxx\n---\nyyy\n" and can be rendered correctly.
81+
--
82+
-- Notes:
83+
--
84+
-- To insert a new line in Markdown, we need two '\\n', like ("\\n\\n"), __or__ a section
85+
-- symbol with one '\\n', like ("***\\n").
8386
spanDocToMarkdown :: SpanDoc -> [T.Text]
8487
spanDocToMarkdown = \case
8588
(SpanDocString docs uris) ->

ghcide/test/exe/Main.hs

+4-2
Original file line numberDiff line numberDiff line change
@@ -4254,6 +4254,7 @@ findDefinitionAndHoverTests = let
42544254
ExpectRange expectedRange -> checkHoverRange expectedRange rangeInHover msg
42554255
ExpectHoverRange expectedRange -> checkHoverRange expectedRange rangeInHover msg
42564256
ExpectHoverText snippets -> liftIO $ traverse_ (`assertFoundIn` msg) snippets
4257+
ExpectHoverTextRegex re -> liftIO $ assertBool ("Regex not found in " <> T.unpack msg) (msg =~ re :: Bool)
42574258
ExpectNoHover -> liftIO $ assertFailure $ "Expected no hover but got " <> show hover
42584259
_ -> pure () -- all other expectations not relevant to hover
42594260
_ -> liftIO $ assertFailure $ "test not expecting this kind of hover info" <> show hover
@@ -4344,7 +4345,7 @@ findDefinitionAndHoverTests = let
43444345
innL48 = Position 52 5 ; innSig = [ExpectHoverText ["inner", "Char"], mkR 49 2 49 7]
43454346
holeL60 = Position 62 7 ; hleInfo = [ExpectHoverText ["_ ::"]]
43464347
holeL65 = Position 65 8 ; hleInfo2 = [ExpectHoverText ["_ :: a -> Maybe a"]]
4347-
cccL17 = Position 17 16 ; docLink = [ExpectHoverText ["[Documentation](file:///"]]
4348+
cccL17 = Position 17 16 ; docLink = [ExpectHoverTextRegex "\\*Defined in 'GHC.Types'\\* \\*\\(ghc-prim-[0-9.]+\\)\\*\n\n"]
43484349
imported = Position 56 13 ; importedSig = getDocUri "Foo.hs" >>= \foo -> return [ExpectHoverText ["foo", "Foo", "Haddock"], mkL foo 5 0 5 3]
43494350
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], mkL bar 3 0 3 14]
43504351
thLocL57 = Position 59 10 ; thLoc = [ExpectHoverText ["Identity"]]
@@ -4399,7 +4400,7 @@ findDefinitionAndHoverTests = let
43994400
, test broken broken innL48 innSig "inner signature #767"
44004401
, test no yes holeL60 hleInfo "hole without internal name #831"
44014402
, test no yes holeL65 hleInfo2 "hole with variable"
4402-
, test no skip cccL17 docLink "Haddock html links"
4403+
, test no yes cccL17 docLink "Haddock html links"
44034404
, testM yes yes imported importedSig "Imported symbol"
44044405
, testM yes yes reexported reexportedSig "Imported symbol (reexported)"
44054406
, if | ghcVersion == GHC90 && isWindows ->
@@ -5743,6 +5744,7 @@ data Expect
57435744
-- | ExpectDefRange Range -- Only gotoDef should report this range
57445745
| ExpectHoverRange Range -- Only hover should report this range
57455746
| ExpectHoverText [T.Text] -- the hover message must contain these snippets
5747+
| ExpectHoverTextRegex T.Text -- the hover message must match this pattern
57465748
| ExpectExternFail -- definition lookup in other file expected to fail
57475749
| ExpectNoDefinitions
57485750
| ExpectNoHover

0 commit comments

Comments
 (0)