Skip to content

Commit 4da8eb9

Browse files
committed
edit documentation and code to reflect cabal.project
1 parent a479a31 commit 4da8eb9

File tree

6 files changed

+76
-110
lines changed

6 files changed

+76
-110
lines changed

.gitignore

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,3 @@ store/
5151
gh-release-artifacts/
5252

5353
.hls/
54-
55-
# local cabal package
56-
vendor/parse-cabal-project

haskell-language-server.cabal

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -341,12 +341,8 @@ library hls-cabal-project-plugin
341341
Ide.Plugin.CabalProject.Diagnostics
342342
Ide.Plugin.CabalProject.Types
343343
Ide.Plugin.CabalProject.Completion.Completions
344-
-- Ide.Plugin.CabalProject.Completion.Completer.Simple
345-
-- Ide.Plugin.CabalProject.Completion.Completer.Types
346-
Ide.Plugin.CabalProject.Completion.CabalProjectFields
347344
Ide.Plugin.CabalProject.Completion.Data
348345

349-
350346
build-depends:
351347
, bytestring
352348
, Cabal-syntax >= 3.7
@@ -378,7 +374,6 @@ library hls-cabal-project-plugin
378374
, base16-bytestring
379375
, cryptohash-sha1
380376

381-
382377
hs-source-dirs: plugins/hls-cabal-project-plugin/src
383378

384379
test-suite hls-cabal-project-plugin-tests
@@ -406,7 +401,6 @@ test-suite hls-cabal-project-plugin-tests
406401
, cabal-install
407402
, haskell-language-server:hls-cabal-plugin
408403

409-
410404
-----------------------------
411405
-- class plugin
412406
-----------------------------

plugins/hls-cabal-project-plugin/src/Ide/Plugin/CabalProject.hs

Lines changed: 56 additions & 71 deletions
Original file line numberDiff line numberDiff line change
@@ -12,59 +12,42 @@ import Control.DeepSeq
1212
import Control.Lens ((^.))
1313
import Control.Monad.Extra
1414
import Control.Monad.IO.Class
15-
import Control.Monad.Trans.Class (lift)
1615
import Control.Monad.Trans.Maybe (runMaybeT)
1716
import qualified Data.ByteString as BS
1817
import Data.Hashable
19-
import Data.HashMap.Strict (HashMap,
20-
toList)
18+
import Data.HashMap.Strict (HashMap)
19+
-- toList)
2120
import qualified Data.HashMap.Strict as HashMap
22-
import qualified Data.List as List
2321
import qualified Data.List.NonEmpty as NE
24-
import qualified Data.Maybe as Maybe
2522
import Data.Proxy
2623
import qualified Data.Text ()
27-
import qualified Data.Text as T
2824
import qualified Data.Text.Encoding as Encoding
2925
import Data.Text.Utf16.Rope.Mixed as Rope
3026
import Development.IDE as D
31-
import Development.IDE.Core.FileStore (getVersionedTextDoc)
32-
import Development.IDE.Core.PluginUtils
3327
import Development.IDE.Core.Shake (restartShakeSession)
3428
import qualified Development.IDE.Core.Shake as Shake
3529
import Development.IDE.Graph (Key,
3630
alwaysRerun)
37-
import Development.IDE.LSP.HoverDefinition (foundHover)
3831
import qualified Development.IDE.Plugin.Completions.Logic as Ghcide
3932
import Development.IDE.Types.Shake (toKey)
40-
import qualified Distribution.CabalSpecVersion as Cabal
4133
import qualified Distribution.Fields as Syntax
42-
import Distribution.Package (Dependency)
43-
import Distribution.PackageDescription (allBuildDepends,
44-
depPkgName,
45-
unPackageName)
46-
import Distribution.PackageDescription.Configuration (flattenPackageDescription)
47-
import Distribution.Parsec.Error
34+
-- import Distribution.PackageDescription (allBuildDepends,
35+
-- depPkgName,
36+
-- unPackageName)
4837
import qualified Distribution.Parsec.Position as Syntax
4938
import GHC.Generics
50-
import Ide.Plugin.Cabal.Completion.CabalFields as CabalFields
5139
import qualified Ide.Plugin.Cabal.Completion.Completer.Types as CompleterTypes
52-
import qualified Ide.Plugin.Cabal.Completion.Data as Data
5340
import qualified Ide.Plugin.Cabal.Completion.Types as CTypes
5441
import Ide.Plugin.Cabal.Orphans ()
5542
import qualified Ide.Plugin.CabalProject.Completion.Completions as Completions
5643
import Ide.Plugin.CabalProject.Diagnostics as Diagnostics
5744
import Ide.Plugin.CabalProject.Parse as Parse
5845
import Ide.Plugin.CabalProject.Types as Types
59-
import Ide.Plugin.Error
6046
import Ide.Types
6147
import qualified Language.LSP.Protocol.Lens as JL
6248
import qualified Language.LSP.Protocol.Message as LSP
6349
import Language.LSP.Protocol.Types
6450
import qualified Language.LSP.VFS as VFS
65-
import System.FilePath (takeFileName)
66-
import Text.Regex.TDFA
67-
6851

