11module Ide.Plugin.Notes (descriptor , Log ) where
22
33import Control.Lens ((^.) )
4- import Control.Monad.Except (throwError )
4+ import Control.Monad.Except (ExceptT , MonadError ,
5+ throwError )
56import Control.Monad.IO.Class (liftIO )
67import qualified Data.Array as A
8+ import Data.Foldable (foldl' )
79import Data.HashMap.Strict (HashMap )
810import qualified Data.HashMap.Strict as HM
911import qualified Data.HashSet as HS
12+ import Data.List (uncons )
1013import Data.Maybe (catMaybes , listToMaybe ,
1114 mapMaybe )
1215import Data.Text (Text , intercalate )
@@ -21,8 +24,8 @@ import GHC.Generics (Generic)
2124import Ide.Plugin.Error (PluginError (.. ))
2225import Ide.Types
2326import 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 ))
2629import Language.LSP.Protocol.Types
2730import Text.Regex.TDFA (Regex , caseSensitive ,
2831 defaultCompOpt ,
@@ -31,25 +34,32 @@ import Text.Regex.TDFA (Regex, caseSensitive,
3134
3235data Log
3336 = LogShake Shake. Log
34- | LogNotesFound NormalizedFilePath [(Text , Position )]
37+ | LogNotesFound NormalizedFilePath [(Text , [Position ])]
38+ | LogNoteReferencesFound NormalizedFilePath [(Text , [Position ])]
3539 deriving Show
3640
3741data 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
4246data GetNotes = MkGetNotes
4347 deriving (Show , Generic , Eq , Ord )
4448 deriving anyclass (Hashable , NFData )
4549type 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+
4756instance 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{-
5565The 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.
5969descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
6070descriptor 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
6577findNotesRules :: 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+
75129jumpToNote :: PluginMethodHandler IdeState Method_TextDocumentDefinition
76130jumpToNote 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
104144jumpToNote _ _ _ = 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 ] ))
107147findNotesInFile 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 ))
0 commit comments