11module Ide.Plugin.Notes (descriptor , Log ) where
22
33import Control.Lens ((^.) )
4- import Control.Monad.Except (ExceptT )
4+ import Control.Monad.Except (ExceptT , MonadError ,
5+ throwError )
56import Control.Monad.IO.Class (liftIO )
67import qualified Data.Array as A
78import Data.Foldable (foldl' )
@@ -10,13 +11,13 @@ import qualified Data.HashMap.Strict as HM
1011import qualified Data.HashSet as HS
1112import Data.List (uncons )
1213import Data.Maybe (catMaybes , listToMaybe ,
13- mapMaybe , fromMaybe )
14+ mapMaybe )
1415import Data.Text (Text , intercalate )
1516import qualified Data.Text as T
1617import qualified Data.Text.Utf16.Rope.Mixed as Rope
1718import Data.Traversable (for )
1819import Development.IDE hiding (line )
19-
20+ import Development.IDE.Core.PluginUtils ( runActionE , useE )
2021import Development.IDE.Core.Shake (toKnownFiles )
2122import qualified Development.IDE.Core.Shake as Shake
2223import Development.IDE.Graph.Classes (Hashable , NFData )
@@ -62,12 +63,11 @@ type instance RuleResult GetNoteReferences = HashMap Text [(NormalizedFilePath,
6263
6364instance Pretty Log where
6465 pretty = \ case
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)) <> " ]"
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)) <> " ]"
7171
7272{-
7373The first time the user requests a jump-to-definition on a note reference, the
@@ -100,36 +100,25 @@ 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
103105
104106getNote :: NormalizedFilePath -> IdeState -> Position -> ExceptT PluginError (HandlerM c ) (Maybe Text )
105107getNote nfp state (Position l c) = do
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
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
125114 where
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-
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
133122
134123listReferences :: PluginMethodHandler IdeState Method_TextDocumentReferences
135124listReferences state _ param
@@ -138,67 +127,38 @@ listReferences state _ param
138127 let pos@ (Position l _) = param ^. L. position
139128 noteOpt <- getNote nfp state pos
140129 case noteOpt of
141- Nothing ->
142-
143- pure (InR Null )
144-
130+ Nothing -> pure (InR Null )
145131 Just note -> do
146- mNotes <- liftIO $ runAction " notes.definedNoteReferencess" state (use MkGetNoteReferences nfp)
147-
148- let notes = fromMaybe HM. empty mNotes
149-
132+ notes <- runActionE " notes.definedNoteReferencess" state $ useE MkGetNoteReferences nfp
150133 case HM. lookup note notes of
151- Nothing ->
152-
153- pure (InR Null )
154-
134+ Nothing -> pure (InR Null )
155135 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
136+ pure $ InL (mapMaybe (\ (noteFp, pos@ (Position l' _)) ->
137+ if l' == l then Nothing
138+ else Just (Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))
139+ ) poss)
164140 where
165141 uriOrig = toNormalizedUri $ param ^. (L. textDocument . L. uri)
166-
167- listReferences _ _ _ =
168-
169- pure (InR Null )
170-
142+ listReferences _ _ _ = throwError $ PluginInternalError " conversion to normalized file path failed"
171143
172144jumpToNote :: PluginMethodHandler IdeState Method_TextDocumentDefinition
173145jumpToNote state _ param
174146 | Just nfp <- uriToNormalizedFilePath uriOrig
175147 = do
176148 noteOpt <- getNote nfp state (param ^. L. position)
177149 case noteOpt of
178- Nothing ->
179-
180- pure (InR (InR Null ))
181-
150+ Nothing -> pure (InR (InR Null ))
182151 Just note -> do
183- mNotes <- liftIO $ runAction " notes.definedNotes" state (use MkGetNotes nfp)
184-
185- let notes = fromMaybe HM. empty mNotes
186-
152+ notes <- runActionE " notes.definedNotes" state $ useE MkGetNotes nfp
187153 case HM. lookup note notes of
188- Nothing ->
189-
190- pure (InR (InR Null ))
191-
154+ Nothing -> pure (InR (InR Null ))
192155 Just (noteFp, pos) ->
193- pure $ InL $ Definition $ InL
156+ pure $ InL ( Definition ( InL
194157 (Location (fromNormalizedUri $ normalizedFilePathToUri noteFp) (Range pos pos))
158+ ))
195159 where
196160 uriOrig = toNormalizedUri $ param ^. (L. textDocument . L. uri)
197-
198- jumpToNote _ _ _ =
199-
200- pure (InR (InR Null ))
201-
161+ jumpToNote _ _ _ = throwError $ PluginInternalError " conversion to normalized file path failed"
202162
203163findNotesInFile :: NormalizedFilePath -> Recorder (WithPriority Log ) -> Action (Maybe (HM. HashMap Text Position , HM. HashMap Text [Position ]))
204164findNotesInFile file recorder = do
0 commit comments