Skip to content

Commit 0829e02

Browse files
Fix notes plugin: avoid exceptions on missing note definitions and handle lookups safely
1 parent 3a2b23e commit 0829e02

File tree

1 file changed

+84
-38
lines changed
  • plugins/hls-notes-plugin/src/Ide/Plugin

1 file changed

+84
-38
lines changed

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

Lines changed: 84 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
11
module Ide.Plugin.Notes (descriptor, Log) where
22

33
import Control.Lens ((^.))
4-
import Control.Monad.Except (ExceptT, MonadError,
5-
throwError)
4+
import Control.Monad.Except (ExceptT)
65
import Control.Monad.IO.Class (liftIO)
76
import qualified Data.Array as A
87
import Data.Foldable (foldl')
@@ -11,13 +10,13 @@ import qualified Data.HashMap.Strict as HM
1110
import qualified Data.HashSet as HS
1211
import Data.List (uncons)
1312
import Data.Maybe (catMaybes, listToMaybe,
14-
mapMaybe)
13+
mapMaybe, fromMaybe)
1514
import Data.Text (Text, intercalate)
1615
import qualified Data.Text as T
1716
import qualified Data.Text.Utf16.Rope.Mixed as Rope
1817
import Data.Traversable (for)
1918
import Development.IDE hiding (line)
20-
import Development.IDE.Core.PluginUtils (runActionE, useE)
19+
2120
import Development.IDE.Core.Shake (toKnownFiles)
2221
import qualified Development.IDE.Core.Shake as Shake
2322
import Development.IDE.Graph.Classes (Hashable, NFData)
@@ -63,11 +62,12 @@ type instance RuleResult GetNoteReferences = HashMap Text [(NormalizedFilePath,
6362

6463
instance Pretty Log where
6564
pretty = \case
66-
LogShake l -> pretty l
67-
LogNoteReferencesFound file refs -> "Found note references in " <> prettyNotes file refs
68-
LogNotesFound file notes -> "Found notes in " <> prettyNotes file notes
69-
where prettyNotes file hm = pretty (show file) <> ": ["
70-
<> pretty (intercalate ", " (fmap (\(s, p) -> "\"" <> s <> "\" at " <> intercalate ", " (map (T.pack . show) p)) hm)) <> "]"
65+
LogShake l -> pretty l
66+
LogNoteReferencesFound file refs -> "Found note references in " <> prettyNotes file refs
67+
LogNotesFound file notes -> "Found notes in " <> prettyNotes file notes
68+
where
69+
prettyNotes file hm = pretty (show file) <> ": ["
70+
<> pretty (intercalate ", " (fmap (\(s, p) -> "\"" <> s <> "\" at " <> intercalate ", " (map (T.pack . show) p)) hm)) <> "]"
7171

7272
{-
7373
The first time the user requests a jump-to-definition on a note reference, the
@@ -100,25 +100,36 @@ findNotesRules recorder = do
100100
)
101101
pure $ Just $ foldl' (HM.unionWith (<>)) HM.empty definedReferences
102102

103-
err :: MonadError PluginError m => Text -> Maybe a -> m a
104-
err s = maybe (throwError $ PluginInternalError s) pure
105103

106104
getNote :: NormalizedFilePath -> IdeState -> Position -> ExceptT PluginError (HandlerM c) (Maybe Text)
107105
getNote nfp state (Position l c) = do
108-
contents <-
109-
err "Error getting file contents"
110-
=<< liftIO (runAction "notes.getfileContents" state (getFileContents nfp))
111-
line <- err "Line not found in file" (listToMaybe $ Rope.lines $ fst
112-
(Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) contents))
113-
pure $ listToMaybe $ mapMaybe (atPos $ fromIntegral c) $ matchAllText noteRefRegex line
106+
mContents <- liftIO (runAction "notes.getfileContents" state (getFileContents nfp))
107+
case mContents of
108+
Nothing ->
109+
110+
pure Nothing
111+
112+
Just contents -> do
113+
114+
let ropeLine = snd $ Rope.splitAtLine (fromIntegral l) contents
115+
mLine = listToMaybe $ Rope.lines $ fst (Rope.splitAtLine 1 ropeLine)
116+
117+
case mLine of
118+
Nothing -> pure Nothing
119+
Just ln ->
120+
121+
pure $
122+
listToMaybe $
123+
mapMaybe (atPos (fromIntegral c)) $
124+
matchAllText noteRefRegex ln
114125
where
115-
atPos c arr = case arr A.! 0 of
116-
-- We check if the line we are currently at contains a note
117-
-- reference. However, we need to know if the cursor is within the
118-
-- match or somewhere else. The second entry of the array contains
119-
-- the title of the note as extracted by the regex.
120-
(_, (c', len)) -> if c' <= c && c <= c' + len
121-
then Just (fst (arr A.! 1)) else Nothing
126+
127+
atPos cur arr =
128+
let (_, (start, len)) = arr A.! 0
129+
in if start <= cur && cur <= start + len
130+
then Just (fst (arr A.! 1))
131+
else Nothing
132+
122133

123134
listReferences :: PluginMethodHandler IdeState Method_TextDocumentReferences
124135
listReferences state _ param
@@ -127,32 +138,67 @@ listReferences state _ param
127138
let pos@(Position l _) = param ^. L.position
128139
noteOpt <- getNote nfp state pos
129140
case noteOpt of
130-
Nothing -> pure (InR Null)
141+
Nothing ->
142+
143+
pure (InR Null)
144+
131145
Just note -> do
132-
notes <- runActionE "notes.definedNoteReferencess" state $ useE MkGetNoteReferences nfp
133-
poss <- err ("Note reference (a comment of the form `{- Note [" <> note <> "] -}`) not found") (HM.lookup note notes)
134-
pure $ InL (mapMaybe (\(noteFp, pos@(Position l' _)) -> if l' == l then Nothing else Just (
135-
Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))) poss)
146+
mNotes <- liftIO $ runAction "notes.definedNoteReferencess" state (use MkGetNoteReferences nfp)
147+
148+
let notes = fromMaybe HM.empty mNotes
149+
150+
case HM.lookup note notes of
151+
Nothing ->
152+
153+
pure (InR Null)
154+
155+
Just poss ->
156+
pure $ InL $
157+
mapMaybe
158+
(\(noteFp, pos@(Position l' _)) ->
159+
if l' == l
160+
then Nothing
161+
else Just (Location (fromNormalizedUri $ normalizedFilePathToUri noteFp)
162+
(Range pos pos)))
163+
poss
136164
where
137165
uriOrig = toNormalizedUri $ param ^. (L.textDocument . L.uri)
138-
listReferences _ _ _ = throwError $ PluginInternalError "conversion to normalized file path failed"
166+
167+
listReferences _ _ _ =
168+
169+
pure (InR Null)
170+
139171

140172
jumpToNote :: PluginMethodHandler IdeState Method_TextDocumentDefinition
141173
jumpToNote state _ param
142174
| Just nfp <- uriToNormalizedFilePath uriOrig
143175
= do
144176
noteOpt <- getNote nfp state (param ^. L.position)
145177
case noteOpt of
146-
Nothing -> pure (InR (InR Null))
178+
Nothing ->
179+
180+
pure (InR (InR Null))
181+
147182
Just note -> do
148-
notes <- runActionE "notes.definedNotes" state $ useE MkGetNotes nfp
149-
(noteFp, pos) <- err ("Note definition (a comment of the form `{- Note [" <> note <> "]\\n~~~ ... -}`) not found") (HM.lookup note notes)
150-
pure $ InL (Definition (InL
151-
(Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))
152-
))
183+
mNotes <- liftIO $ runAction "notes.definedNotes" state (use MkGetNotes nfp)
184+
185+
let notes = fromMaybe HM.empty mNotes
186+
187+
case HM.lookup note notes of
188+
Nothing ->
189+
190+
pure (InR (InR Null))
191+
192+
Just (noteFp, pos) ->
193+
pure $ InL $ Definition $ InL
194+
(Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))
153195
where
154196
uriOrig = toNormalizedUri $ param ^. (L.textDocument . L.uri)
155-
jumpToNote _ _ _ = throwError $ PluginInternalError "conversion to normalized file path failed"
197+
198+
jumpToNote _ _ _ =
199+
200+
pure (InR (InR Null))
201+
156202

157203
findNotesInFile :: NormalizedFilePath -> Recorder (WithPriority Log) -> Action (Maybe (HM.HashMap Text Position, HM.HashMap Text [Position]))
158204
findNotesInFile file recorder = do
@@ -194,4 +240,4 @@ noteRefRegex, noteRegex :: Regex
194240
, mkReg ("note \\[([[:print:]]+)\\][[:blank:]]*\r?\n[[:blank:]]*(--)?[[:blank:]]*~~~" :: String)
195241
)
196242
where
197-
mkReg = makeRegexOpts (defaultCompOpt { caseSensitive = False }) defaultExecOpt
243+
mkReg = makeRegexOpts (defaultCompOpt { caseSensitive = False }) defaultExecOpt

0 commit comments

Comments
 (0)