|
1 |
| -module Ide.Plugin.Notes (descriptor) where |
| 1 | +module Ide.Plugin.Notes (descriptor, Log) where |
2 | 2 |
|
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) |
5 | 21 | import Ide.Types
|
| 22 | +import qualified Language.LSP.Server as LSP |
6 | 23 | 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) |
7 | 29 |
|
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 |
12 | 46 | }
|
| 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 |
0 commit comments