Skip to content

Commit b3ba0c4

Browse files
committed
hls-notes-plugin: Find notes at index time and cache
1 parent 029303b commit b3ba0c4

File tree

7 files changed

+124
-117
lines changed

7 files changed

+124
-117
lines changed

flake.lock

Lines changed: 9 additions & 9 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

plugins/hls-notes-plugin/hls-notes-plugin.cabal

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -23,11 +23,9 @@ common warnings
2323

2424
library
2525
import: warnings
26-
other-modules:
27-
Ide.Plugin.Notes.Internal
2826
exposed-modules: Ide.Plugin.Notes
2927
build-depends:
30-
, base >=4.16 && <5
28+
, base >=4.12 && <5
3129
, array
3230
, bytestring
3331
, ghcide
@@ -37,13 +35,17 @@ library
3735
, hls-graph
3836
, regex-tdfa ^>= 1.3.1
3937
, text
38+
, text-rope
39+
, transformers
40+
, unordered-containers
4041
hs-source-dirs: src
4142
default-language: GHC2021
4243
default-extensions:
4344
DataKinds
45+
ExplicitNamespaces
4446
LambdaCase
4547
OverloadedStrings
46-
ExplicitNamespaces
48+
TypeFamilies
4749

4850
test-suite tests
4951
import: warnings
Lines changed: 99 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,104 @@
1-
module Ide.Plugin.Notes (descriptor) where
1+
module Ide.Plugin.Notes (descriptor, Log) where
22

3-
import Development.IDE
4-
import qualified Ide.Plugin.Notes.Internal as X
3+
import Control.Lens (ix, (^.), (^?))
4+
import Control.Monad.IO.Class (liftIO)
5+
import Control.Monad.Trans.Class (lift)
6+
import qualified Data.Array as A
7+
import Data.HashMap.Strict (HashMap)
8+
import qualified Data.HashMap.Strict as HM
9+
import Data.Maybe (listToMaybe, mapMaybe)
10+
import Data.Text (Text, intercalate)
11+
import qualified Data.Text as T
12+
import qualified Data.Text.Utf16.Rope as Rope
13+
import Data.Typeable (Typeable)
14+
import Development.IDE hiding (line)
15+
import qualified Development.IDE.Core.Shake as Shake
16+
import Development.IDE.Graph.Classes (Hashable, NFData)
17+
import GHC.Generics (Generic)
18+
import Ide.PluginUtils (getNormalizedFilePath,
19+
pluginResponse,
20+
throwPluginError)
521
import Ide.Types
22+
import qualified Language.LSP.Server as LSP
623
import Language.LSP.Types
24+
import qualified Language.LSP.Types.Lens as L
25+
import Language.LSP.VFS (VirtualFile (..))
26+
import Text.Regex.TDFA (Regex, caseSensitive,
27+
defaultCompOpt, defaultExecOpt,
28+
makeRegexOpts, matchAllText)
729

