Skip to content

Commit cbb61d5

Browse files
committed
hls-notes-plugin: Allow to see where a note is referenced from
1 parent 9adae74 commit cbb61d5

File tree

4 files changed

+98
-35
lines changed

4 files changed

+98
-35
lines changed

plugins/hls-notes-plugin/src/Ide/Plugin/Notes.hs

Lines changed: 75 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,15 @@
11
module Ide.Plugin.Notes (descriptor, Log) where
22

33
import Control.Lens ((^.))
4-
import Control.Monad.Except (throwError)
4+
import Control.Monad.Except (ExceptT, MonadError,
5+
throwError)
56
import Control.Monad.IO.Class (liftIO)
67
import qualified Data.Array as A
8+
import Data.Foldable (foldl')
79
import Data.HashMap.Strict (HashMap)
810
import qualified Data.HashMap.Strict as HM
911
import qualified Data.HashSet as HS
12+
import Data.List (uncons)
1013
import Data.Maybe (catMaybes, listToMaybe,
1114
mapMaybe)
1215
import Data.Text (Text, intercalate)
@@ -21,8 +24,8 @@ import GHC.Generics (Generic)
2124
import Ide.Plugin.Error (PluginError (..))
2225
import Ide.Types
2326
import qualified Language.LSP.Protocol.Lens as L
24-
import Language.LSP.Protocol.Message (Method (Method_TextDocumentDefinition),
25-
SMethod (SMethod_TextDocumentDefinition))
27+
import Language.LSP.Protocol.Message (Method (Method_TextDocumentDefinition, Method_TextDocumentReferences),
28+
SMethod (SMethod_TextDocumentDefinition, SMethod_TextDocumentReferences))
2629
import Language.LSP.Protocol.Types
2730
import Text.Regex.TDFA (Regex, caseSensitive,
2831
defaultCompOpt,
@@ -31,25 +34,32 @@ import Text.Regex.TDFA (Regex, caseSensitive,
3134

3235
data Log
3336
= LogShake Shake.Log
34-
| LogNotesFound NormalizedFilePath [(Text, Position)]
37+
| LogNotesFound NormalizedFilePath [(Text, [Position])]
38+
| LogNoteReferencesFound NormalizedFilePath [(Text, [Position])]
3539
deriving Show
3640

3741
data GetNotesInFile = MkGetNotesInFile
3842
deriving (Show, Generic, Eq, Ord)
3943
deriving anyclass (Hashable, NFData)
40-
type instance RuleResult GetNotesInFile = HM.HashMap Text Position
44+
type instance RuleResult GetNotesInFile = (HM.HashMap Text Position, HM.HashMap Text [Position])
4145

4246
data GetNotes = MkGetNotes
4347
deriving (Show, Generic, Eq, Ord)
4448
deriving anyclass (Hashable, NFData)
4549
type instance RuleResult GetNotes = HashMap Text (NormalizedFilePath, Position)
4650

51+
data GetNoteReferences = MkGetNoteReferences
52+
deriving (Show, Generic, Eq, Ord)
53+
deriving anyclass (Hashable, NFData)
54+
type instance RuleResult GetNoteReferences = HashMap Text [(NormalizedFilePath, Position)]
55+
4756
instance Pretty Log where
4857
pretty = \case
49-
LogShake l -> pretty l
50-
LogNotesFound file notes ->
51-
"Found notes in " <> pretty (show file) <> ": ["
52-
<> pretty (intercalate ", " (fmap (\(s, p) -> "\"" <> s <> "\" at " <> T.pack (show p)) notes)) <> "]"
58+
LogShake l -> pretty l
59+
LogNoteReferencesFound file refs -> "Found note references in " <> prettyNotes file refs
60+
LogNotesFound file notes -> "Found notes in " <> prettyNotes file notes
61+
where prettyNotes file hm = pretty (show file) <> ": ["
62+
<> pretty (intercalate ", " (fmap (\(s, p) -> "\"" <> s <> "\" at " <> intercalate ", " (map (T.pack . show) p)) hm)) <> "]"
5363

5464
{-
5565
The first time the user requests a jump-to-definition on a note reference, the
@@ -59,7 +69,9 @@ title is then saved in the HLS database to be retrieved for all future requests.
5969
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
6070
descriptor recorder plId = (defaultPluginDescriptor plId "Provides goto definition support for GHC-style notes")
6171
{ Ide.Types.pluginRules = findNotesRules recorder
62-
, Ide.Types.pluginHandlers = mkPluginHandler SMethod_TextDocumentDefinition jumpToNote
72+
, Ide.Types.pluginHandlers =
73+
mkPluginHandler SMethod_TextDocumentDefinition jumpToNote
74+
<> mkPluginHandler SMethod_TextDocumentReferences listReferences
6375
}
6476

6577
findNotesRules :: Recorder (WithPriority Log) -> Rules ()
@@ -69,20 +81,56 @@ findNotesRules recorder = do
6981

7082
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \MkGetNotes _ -> do
7183
targets <- toKnownFiles <$> useNoFile_ GetKnownTargets
72-
definedNotes <- catMaybes <$> mapM (\nfp -> fmap (HM.map (nfp,)) <$> use MkGetNotesInFile nfp) (HS.toList targets)
84+
definedNotes <- catMaybes <$> mapM (\nfp -> fmap (HM.map (nfp,) . fst) <$> use MkGetNotesInFile nfp) (HS.toList targets)
7385
pure $ Just $ HM.unions definedNotes
7486

87+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \MkGetNoteReferences _ -> do
88+
targets <- toKnownFiles <$> useNoFile_ GetKnownTargets
89+
definedReferences <- catMaybes <$> mapM (\nfp -> fmap (HM.map (fmap (nfp,)) . snd) <$> use MkGetNotesInFile nfp) (HS.toList targets)
90+
pure $ Just $ foldl' (HM.unionWith (<>)) HM.empty definedReferences
91+
92+
err :: MonadError PluginError m => Text -> Maybe a -> m a
93+
err s = maybe (throwError $ PluginInternalError s) pure
94+
95+
getNote :: NormalizedFilePath -> IdeState -> Position -> ExceptT PluginError (HandlerM c) (Maybe Text)
96+
getNote nfp state (Position l c) = do
97+
contents <-
98+
err "Error getting file contents"
99+
=<< liftIO (runAction "notes.getfileContents" state (getFileContents nfp))
100+
line <- err "Line not found in file" (listToMaybe $ Rope.lines $ fst
101+
(Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) contents))
102+
pure $ listToMaybe $ mapMaybe (atPos $ fromIntegral c) $ matchAllText noteRefRegex line
103+
where
104+
atPos c arr = case arr A.! 0 of
105+
-- We check if the line we are currently at contains a note
106+
-- reference. However, we need to know if the cursor is within the
107+
-- match or somewhere else. The second entry of the array contains
108+
-- the title of the note as extracted by the regex.
109+
(_, (c', len)) -> if c' <= c && c <= c' + len
110+
then Just (fst (arr A.! 1)) else Nothing
111+
112+
listReferences :: PluginMethodHandler IdeState Method_TextDocumentReferences
113+
listReferences state _ param
114+
| Just nfp <- uriToNormalizedFilePath uriOrig
115+
= do
116+
let pos@(Position l _) = param ^. L.position
117+
noteOpt <- getNote nfp state pos
118+
case noteOpt of
119+
Nothing -> pure (InR Null)
120+
Just note -> do
121+
notes <- runActionE "notes.definedNoteReferencess" state $ useE MkGetNoteReferences nfp
122+
poss <- err ("Note reference (a comment of the form `{- Note [" <> note <> "] -}`) not found") (HM.lookup note notes)
123+
pure $ InL (mapMaybe (\(noteFp, pos@(Position l' _)) -> if l' == l then Nothing else Just (
124+
Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))) poss)
125+
where
126+
uriOrig = toNormalizedUri $ param ^. (L.textDocument . L.uri)
127+
listReferences _ _ _ = throwError $ PluginInternalError "conversion to normalized file path failed"
128+
75129
jumpToNote :: PluginMethodHandler IdeState Method_TextDocumentDefinition
76130
jumpToNote state _ param
77131
| Just nfp <- uriToNormalizedFilePath uriOrig
78132
= do
79-
let Position l c = param ^. L.position
80-
contents <-
81-
err "Error getting file contents"
82-
=<< liftIO (runAction "notes.getfileContents" state (getFileContents nfp))
83-
line <- err "Line not found in file" (listToMaybe $ Rope.lines $ fst
84-
(Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) contents))
85-
let noteOpt = listToMaybe $ mapMaybe (atPos $ fromIntegral c) $ matchAllText noteRefRegex line
133+
noteOpt <- getNote nfp state (param ^. L.position)
86134
case noteOpt of
87135
Nothing -> pure (InR (InR Null))
88136
Just note -> do
@@ -93,28 +141,23 @@ jumpToNote state _ param
93141
))
94142
where
95143
uriOrig = toNormalizedUri $ param ^. (L.textDocument . L.uri)
96-
err s = maybe (throwError $ PluginInternalError s) pure
97-
atPos c arr = case arr A.! 0 of
98-
-- We check if the line we are currently at contains a note
99-
-- reference. However, we need to know if the cursor is within the
100-
-- match or somewhere else. The second entry of the array contains
101-
-- the title of the note as extracted by the regex.
102-
(_, (c', len)) -> if c' <= c && c <= c' + len
103-
then Just (fst (arr A.! 1)) else Nothing
104144
jumpToNote _ _ _ = throwError $ PluginInternalError "conversion to normalized file path failed"
105145

106-
findNotesInFile :: NormalizedFilePath -> Recorder (WithPriority Log) -> Action (Maybe (HM.HashMap Text Position))
146+
findNotesInFile :: NormalizedFilePath -> Recorder (WithPriority Log) -> Action (Maybe (HM.HashMap Text Position, HM.HashMap Text [Position]))
107147
findNotesInFile file recorder = do
108148
-- GetFileContents only returns a value if the file is open in the editor of
109149
-- the user. If not, we need to read it from disk.
110150
contentOpt <- (snd =<<) <$> use GetFileContents file
111151
content <- case contentOpt of
112152
Just x -> pure $ Rope.toText x
113153
Nothing -> liftIO $ readFileUtf8 $ fromNormalizedFilePath file
114-
let matches = (A.! 1) <$> matchAllText noteRegex content
115-
m = toPositions matches content
116-
logWith recorder Debug $ LogNotesFound file (HM.toList m)
117-
pure $ Just m
154+
let noteMatches = (A.! 1) <$> matchAllText noteRegex content
155+
notes = toPositions noteMatches content
156+
logWith recorder Debug $ LogNotesFound file (HM.toList notes)
157+
let refMatches = (A.! 1) <$> matchAllText noteRefRegex content
158+
refs = toPositions refMatches content
159+
logWith recorder Debug $ LogNoteReferencesFound file (HM.toList refs)
160+
pure $ Just (HM.mapMaybe (fmap fst . uncons) notes, refs)
118161
where
119162
uint = fromIntegral . toInteger
120163
-- the regex library returns the character index of the match. However
@@ -129,7 +172,7 @@ findNotesInFile file recorder = do
129172
let !c' = c + 1
130173
(!n', !nc') = if char' == '\n' then (n + 1, c') else (n, nc)
131174
p@(!_, !_) = if char == c then
132-
(xs, HM.insert name (Position (uint n') (uint (char - nc'))) m)
175+
(xs, HM.insertWith (<>) name [Position (uint n') (uint (char - nc'))] m)
133176
else (x:xs, m)
134177
in (p, (n', nc', c'))
135178
) ((matches, HM.empty), (0, 0, 0))

plugins/hls-notes-plugin/test/NotesTest.hs

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ main :: IO ()
1111
main = defaultTestRunner $
1212
testGroup "Notes"
1313
[ gotoNoteTests
14+
, noteReferenceTests
1415
]
1516

1617
runSessionWithServer' :: FilePath -> (FilePath -> Session a) -> IO a
@@ -21,6 +22,21 @@ runSessionWithServer' fp act =
2122
, testDirLocation = Left fp
2223
} act
2324

25+
noteReferenceTests :: TestTree
26+
noteReferenceTests = testGroup "Note References"
27+
[
28+
testCase "multi_file" $ runSessionWithServer' testDataDir $ \dir -> do
29+
doc <- openDoc "NoteDef.hs" "haskell"
30+
waitForKickDone
31+
refs <- getReferences doc (Position 21 15) False
32+
let fp = dir </> "NoteDef.hs"
33+
liftIO $ refs @?= [
34+
Location (filePathToUri (dir </> "Other.hs")) (Range (Position 6 13) (Position 6 13)),
35+
Location (filePathToUri fp) (Range (Position 9 9) (Position 9 9)),
36+
Location (filePathToUri fp) (Range (Position 5 67) (Position 5 67))
37+
]
38+
]
39+
2440
gotoNoteTests :: TestTree
2541
gotoNoteTests = testGroup "Goto Note Definition"
2642
[
@@ -29,13 +45,13 @@ gotoNoteTests = testGroup "Goto Note Definition"
2945
waitForKickDone
3046
defs <- getDefinitions doc (Position 3 41)
3147
let fp = dir </> "NoteDef.hs"
32-
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 8 9) (Position 8 9))]))
48+
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 11 9) (Position 11 9))]))
3349
, testCase "liberal_format" $ runSessionWithServer' testDataDir $ \dir -> do
3450
doc <- openDoc "NoteDef.hs" "haskell"
3551
waitForKickDone
3652
defs <- getDefinitions doc (Position 5 64)
3753
let fp = dir </> "NoteDef.hs"
38-
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 18 11) (Position 18 11))]))
54+
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 21 11) (Position 21 11))]))
3955

