@@ -11,7 +11,7 @@ import Control.DeepSeq
1111import Control.Lens ((^.) )
1212import Control.Monad.Extra
1313import Control.Monad.IO.Class
14- import Control.Monad.Trans.Class ( lift )
14+ import Control.Monad.Trans.Class
1515import Control.Monad.Trans.Maybe (runMaybeT )
1616import qualified Data.ByteString as BS
1717import Data.Hashable
@@ -27,12 +27,17 @@ import Development.IDE.Graph (Key, alwaysRerun)
2727import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
2828import qualified Development.IDE.Plugin.Completions.Types as Ghcide
2929import Development.IDE.Types.Shake (toKey )
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
@@ -145,30 +150,55 @@ cabalRules recorder plId = do
145150 -- Make sure we initialise the cabal files-of-interest.
146151 ofInterestRules recorder
147152 -- Rule to produce diagnostics for cabal files.
148- define (cmapWithPrio LogShake recorder) $ \ Types. GetCabalDiagnostics file -> do
153+ define (cmapWithPrio LogShake recorder) $ \ ParseCabalFields file -> do
149154 config <- getPluginConfigAction plId
150155 if not (plcGlobalOn config && plcDiagnosticsOn config)
151- then pure ([] , Nothing )
152- else do
153- -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
154- -- we rerun this rule because this rule *depends* on GetModificationTime.
155- (t, mCabalSource) <- use_ GetFileContents file
156- log' Debug $ LogModificationTime file t
157- contents <- case mCabalSource of
158- Just sources ->
159- pure $ Encoding. encodeUtf8 sources
160- Nothing -> do
161- liftIO $ BS. readFile $ fromNormalizedFilePath file
162-
163- (pWarnings, pm) <- liftIO $ Parse. parseCabalFileContents contents
164- let warningDiags = fmap (Diagnostics. warningDiagnostic file) pWarnings
165- case pm of
166- Left (_cabalVersion, pErrorNE) -> do
167- let errorDiags = NE. toList $ NE. map (Diagnostics. errorDiagnostic file) pErrorNE
168- allDiags = errorDiags <> warningDiags
169- pure (allDiags, Nothing )
170- Right gpd -> do
171- pure (warningDiags, Just gpd)
156+ then pure ([] , Nothing )
157+ else do
158+ -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
159+ -- we rerun this rule because this rule *depends* on GetModificationTime.
160+ (t, mCabalSource) <- use_ GetFileContents file
161+ log' Debug $ LogModificationTime file t
162+ contents <- case mCabalSource of
163+ Just sources ->
164+ pure $ Encoding. encodeUtf8 sources
165+ Nothing -> do
166+ liftIO $ BS. readFile $ fromNormalizedFilePath file
167+
168+ case Parse. readCabalFields file contents of
169+ Left _ ->
170+ pure ([] , Nothing )
171+ Right fields ->
172+ pure ([] , Just fields)
173+
174+ define (cmapWithPrio LogShake recorder) $ \ ParseCabalFile file -> do
175+ config <- getPluginConfigAction plId
176+ if not (plcGlobalOn config && plcDiagnosticsOn config)
177+ then pure ([] , Nothing )
178+ else do
179+ -- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
180+ -- we rerun this rule because this rule *depends* on GetModificationTime.
181+ (t, mCabalSource) <- use_ GetFileContents file
182+ log' Debug $ LogModificationTime file t
183+ contents <- case mCabalSource of
184+ Just sources ->
185+ pure $ Encoding. encodeUtf8 sources
186+ Nothing -> do
187+ liftIO $ BS. readFile $ fromNormalizedFilePath file
188+
189+ -- Instead of fully reparsing the sources to get a 'GenericPackageDescription',
190+ -- we would much rather re-use the already parsed results of 'ParseCabalFields'.
191+ -- Unfortunately, Cabal-syntax doesn't expose the function 'parseGenericPackageDescription''
192+ -- which allows us to resume the parsing pipeline with '[Field Position]'.
193+ (pWarnings, pm) <- liftIO $ Parse. parseCabalFileContents contents
194+ let warningDiags = fmap (Diagnostics. warningDiagnostic file) pWarnings
195+ case pm of
196+ Left (_cabalVersion, pErrorNE) -> do
197+ let errorDiags = NE. toList $ NE. map (Diagnostics. errorDiagnostic file) pErrorNE
198+ allDiags = errorDiags <> warningDiags
199+ pure (allDiags, Nothing )
200+ Right gpd -> do
201+ pure (warningDiags, Just gpd)
172202
173203 action $ do
174204 -- Run the cabal kick. This code always runs when 'shakeRestart' is run.
@@ -188,7 +218,7 @@ function invocation.
188218kick :: Action ()
189219kick = do
190220 files <- HashMap. keys <$> getCabalFilesOfInterestUntracked
191- void $ uses Types. GetCabalDiagnostics files
221+ void $ uses Types. ParseCabalFile files
192222
193223-- ----------------------------------------------------------------
194224-- Code Actions
@@ -281,24 +311,31 @@ completion :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'LSP.M
281311completion recorder ide _ complParams = do
282312 let (TextDocumentIdentifier uri) = complParams ^. JL. textDocument
283313 position = complParams ^. JL. position
284- contents <- lift $ getVirtualFile $ toNormalizedUri uri
285- case (contents, uriToFilePath' uri) of
286- (Just cnts, Just path) -> do
287- let pref = Ghcide. getCompletionPrefix position cnts
288- let res = result pref path cnts
289- liftIO $ fmap InL res
290- _ -> pure . InR $ InR Null
314+ mVf <- lift $ getVirtualFile $ toNormalizedUri uri
315+ case (,) <$> mVf <*> uriToFilePath' uri of
316+ Just (cnts, path) -> do
317+ mFields <- liftIO $ runIdeAction " cabal-plugin.fields" (shakeExtras ide) $ useWithStaleFast ParseCabalFields $ toNormalizedFilePath path
318+ case mFields of
319+ Nothing ->
320+ pure . InR $ InR Null
321+ Just (fields, _) -> do
322+ let pref = Ghcide. getCompletionPrefix position cnts
323+ let res = produceCompletions pref path fields
324+ liftIO $ fmap InL res
325+ Nothing -> pure . InR $ InR Null
291326 where
292- result :: Ghcide. PosPrefixInfo -> FilePath -> VFS. VirtualFile -> IO [CompletionItem ]
293- result prefix fp cnts = do
294- runMaybeT context >>= \ case
327+ completerRecorder = cmapWithPrio LogCompletions recorder
328+
329+ produceCompletions :: Ghcide. PosPrefixInfo -> FilePath -> [Syntax. Field Syntax. Position ] -> IO [CompletionItem ]
330+ produceCompletions prefix fp fields = do
331+ runMaybeT (context fields) >>= \ case
295332 Nothing -> pure []
296333 Just ctx -> do
297334 logWith recorder Debug $ LogCompletionContext ctx pos
298335 let completer = Completions. contextToCompleter ctx
299336 let completerData = CompleterTypes. CompleterData
300337 { getLatestGPD = do
301- mGPD <- runIdeAction " cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast Types. GetCabalDiagnostics $ toNormalizedFilePath fp
338+ mGPD <- runIdeAction " cabal-plugin.modulesCompleter.gpd" (shakeExtras ide) $ useWithStaleFast ParseCabalFile $ toNormalizedFilePath fp
302339 pure $ fmap fst mGPD
303340 , cabalPrefixInfo = prefInfo
304341 , stanzaName =
@@ -309,7 +346,6 @@ completion recorder ide _ complParams = do
309346 completions <- completer completerRecorder completerData
310347 pure completions
311348 where
312- completerRecorder = cmapWithPrio LogCompletions recorder
313349 pos = Ghcide. cursorPos prefix
314- context = Completions. getContext completerRecorder prefInfo (cnts ^. VFS. file_text)
350+ context fields = Completions. getContext completerRecorder prefInfo fields
315351 prefInfo = Completions. getCabalPrefixInfo fp prefix
0 commit comments