8-
descriptor :: PluginId -> PluginDescriptor IdeState
9-
descriptor plId = (defaultPluginDescriptor plId)
10-
{ Ide.Types.pluginHandlers =
11-
mkPluginHandler STextDocumentDefinition X.jumpToNote
30+
data Log
31+
= LogShake Shake.Log
32+
| LogNotesFound [Text]
33+
deriving Show
34+
35+
instance Pretty Log where
36+
pretty = \case
37+
LogShake l -> pretty l
38+
LogNotesFound notes ->
39+
"Found notes: ["
40+
<> pretty (intercalate ", " (fmap (\s -> "\"" <> s <> "\"") notes)) <> "]"
41+
42+
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
43+
descriptor recorder plId = (defaultPluginDescriptor plId)
44+
{ Ide.Types.pluginHandlers = mkPluginHandler STextDocumentDefinition jumpToNote
45+
, Ide.Types.pluginRules = findNotesRules recorder
1246
}
47+
48+
jumpToNote :: PluginMethodHandler IdeState TextDocumentDefinition
49+
jumpToNote state _ param = pluginResponse $ do
50+
let uriOrig = param ^. (L.textDocument . L.uri)
51+
Position l c = param ^. L.position
52+
nfp <- getNormalizedFilePath uriOrig
53+
contents <- fmap _file_text . err "Error getting file contents"
54+
=<< lift (LSP.getVirtualFile (toNormalizedUri uriOrig))
55+
line <- err "Line not found in file" (Rope.lines contents ^? ix (fromIntegral l))
56+
note <- err "No note at this position" $ listToMaybe $
57+
mapMaybe (atPos $ fromIntegral c) $ matchAllText noteRefRegex line
58+
allNotes <- err "No notes found in file" =<<
59+
liftIO (runAction "Notes.getNotes" state $ use MkNoteDefinitions nfp)
60+
pos <- err "Note not found" (HM.lookup note allNotes)
61+
pure $ InL (Location uriOrig (Range pos pos))
62+
where
63+
err s = maybe (throwPluginError s) pure
64+
atPos c arr = case arr A.! 0 of
65+
(_, (c', len)) -> if c' <= c && c <= c' + len
66+
then Just (fst (arr A.! 1)) else Nothing
67+
68+
data NoteDefinitions = MkNoteDefinitions
69+
deriving (Eq, Show, Typeable, Generic)
70+
instance Hashable NoteDefinitions
71+
instance NFData NoteDefinitions
72+
73+
type instance RuleResult NoteDefinitions = HashMap Text Position
74+
75+
findNotesRules :: Recorder (WithPriority Log) -> Rules ()
76+
findNotesRules recorder = do
77+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \MkNoteDefinitions file -> do
78+
content <- snd <$> use_ GetFileContents file
79+
let m = do
80+
c <- content
81+
let matches = (A.! 1) <$> matchAllText noteRegex c
82+
pure $ toPositions matches c
83+
logWith recorder Debug $ LogNotesFound (maybe [] HM.keys m)
84+
pure m
85+
where
86+
uint = fromIntegral . toInteger
87+
toPositions matches = snd . fst . T.foldl' (\case
88+
(([], m), _) -> const (([], m), (0, 0, 0))
89+
((x@(name, (char, _)):xs, m), (n, nc, c)) -> \char' ->
90+
let !c' = c + 1
91+
(!n', !nc') = if char' == '\n' then (n + 1, c') else (n, nc)
92+
p = if char == c then
93+
(xs, HM.insert name (Position (uint n') (uint (char - nc'))) m)
94+
else (x:xs, m)
95+
in (p, (n', nc', c'))
96+
) ((matches, HM.empty), (0, 0, 0))
97+
98+
noteRefRegex, noteRegex :: Regex
99+
(noteRefRegex, noteRegex) =
100+
( mkReg ("note \\[(.+)\\]( in (([A-Za-z0-9]+\\.)*[A-Za-z0-9]+))?" :: String)
101+
, mkReg ("note \\[([[:print:]]+)\\][[:blank:]]*[[:space:]][[:space:]]?~~~" :: String)
102+
)
103+
where
104+
mkReg = makeRegexOpts (defaultCompOpt { caseSensitive = False }) defaultExecOpt

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

Lines changed: 0 additions & 89 deletions
This file was deleted.

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,12 @@
11
module Main (main) where
22

3-
import Ide.Plugin.Notes (descriptor)
3+
import Ide.Plugin.Notes (Log, descriptor)
44
import System.Directory (canonicalizePath)
55
import System.FilePath ((</>))
66
import Test.Hls
77

8-
plugin :: PluginTestDescriptor ()
9-
plugin = mkPluginTestDescriptor' descriptor "notes"
8+
plugin :: PluginTestDescriptor Log
9+
plugin = mkPluginTestDescriptor descriptor "notes"
1010

1111
main :: IO ()
1212
main = defaultTestRunner $
@@ -21,7 +21,7 @@ gotoNoteTests = testGroup "Goto Note Definition"
2121
defs <- getDefinitions doc (Position 3 41)
2222
liftIO $ do
2323
fp <- canonicalizePath "NoteDef.hs"
24-
defs @?= InL [Location (filePathToUri fp) (Range (Position 7 0) (Position 7 0))]
24+
defs @?= InL [Location (filePathToUri fp) (Range (Position 5 9) (Position 5 9))]
2525
, testCase "no_note" $ runSessionWithServer plugin testDataDir $ do
2626
doc <- openDoc "NoteDef.hs" "haskell"
2727
defs <- getDefinitions doc (Position 1 0)

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

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,12 @@ module NoteDef (foo) where
33
foo :: Int -> Int
44
foo _ = 0 -- We always return zero, see Note [Returning zero from foo]
55

6-
{-
7-
8-
Note [Returning zero from foo]
6+
{- Note [Returning zero from foo]
97
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
108
This is a big long form note, with very important info
119
10+
Note [Multiple notes in comment]
11+
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
12+
This is also a very common thing to do for GHC
13+
1214
-}

src/HlsPlugins.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -243,7 +243,7 @@ idePlugins recorder = pluginDescToIdePlugins allPlugins
243243
let pId = "overloaded-record-dot" in OverloadedRecordDot.descriptor (pluginRecorder pId) pId :
244244
#endif
245245
#if hls_notes
246-
Notes.descriptor "notes" :
246+
let pId = "notes" in Notes.descriptor (pluginRecorder pId) pId :
247247
#endif
248248
GhcIde.descriptors (pluginRecorder "ghcide")
249249

0 commit comments

Comments
 (0)