4056
, testCase "invalid_note" $ runSessionWithServer' testDataDir $ const $ do
4157
doc <- openDoc "NoteDef.hs" "haskell"
@@ -54,7 +70,7 @@ gotoNoteTests = testGroup "Goto Note Definition"
5470
waitForKickDone
5571
defs <- getDefinitions doc (Position 5 20)
5672
let fp = dir </> "NoteDef.hs"
57-
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 12 6) (Position 12 6))]))
73+
liftIO $ defs @?= InL (Definition (InR [Location (filePathToUri fp) (Range (Position 15 6) (Position 15 6))]))
5874
]
5975

6076
testDataDir :: FilePath

plugins/hls-notes-plugin/test/testdata/NoteDef.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,9 @@ foo _ = 0 -- We always return zero, see Note [Returning zero from foo]
66
-- The plugin is more liberal with the note definitions, see Note [Single line comments]
77
-- It does not work on wrong note definitions, see Note [Not a valid Note]
88

9+
-- We can also have multiple references to the same note, see
10+
-- Note [Single line comments]
11+
912
{- Note [Returning zero from foo]
1013
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1114
This is a big long form note, with very important info

plugins/hls-notes-plugin/test/testdata/Other.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,3 +4,4 @@ import NoteDef
44

55
bar :: Int
66
bar = 4 -- See @Note [Multiple notes in comment]@ in NoteDef
7+
-- See Note [Single line comments]

0 commit comments

Comments
 (0)