@@ -12,7 +12,7 @@ import Control.DeepSeq
1212import Control.Lens ((^.) )
1313import Control.Monad.Extra
1414import Control.Monad.IO.Class
15- import Control.Monad.Trans.Class ( lift )
15+ import Control.Monad.Trans.Class
1616import Control.Monad.Trans.Maybe (runMaybeT )
1717import qualified Data.ByteString as BS
1818import Data.Hashable
@@ -27,12 +27,17 @@ import qualified Development.IDE.Core.Shake as Shake
2727import Development.IDE.Graph (alwaysRerun )
2828import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
2929import qualified Development.IDE.Plugin.Completions.Types as Ghcide
30+ import qualified Distribution.Fields as Syntax
31+ import qualified Distribution.Parsec.Position as Syntax
3032import GHC.Generics
3133import qualified Ide.Plugin.Cabal.Completion.Completer.Types as CompleterTypes
3234import qualified Ide.Plugin.Cabal.Completion.Completions as Completions
35+ import Ide.Plugin.Cabal.Completion.Types (ParseCabalFields (.. ),
36+ ParseCabalFile (.. ))
3337import qualified Ide.Plugin.Cabal.Completion.Types as Types
3438import qualified Ide.Plugin.Cabal.Diagnostics as Diagnostics
3539import qualified Ide.Plugin.Cabal.LicenseSuggest as LicenseSuggest
40+ import Ide.Plugin.Cabal.Orphans ()
3641import qualified Ide.Plugin.Cabal.Parse as Parse
3742import Ide.Types
3843import qualified Language.LSP.Protocol.Lens as JL
@@ -70,7 +75,7 @@ instance Pretty Log where
7075 " Set files of interest to:" <+> viaShow files
7176 LogCompletionContext context position ->
7277 " Determined completion context:"
73- <+> viaShow context
78+ <+> pretty context
7479 <+> " for cursor position:"
7580 <+> pretty position
7681 LogCompletions logs -> pretty logs
@@ -144,30 +149,55 @@ cabalRules recorder plId = do
144149 -- Make sure we initialise the cabal files-of-interest.
145150 ofInterestRules recorder
146151 -- Rule to produce diagnostics for cabal files.
147- define (cmapWithPrio LogShake recorder) $ \ Types. GetCabalDiagnostics file -> do
152+ define (cmapWithPrio LogShake recorder) $ \ ParseCabalFields file -> do
148153 config <- getPluginConfigAction plId
149154 if not (plcGlobalOn config && plcDiagnosticsOn config)
150- then pure ([] , Nothing )
151- else do
152- -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
153- -- we rerun this rule because this rule *depends* on GetModificationTime.
154- (t, mCabalSource) <- use_ GetFileContents file
155- log' Debug $ LogModificationTime file t
156- contents <- case mCabalSource of
157- Just sources ->
158- pure $ Encoding. encodeUtf8 sources
159- Nothing -> do
160- liftIO $ BS. readFile $ fromNormalizedFilePath file
161-
162- (pWarnings, pm) <- liftIO $ Parse. parseCabalFileContents contents
163- let warningDiags = fmap (Diagnostics. warningDiagnostic file) pWarnings
164- case pm of
165- Left (_cabalVersion, pErrorNE) -> do
166- let errorDiags = NE. toList $ NE. map (Diagnostics. errorDiagnostic file) pErrorNE
167- allDiags = errorDiags <> warningDiags
168- pure (allDiags, Nothing )
169- Right gpd -> do
170- pure (warningDiags, Just gpd)
155+ then pure ([] , Nothing )
156+ else do
157+ -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
158+ -- we rerun this rule because this rule *depends* on GetModificationTime.
159+ (t, mCabalSource) <- use_ GetFileContents file
160+ log' Debug $ LogModificationTime file t
161+ contents <- case mCabalSource of
162+ Just sources ->
163+ pure $ Encoding. encodeUtf8 sources
164+ Nothing -> do
165+ liftIO $ BS. readFile $ fromNormalizedFilePath file
166+
167+ case Parse. readCabalFields file contents of
168+ Left _ ->
169+ pure ([] , Nothing )
170+ Right fields ->
171+ pure ([] , Just fields)
172+
173+ define (cmapWithPrio LogShake recorder) $ \ ParseCabalFile file -> do
174+ config <- getPluginConfigAction plId
175+ if not (plcGlobalOn config && plcDiagnosticsOn config)
176+ then pure ([] , Nothing )
177+ else do
178+ -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
179+ -- we rerun this rule because this rule *depends* on GetModificationTime.
180+ (t, mCabalSource) <- use_ GetFileContents file
181+ log' Debug $ LogModificationTime file t
182+ contents <- case mCabalSource of
183+ Just sources ->
184+ pure $ Encoding. encodeUtf8 sources
185+ Nothing -> do
186+ liftIO $ BS. readFile $ fromNormalizedFilePath file
187+
188+ -- Instead of fully reparsing the sources to get a 'GenericPackageDescription',
189+ -- we would much rather re-use the already parsed results of 'ParseCabalFields'.
190+ -- Unfortunately, Cabal-syntax doesn't expose the function 'parseGenericPackageDescription''
191+ -- which allows us to resume the parsing pipeline with '[Field Position]'.
192+ (pWarnings, pm) <- liftIO $ Parse. parseCabalFileContents contents
193+ let warningDiags = fmap (Diagnostics. warningDiagnostic file) pWarnings
194+ case pm of
195+ Left (_cabalVersion, pErrorNE) -> do
196+ let errorDiags = NE. toList $ NE. map (Diagnostics. errorDiagnostic file) pErrorNE
197+ allDiags = errorDiags <> warningDiags
198+ pure (allDiags, Nothing )
199+ Right gpd -> do
200+ pure (warningDiags, Just gpd)
171201
172202 action $ do
173203 -- Run the cabal kick. This code always runs when 'shakeRestart' is run.
@@ -187,7 +217,7 @@ function invocation.
187217kick :: Action ()
188218kick = do
189219 files <- HashMap. keys <$> getCabalFilesOfInterestUntracked
190- void $ uses Types. GetCabalDiagnostics files
220+ void $ uses Types. ParseCabalFile files
191221
192222-- ----------------------------------------------------------------
193223-- Code Actions
@@ -278,24 +308,31 @@ completion :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.M
278308completion recorder ide _ complParams = do
279309 let (TextDocumentIdentifier uri) = complParams ^. JL. textDocument
280310 position = complParams ^. JL. position
281- contents <- lift $ getVirtualFile $ toNormalizedUri uri
282- case (contents, uriToFilePath' uri) of
283- (Just cnts, Just path) -> do
284- let pref = Ghcide. getCompletionPrefix position cnts
285- let res = result pref path cnts
286- liftIO $ fmap InL res
287- _ -> pure . InR $ InR Null
311+ mVf <- lift $ getVirtualFile $ toNormalizedUri uri
312+ case (,) <$> mVf <*> uriToFilePath' uri of
313+ Just (cnts, path) -> do
314+ mFields <- liftIO $ runIdeAction " cabal-plugin.fields" (shakeExtras ide) $ useWithStaleFast ParseCabalFields $ toNormalizedFilePath path
315+ case mFields of
316+ Nothing ->
317+ pure . InR $ InR Null
318+ Just (fields, _) -> do
319+ let pref = Ghcide. getCompletionPrefix position cnts
320+ let res = produceCompletions pref path fields
321+ liftIO $ fmap InL res
322+ Nothing -> pure . InR $ InR Null
288323 where
289- result :: Ghcide. PosPrefixInfo -> FilePath -> VFS. VirtualFile -> IO [CompletionItem ]
290- result prefix fp cnts = do
291- runMaybeT context >>= \ case
324+ completerRecorder = cmapWithPrio LogCompletions recorder
325+
326+ produceCompletions :: Ghcide. PosPrefixInfo -> FilePath -> [Syntax. Field Syntax. Position ] -> IO [CompletionItem ]
327+ produceCompletions prefix fp fields = do
328+ runMaybeT (context fields) >>= \ case
292329 Nothing -> pure []
293330 Just ctx -> do
294331 logWith recorder Debug $ LogCompletionContext ctx pos
295332 let completer = Completions. contextToCompleter ctx
296333 let completerData = CompleterTypes. CompleterData
297334 { getLatestGPD = do
298- mGPD <- runIdeAction " cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast Types. GetCabalDiagnostics $ toNormalizedFilePath fp
335+ mGPD <- runIdeAction " cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast ParseCabalFile $ toNormalizedFilePath fp
299336 pure $ fmap fst mGPD
300337 , cabalPrefixInfo = prefInfo
301338 , stanzaName =
@@ -306,7 +343,6 @@ completion recorder ide _ complParams = do
306343 completions <- completer completerRecorder completerData
307344 pure completions
308345 where
309- completerRecorder = cmapWithPrio LogCompletions recorder
310346 pos = Ghcide. cursorPos prefix
311- context = Completions. getContext completerRecorder prefInfo (cnts ^. VFS. file_text)
347+ context fields = Completions. getContext completerRecorder prefInfo fields
312348 prefInfo = Completions. getCabalPrefixInfo fp prefix
0 commit comments