6952
data Log
7053
= LogModificationTime NormalizedFilePath FileVersion
@@ -103,7 +86,7 @@ instance Pretty Log where
10386
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
10487
descriptor recorder plId =
10588
(defaultCabalProjectPluginDescriptor plId "Provides a variety of IDE features in cabal.project files")
106-
{ pluginRules = cabalRules recorder plId
89+
{ pluginRules = cabalProjectRules recorder plId
10790
, pluginHandlers =
10891
mconcat
10992
[
@@ -115,25 +98,25 @@ descriptor recorder plId =
11598
\ide vfs _ (DidOpenTextDocumentParams TextDocumentItem{_uri, _version}) -> liftIO $ do
11699
whenUriFile _uri $ \file -> do
117100
log' Debug $ LogDocOpened _uri
118-
restartCabalShakeSession (shakeExtras ide) vfs file "(opened)" $
101+
restartCabalProjectShakeSession (shakeExtras ide) vfs file "(opened)" $
119102
addFileOfInterest recorder ide file Modified{firstOpen = True}
120103
, mkPluginNotificationHandler LSP.SMethod_TextDocumentDidChange $
121104
\ide vfs _ (DidChangeTextDocumentParams VersionedTextDocumentIdentifier{_uri} _) -> liftIO $ do
122105
whenUriFile _uri $ \file-> do
123106
log' Debug $ LogDocModified _uri
124-
restartCabalShakeSession (shakeExtras ide) vfs file "(changed)" $
107+
restartCabalProjectShakeSession (shakeExtras ide) vfs file "(changed)" $
125108
addFileOfInterest recorder ide file Modified{firstOpen = False}
126109
, mkPluginNotificationHandler LSP.SMethod_TextDocumentDidSave $
127110
\ide vfs _ (DidSaveTextDocumentParams TextDocumentIdentifier{_uri} _) -> liftIO $ do
128111
whenUriFile _uri $ \file -> do
129112
log' Debug $ LogDocSaved _uri
130-
restartCabalShakeSession (shakeExtras ide) vfs file "(saved)" $
113+
restartCabalProjectShakeSession (shakeExtras ide) vfs file "(saved)" $
131114
addFileOfInterest recorder ide file OnDisk
132115
, mkPluginNotificationHandler LSP.SMethod_TextDocumentDidClose $
133116
\ide vfs _ (DidCloseTextDocumentParams TextDocumentIdentifier{_uri}) -> liftIO $ do
134117
whenUriFile _uri $ \file -> do
135118
log' Debug $ LogDocClosed _uri
136-
restartCabalShakeSession (shakeExtras ide) vfs file "(closed)" $
119+
restartCabalProjectShakeSession (shakeExtras ide) vfs file "(closed)" $
137120
deleteFileOfInterest recorder ide file
138121
]
139122
, pluginConfigDescriptor = defaultConfigDescriptor
@@ -146,7 +129,7 @@ descriptor recorder plId =
146129
whenUriFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
147130
whenUriFile uri act = whenJust (uriToFilePath uri) $ act . toNormalizedFilePath'
148131

149-
{- | Helper function to restart the shake session, specifically for modifying .cabal files.
132+
{- | Helper function to restart the shake session, specifically for modifying cabal.project files.
150133
No special logic, just group up a bunch of functions you need for the base
151134
Notification Handlers.
152135
@@ -155,28 +138,28 @@ needs to be re-parsed. That's what we do when we record the dirty key that our p
155138
rule depends on.
156139
Then we restart the shake session, so that changes to our virtual files are actually picked up.
157140
-}
158-
restartCabalShakeSession :: ShakeExtras -> VFS.VFS -> NormalizedFilePath -> String -> IO [Key] -> IO ()
159-
restartCabalShakeSession shakeExtras vfs file actionMsg actionBetweenSession = do
141+
restartCabalProjectShakeSession :: ShakeExtras -> VFS.VFS -> NormalizedFilePath -> String -> IO [Key] -> IO ()
142+
restartCabalProjectShakeSession shakeExtras vfs file actionMsg actionBetweenSession = do
160143
restartShakeSession shakeExtras (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
161144
keys <- actionBetweenSession
162145
return (toKey GetModificationTime file:keys)
163146

164147

165-
cabalRules :: Recorder (WithPriority Log) -> PluginId -> Rules ()
166-
cabalRules recorder plId = do
167-
-- Make sure we initialise the cabal files-of-interest.
148+
cabalProjectRules :: Recorder (WithPriority Log) -> PluginId -> Rules ()
149+
cabalProjectRules recorder plId = do
150+
-- Make sure we initialise the cabal.project files-of-interest.
168151
ofInterestRules recorder
169-
-- Rule to produce diagnostics for cabal files.
152+
-- Rule to produce diagnostics for cabal.project files.
170153
define (cmapWithPrio LogShake recorder) $ \ParseCabalProjectFields file -> do
171154
config <- getPluginConfigAction plId
172155
if not (plcGlobalOn config && plcDiagnosticsOn config)
173156
then pure ([], Nothing)
174157
else do
175158
-- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
176159
-- we rerun this rule because this rule *depends* on GetModificationTime.
177-
(t, mCabalSource) <- use_ GetFileContents file
160+
(t, mCabalProjectSource) <- use_ GetFileContents file
178161
log' Debug $ LogModificationTime file t
179-
contents <- case mCabalSource of
162+
contents <- case mCabalProjectSource of
180163
Just sources ->
181164
pure $ Encoding.encodeUtf8 $ Rope.toText sources
182165
Nothing -> do
@@ -195,10 +178,10 @@ cabalRules recorder plId = do
195178
else do
196179
-- whenever this key is marked as dirty (e.g., when a user writes stuff to it),
197180
-- we rerun this rule because this rule *depends* on GetModificationTime.
198-
(t, mCabalSource) <- use_ GetFileContents file
181+
(t, mCabalProjectSource) <- use_ GetFileContents file
199182
log' Debug $ LogModificationTime file t
200183

201-
contents <- case mCabalSource of
184+
contents <- case mCabalProjectSource of
202185
Just sources ->
203186
pure $ Encoding.encodeUtf8 $ Rope.toText sources
204187
Nothing ->
@@ -216,96 +199,96 @@ cabalRules recorder plId = do
216199
pure (warnDiags, Just projCfg)
217200

218201
action $ do
219-
-- Run the cabal kick. This code always runs when 'shakeRestart' is run.
202+
-- Run the cabal.project kick. This code always runs when 'shakeRestart' is run.
220203
-- Must be careful to not impede the performance too much. Crucial to
221204
-- a snappy IDE experience.
222205
kick
223206
where
224207
log' = logWith recorder
225208

226-
{- | This is the kick function for the cabal plugin.
209+
{- | This is the kick function for the cabal project plugin.
227210
We run this action, whenever we shake session us run/restarted, which triggers
228-
actions to produce diagnostics for cabal files.
211+
actions to produce diagnostics for cabal.project files.
229212
230213
It is paramount that this kick-function can be run quickly, since it is a blocking
231214
function invocation.
232215
-}
233216
kick :: Action ()
234217
kick = do
235-
files <- HashMap.keys <$> getCabalFilesOfInterestUntracked
218+
files <- HashMap.keys <$> getCabalProjectFilesOfInterestUntracked
236219
-- let keys = map Types.ParseCabalProjectFile files
237220
Shake.runWithSignal (Proxy @"kick/start/cabal-project") (Proxy @"kick/done/cabal-project") files Types.ParseCabalProjectFile
238221

239222

240223
-- ----------------------------------------------------------------
241-
-- Cabal file of Interest rules and global variable
224+
-- Cabal.project file of Interest rules and global variable
242225
-- ----------------------------------------------------------------
243226

244-
{- | Cabal files that are currently open in the lsp-client.
227+
{- | Cabal.project files that are currently open in the lsp-client.
245228
Specific actions happen when these files are saved, closed or modified,
246229
such as generating diagnostics, re-parsing, etc...
247230
248231
We need to store the open files to parse them again if we restart the shake session.
249232
Restarting of the shake session happens whenever these files are modified.
250233
-}
251-
newtype OfInterestCabalVar = OfInterestCabalVar (Var (HashMap NormalizedFilePath FileOfInterestStatus))
234+
newtype OfInterestCabalProjectVar = OfInterestCabalProjectVar (Var (HashMap NormalizedFilePath FileOfInterestStatus))
252235

253-
instance Shake.IsIdeGlobal OfInterestCabalVar
236+
instance Shake.IsIdeGlobal OfInterestCabalProjectVar
254237

255-
data IsCabalFileOfInterest = IsCabalFileOfInterest
238+
data IsCabalProjectFileOfInterest = IsCabalProjectFileOfInterest
256239
deriving (Eq, Show, Generic)
257-
instance Hashable IsCabalFileOfInterest
258-
instance NFData IsCabalFileOfInterest
240+
instance Hashable IsCabalProjectFileOfInterest
241+
instance NFData IsCabalProjectFileOfInterest
259242

260-
type instance RuleResult IsCabalFileOfInterest = CabalFileOfInterestResult
243+
type instance RuleResult IsCabalProjectFileOfInterest = CabalProjectFileOfInterestResult
261244

262-
data CabalFileOfInterestResult = NotCabalFOI | IsCabalFOI FileOfInterestStatus
245+
data CabalProjectFileOfInterestResult = NotCabalProjectFOI | IsCabalProjectFOI FileOfInterestStatus
263246
deriving (Eq, Show, Generic)
264-
instance Hashable CabalFileOfInterestResult
265-
instance NFData CabalFileOfInterestResult
247+
instance Hashable CabalProjectFileOfInterestResult
248+
instance NFData CabalProjectFileOfInterestResult
266249

267250
{- | The rule that initialises the files of interest state.
268251
269252
Needs to be run on start-up.
270253
-}
271254
ofInterestRules :: Recorder (WithPriority Log) -> Rules ()
272255
ofInterestRules recorder = do
273-
Shake.addIdeGlobal . OfInterestCabalVar =<< liftIO (newVar HashMap.empty)
274-
Shake.defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \IsCabalFileOfInterest f -> do
256+
Shake.addIdeGlobal . OfInterestCabalProjectVar =<< liftIO (newVar HashMap.empty)
257+
Shake.defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \IsCabalProjectFileOfInterest f -> do
275258
alwaysRerun
276-
filesOfInterest <- getCabalFilesOfInterestUntracked
277-
let foi = maybe NotCabalFOI IsCabalFOI $ f `HashMap.lookup` filesOfInterest
259+
filesOfInterest <- getCabalProjectFilesOfInterestUntracked
260+
let foi = maybe NotCabalProjectFOI IsCabalProjectFOI $ f `HashMap.lookup` filesOfInterest
278261
fp = summarize foi
279262
res = (Just fp, Just foi)
280263
return res
281264
where
282-
summarize NotCabalFOI = BS.singleton 0
283-
summarize (IsCabalFOI OnDisk) = BS.singleton 1
284-
summarize (IsCabalFOI (Modified False)) = BS.singleton 2
285-
summarize (IsCabalFOI (Modified True)) = BS.singleton 3
286-
287-
getCabalFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
288-
getCabalFilesOfInterestUntracked = do
289-
OfInterestCabalVar var <- Shake.getIdeGlobalAction
265+
summarize NotCabalProjectFOI = BS.singleton 0
266+
summarize (IsCabalProjectFOI OnDisk) = BS.singleton 1
267+
summarize (IsCabalProjectFOI (Modified False)) = BS.singleton 2
268+
summarize (IsCabalProjectFOI (Modified True)) = BS.singleton 3
269+
270+
getCabalProjectFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
271+
getCabalProjectFilesOfInterestUntracked = do
272+
OfInterestCabalProjectVar var <- Shake.getIdeGlobalAction
290273
liftIO $ readVar var
291274

292275
addFileOfInterest :: Recorder (WithPriority Log) -> IdeState -> NormalizedFilePath -> FileOfInterestStatus -> IO [Key]
293276
addFileOfInterest recorder state f v = do
294-
OfInterestCabalVar var <- Shake.getIdeGlobalState state
277+
OfInterestCabalProjectVar var <- Shake.getIdeGlobalState state
295278
(prev, files) <- modifyVar var $ \dict -> do
296279
let (prev, new) = HashMap.alterF (,Just v) f dict
297280
pure (new, (prev, new))
298281
if prev /= Just v
299282
then do
300283
log' Debug $ LogFOI files
301-
return [toKey IsCabalFileOfInterest f]
284+
return [toKey IsCabalProjectFileOfInterest f]
302285
else return []
303286
where
304287
log' = logWith recorder
305288

306289
deleteFileOfInterest :: Recorder (WithPriority Log) -> IdeState -> NormalizedFilePath -> IO [Key]
307290
deleteFileOfInterest recorder state f = do
308-
OfInterestCabalVar var <- Shake.getIdeGlobalState state
291+
OfInterestCabalProjectVar var <- Shake.getIdeGlobalState state
309292
files <- modifyVar' var $ HashMap.delete f
310293
log' Debug $ LogFOI files
311294
return [toKey IsFileOfInterest f]
@@ -329,20 +312,22 @@ completion recorder ide _ complParams = do
329312
pure . InR $ InR Null
330313
Just (fields, _) -> do
331314
let lspPrefInfo = Ghcide.getCompletionPrefixFromRope position cnts
332-
cabalPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
333-
let res = computeCompletionsAt recorder ide cabalPrefInfo path fields
315+
cabalProjectPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
316+
let res = computeCompletionsAt recorder ide cabalProjectPrefInfo path fields
334317
liftIO $ fmap InL res
335318
Nothing -> pure . InR $ InR Null
336319

337320
computeCompletionsAt :: Recorder (WithPriority Log) -> IdeState -> CTypes.CabalPrefixInfo -> FilePath -> [Syntax.Field Syntax.Position] -> IO [CompletionItem]
338-
computeCompletionsAt recorder ide prefInfo fp fields = do
321+
computeCompletionsAt recorder _ prefInfo _ fields = do
339322
runMaybeT (context fields) >>= \case
340323
Nothing -> pure []
341324
Just ctx -> do
342325
logWith recorder Debug $ LogCompletionContext ctx pos
343326
let completer = Completions.contextToCompleter ctx
344327
let completerData = CompleterTypes.CompleterData
345328
{
329+
getLatestGPD = pure Nothing,
330+
getCabalCommonSections = pure Nothing,
346331
cabalPrefixInfo = prefInfo
347332
, stanzaName =
348333
case fst ctx of

plugins/hls-cabal-project-plugin/src/Ide/Plugin/CabalProject/Completion/Completions.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
{-# LANGUAGE OverloadedStrings #-}
22

3-
module Ide.Plugin.CabalProject.Completion.Completions (contextToCompleter, getContext, getCabalPrefixInfo) where
3+
module Ide.Plugin.CabalProject.Completion.Completions (contextToCompleter, getContext, getCabalProjectPrefixInfo) where
44

55
import Control.Lens ((^.))
66
import Control.Monad.IO.Class (MonadIO)
@@ -67,13 +67,13 @@ getContext recorder prefInfo fields = do
6767
cursor = lspPositionToCabalPosition (completionCursorPosition prefInfo)
6868

6969
-- | Takes information about the current file's file path,
70-
-- and the cursor position in the file; and builds a CabalPrefixInfo
70+
-- and the cursor position in the file; and builds a CabalPrefixInfo, reused from hls-cabal-plugin
7171
-- with the prefix up to that cursor position.
7272
-- Checks whether a suffix needs to be completed
7373
-- and calculates the range in the document
7474
-- where the completion action should be applied.
75-
getCabalPrefixInfo :: FilePath -> Ghcide.PosPrefixInfo -> CabalPrefixInfo
76-
getCabalPrefixInfo fp prefixInfo =
75+
getCabalProjectPrefixInfo :: FilePath -> Ghcide.PosPrefixInfo -> CabalPrefixInfo
76+
getCabalProjectPrefixInfo fp prefixInfo =
7777
CabalPrefixInfo
7878
{ completionPrefix = completionPrefix',
7979
isStringNotation = mkIsStringNotation separator afterCursorText,
@@ -148,7 +148,7 @@ findCursorContext cursor parentHistory prefixText fields =
148148

149149
-- | Finds the cursor's context, where the cursor is already found to be in a specific field
150150
--
151-
-- Due to the way the field context is recognised for incomplete cabal files,
151+
-- Due to the way the field context is recognised for incomplete cabal.project files,
152152
-- an incomplete keyword is also recognised as a field, therefore we need to determine
153153
-- the specific context as we could still be in a stanza context in this case.
154154
classifyFieldContext :: NonEmpty (Int, StanzaContext) -> Syntax.Position -> Syntax.Field Syntax.Position -> Context

0 commit comments

Comments
 (0)