Skip to content

Commit f959f67

Browse files
committed
hls-notes-plugin: Add more documentation comments
1 parent 43fa7c0 commit f959f67

File tree

2 files changed

+19
-0
lines changed

2 files changed

+19
-0
lines changed

plugins/hls-notes-plugin/README.md

+2
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,8 @@ module Main where
1111
main :: IO
1212
main = do
1313
doSomething -- We need this here, see Note [Do Something] in Foo
14+
-- Using at-signs around the note works as well:
15+
-- see @Note [Do Something]@ in Foo
1416
```
1517

1618
Foo.hs

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

+17
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,11 @@ instance Pretty Log where
5454
"Found notes in " <> pretty (show file) <> ": ["
5555
<> pretty (intercalate ", " (fmap (\(s, p) -> "\"" <> s <> "\" at " <> T.pack (show p)) notes)) <> "]"
5656

57+
{-
58+
The first time the user requests a jump-to-definition on a note reference, the
59+
project is indexed and searched for all note definitions. Their location and
60+
title is then saved in the HLS database to be retrieved for all future requests.
61+
-}
5762
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
5863
descriptor recorder plId = (defaultPluginDescriptor plId)
5964
{ Ide.Types.pluginRules = findNotesRules recorder
@@ -89,12 +94,18 @@ jumpToNote state _ param
8994
uriOrig = toNormalizedUri $ param ^. (L.textDocument . L.uri)
9095
err s = maybe (throwError $ PluginInternalError s) pure
9196
atPos c arr = case arr A.! 0 of
97+
-- We check if the line we are currently at contains a note
98+
-- reference. However, we need to know if the cursor is within the
99+
-- match or somewhere else. The second entry of the array contains
100+
-- the title of the note as extracted by the regex.
92101
(_, (c', len)) -> if c' <= c && c <= c' + len
93102
then Just (fst (arr A.! 1)) else Nothing
94103
jumpToNote _ _ _ = throwError $ PluginInternalError "conversion to normalized file path failed"
95104

96105
findNotesInFile :: NormalizedFilePath -> Recorder (WithPriority Log) -> Action (Maybe (HM.HashMap Text Position))
97106
findNotesInFile file recorder = do
107+
-- GetFileContents only returns a value if the file is open in the editor of
108+
-- the user. If not, we need to read it from disk.
98109
contentOpt <- (snd =<<) <$> use GetFileContents file
99110
content <- case contentOpt of
100111
Just x -> pure x
@@ -105,6 +116,12 @@ findNotesInFile file recorder = do
105116
pure $ Just m
106117
where
107118
uint = fromIntegral . toInteger
119+
-- the regex library returns the character index of the match. However
120+
-- to return the position from HLS we need it as a (line, character)
121+
-- tuple. To convert between the two we count the newline characters and
122+
-- reset the current character index every time. For every regex match,
123+
-- once we have counted up to their character index, we save the current
124+
-- line and character values instead.
108125
toPositions matches = snd . fst . T.foldl' (\case
109126
(([], m), _) -> const (([], m), (0, 0, 0))
110127
((x@(name, (char, _)):xs, m), (n, nc, c)) -> \char' ->

0 commit comments

Comments
 (0)