Skip to content

Commit 5dfee4c

Browse files
authored
Add GetHieAsts rule, Replace SpanInfo, add support for DocumentHighlight and scope-aware completions for local variables (haskell/ghcide#784)
* Add GetHieAsts rule * hlint * fix build for 8.4 * Reimplement Hover/GotoDefn in terms of HIE Files. Implement Document Hightlight LSP request Add GetDocMap, GetHieFile rules. * Fix gotodef for record fields * Completion for locals * Don't need to hack cursor position because of fuzzy ranges * hlint * fix bench and warning on 8.10 * disable 8.4 CI jobs * Don't collect module level bindings * tweaks * Show kinds * docs * Defs for ModuleNames * Fix some tests * hlint * Mark remaining tests as broken * Add completion tests * add highlight tests * Fix HieAst for 8.6 * CPP away the unexpected success * More CPP hacks for 8.10 tests
1 parent e19c5a3 commit 5dfee4c

File tree

26 files changed

+729
-646
lines changed

26 files changed

+729
-646
lines changed

.hlint.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@
9595
- flags:
9696
- default: false
9797
- {name: [-Wno-missing-signatures, -Wno-orphans, -Wno-overlapping-patterns, -Wno-incomplete-patterns, -Wno-missing-fields, -Wno-unused-matches]}
98-
- {name: [-Wno-dodgy-imports], within: [Main, Development.IDE.GHC.Compat]}
98+
- {name: [-Wno-dodgy-imports,-Wno-incomplete-uni-patterns], within: [Main, Development.IDE.GHC.Compat]}
9999
# - modules:
100100
# - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set'
101101
# - {name: Control.Arrow, within: []} # Certain modules are banned entirely

ghcide/.azure/linux-stack.yml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,6 @@ jobs:
1111
STACK_YAML: "stack88.yaml"
1212
stack_86:
1313
STACK_YAML: "stack.yaml"
14-
stack_84:
15-
STACK_YAML: "stack84.yaml"
1614
stack_ghc_lib_88:
1715
STACK_YAML: "stack-ghc-lib.yaml"
1816
variables:

ghcide/.azure/windows-stack.yml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,6 @@ jobs:
1111
STACK_YAML: "stack88.yaml"
1212
stack_86:
1313
STACK_YAML: "stack.yaml"
14-
stack_84:
15-
STACK_YAML: "stack84.yaml"
1614
stack_ghc_lib_88:
1715
STACK_YAML: "stack-ghc-lib.yaml"
1816
variables:

ghcide/ghcide.cabal

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ library
4848
extra,
4949
fuzzy,
5050
filepath,
51+
fingertree,
5152
haddock-library >= 1.8,
5253
hashable,
5354
haskell-lsp-types == 0.22.*,
@@ -140,6 +141,8 @@ library
140141
Development.IDE.LSP.Protocol
141142
Development.IDE.LSP.Server
142143
Development.IDE.Spans.Common
144+
Development.IDE.Spans.AtPoint
145+
Development.IDE.Spans.LocalBindings
143146
Development.IDE.Types.Diagnostics
144147
Development.IDE.Types.Exports
145148
Development.IDE.Types.Location
@@ -173,10 +176,7 @@ library
173176
Development.IDE.GHC.WithDynFlags
174177
Development.IDE.Import.FindImports
175178
Development.IDE.LSP.Notifications
176-
Development.IDE.Spans.AtPoint
177-
Development.IDE.Spans.Calculate
178179
Development.IDE.Spans.Documentation
179-
Development.IDE.Spans.Type
180180
Development.IDE.Plugin.CodeAction.PositionIndexed
181181
Development.IDE.Plugin.CodeAction.Rules
182182
Development.IDE.Plugin.CodeAction.RuleTypes

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 28 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,8 @@ module Development.IDE.Core.Compile
1818
, addRelativeImport
1919
, mkTcModuleResult
2020
, generateByteCode
21-
, generateAndWriteHieFile
21+
, generateHieAsts
22+
, writeHieFile
2223
, writeHiFile
2324
, getModSummaryFromImports
2425
, loadHieFile
@@ -56,7 +57,7 @@ import ErrUtils
5657
#endif
5758

5859
import Finder
59-
import Development.IDE.GHC.Compat hiding (parseModule, typecheckModule)
60+
import Development.IDE.GHC.Compat hiding (parseModule, typecheckModule, writeHieFile)
6061
import qualified Development.IDE.GHC.Compat as GHC
6162
import qualified Development.IDE.GHC.Compat as Compat
6263
import GhcMonad
@@ -65,7 +66,7 @@ import qualified HeaderInfo as Hdr
6566
import HscMain (hscInteractive, hscSimplify)
6667
import MkIface
6768
import StringBuffer as SB
68-
import TcRnMonad (tct_id, TcTyThing(AGlobal, ATcId), initTc, initIfaceLoad, tcg_th_coreplugins)
69+
import TcRnMonad (tct_id, TcTyThing(AGlobal, ATcId), initTc, initIfaceLoad, tcg_th_coreplugins, tcg_binds)
6970
import TcIface (typecheckIface)
7071
import TidyPgm
7172

@@ -320,7 +321,7 @@ mkTcModuleResult tcm upgradedError = do
320321
(iface, _) <- liftIO $ mkIfaceTc session Nothing sf details tcGblEnv
321322
#endif
322323
let mod_info = HomeModInfo iface details Nothing
323-
return $ TcModuleResult tcm mod_info upgradedError
324+
return $ TcModuleResult tcm mod_info upgradedError Nothing
324325
where
325326
(tcGblEnv, details) = tm_internals_ tcm
326327

@@ -331,19 +332,25 @@ atomicFileWrite targetPath write = do
331332
(tempFilePath, cleanUp) <- newTempFileWithin dir
332333
(write tempFilePath >> renameFile tempFilePath targetPath) `onException` cleanUp
333334

334-
generateAndWriteHieFile :: HscEnv -> TypecheckedModule -> BS.ByteString -> IO [FileDiagnostic]
335-
generateAndWriteHieFile hscEnv tcm source =
336-
handleGenerationErrors dflags "extended interface generation" $ do
335+
generateHieAsts :: HscEnv -> TypecheckedModule -> IO ([FileDiagnostic], Maybe (HieASTs Type))
336+
generateHieAsts hscEnv tcm =
337+
handleGenerationErrors' dflags "extended interface generation" $ do
337338
case tm_renamed_source tcm of
338-
Just rnsrc -> do
339-
hf <- runHsc hscEnv $
340-
GHC.mkHieFile mod_summary (fst $ tm_internals_ tcm) rnsrc source
341-
atomicFileWrite targetPath $ flip GHC.writeHieFile hf
339+
Just rnsrc -> runHsc hscEnv $
340+
Just <$> GHC.enrichHie (tcg_binds $ fst $ tm_internals_ tcm) rnsrc
342341
_ ->
343-
return ()
342+
return Nothing
343+
where
344+
dflags = hsc_dflags hscEnv
345+
346+
writeHieFile :: HscEnv -> ModSummary -> [GHC.AvailInfo] -> HieASTs Type -> BS.ByteString -> IO [FileDiagnostic]
347+
writeHieFile hscEnv mod_summary exports ast source =
348+
handleGenerationErrors dflags "extended interface write/compression" $ do
349+
hf <- runHsc hscEnv $
350+
GHC.mkHieFile' mod_summary exports ast source
351+
atomicFileWrite targetPath $ flip GHC.writeHieFile hf
344352
where
345353
dflags = hsc_dflags hscEnv
346-
mod_summary = pm_mod_summary $ tm_parsed_module tcm
347354
mod_location = ms_location mod_summary
348355
targetPath = Compat.ml_hie_file mod_location
349356

@@ -365,6 +372,14 @@ handleGenerationErrors dflags source action =
365372
. (("Error during " ++ T.unpack source) ++) . show @SomeException
366373
]
367374

375+
handleGenerationErrors' :: DynFlags -> T.Text -> IO (Maybe a) -> IO ([FileDiagnostic], Maybe a)
376+
handleGenerationErrors' dflags source action =
377+
fmap ([],) action `catches`
378+
[ Handler $ return . (,Nothing) . diagFromGhcException source dflags
379+
, Handler $ return . (,Nothing) . diagFromString source DsError (noSpan "<internal>")
380+
. (("Error during " ++ T.unpack source) ++) . show @SomeException
381+
]
382+
368383

369384
-- | Setup the environment that GHC needs according to our
370385
-- best understanding (!)

ghcide/src/Development/IDE/Core/PositionMapping.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,6 @@ toCurrentPosition (PositionMapping pm) = positionResultToMaybe . toDelta pm
7474
-- a specific version
7575
newtype PositionMapping = PositionMapping PositionDelta
7676

77-
7877
toCurrentRange :: PositionMapping -> Range -> Maybe Range
7978
toCurrentRange mapping (Range a b) =
8079
Range <$> toCurrentPosition mapping a <*> toCurrentPosition mapping b
@@ -121,7 +120,7 @@ toCurrent (Range start@(Position startLine startColumn) end@(Position endLine en
121120
| line > endLine || line == endLine && column >= endColumn =
122121
-- Position is after the change so increase line and column number
123122
-- as necessary.
124-
PositionExact $ Position newLine newColumn
123+
PositionExact $ newLine `seq` newColumn `seq` Position newLine newColumn
125124
| otherwise = PositionRange start end
126125
-- Position is in the region that was changed.
127126
where
@@ -131,10 +130,10 @@ toCurrent (Range start@(Position startLine startColumn) end@(Position endLine en
131130
newEndColumn
132131
| linesNew == 0 = startColumn + T.length t
133132
| otherwise = T.length $ T.takeWhileEnd (/= '\n') t
134-
!newColumn
133+
newColumn
135134
| line == endLine = column + newEndColumn - endColumn
136135
| otherwise = column
137-
!newLine = line + lineDiff
136+
newLine = line + lineDiff
138137

139138
fromCurrent :: Range -> T.Text -> Position -> PositionResult Position
140139
fromCurrent (Range start@(Position startLine startColumn) end@(Position endLine endColumn)) t (Position line column)
@@ -144,7 +143,7 @@ fromCurrent (Range start@(Position startLine startColumn) end@(Position endLine
144143
| line > newEndLine || line == newEndLine && column >= newEndColumn =
145144
-- Position is after the change so increase line and column number
146145
-- as necessary.
147-
PositionExact $ Position newLine newColumn
146+
PositionExact $ newLine `seq` newColumn `seq` Position newLine newColumn
148147
| otherwise = PositionRange start end
149148
-- Position is in the region that was changed.
150149
where
@@ -155,7 +154,7 @@ fromCurrent (Range start@(Position startLine startColumn) end@(Position endLine
155154
newEndColumn
156155
| linesNew == 0 = startColumn + T.length t
157156
| otherwise = T.length $ T.takeWhileEnd (/= '\n') t
158-
!newColumn
157+
newColumn
159158
| line == newEndLine = column - (newEndColumn - endColumn)
160159
| otherwise = column
161-
!newLine = line - lineDiff
160+
newLine = line - lineDiff

ghcide/src/Development/IDE/Core/RuleTypes.hs

Lines changed: 52 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -15,22 +15,24 @@ import Control.DeepSeq
1515
import Data.Aeson.Types (Value)
1616
import Data.Binary
1717
import Development.IDE.Import.DependencyInformation
18-
import Development.IDE.GHC.Compat
18+
import Development.IDE.GHC.Compat hiding (HieFileResult)
1919
import Development.IDE.GHC.Util
2020
import Development.IDE.Core.Shake (KnownTargets)
2121
import Data.Hashable
2222
import Data.Typeable
2323
import qualified Data.Set as S
24+
import qualified Data.Map as M
2425
import Development.Shake
2526
import GHC.Generics (Generic)
2627

2728
import Module (InstalledUnitId)
2829
import HscTypes (hm_iface, CgGuts, Linkable, HomeModInfo, ModDetails)
2930

30-
import Development.IDE.Spans.Type
31+
import Development.IDE.Spans.Common
32+
import Development.IDE.Spans.LocalBindings
3133
import Development.IDE.Import.FindImports (ArtifactsLocation)
3234
import Data.ByteString (ByteString)
33-
35+
import Language.Haskell.LSP.Types (NormalizedFilePath)
3436

3537
-- NOTATION
3638
-- Foo+ means Foo for the dependencies
@@ -66,6 +68,7 @@ data TcModuleResult = TcModuleResult
6668
-- HomeModInfo instead
6769
, tmrModInfo :: HomeModInfo
6870
, tmrDeferedError :: !Bool -- ^ Did we defer any type errors for this module?
71+
, tmrHieAsts :: !(Maybe (HieASTs Type)) -- ^ The HieASTs if we computed them
6972
}
7073
instance Show TcModuleResult where
7174
show = show . pm_mod_summary . tm_parsed_module . tmrModule
@@ -98,11 +101,38 @@ instance NFData HiFileResult where
98101
instance Show HiFileResult where
99102
show = show . hirModSummary
100103

104+
-- | Save the uncompressed AST here, we compress it just before writing to disk
105+
data HieAstResult
106+
= HAR
107+
{ hieModule :: Module
108+
, hieAst :: !(HieASTs Type)
109+
, refMap :: !RefMap
110+
, importMap :: !(M.Map ModuleName NormalizedFilePath) -- ^ Where are the modules imported by this file located?
111+
}
112+
113+
instance NFData HieAstResult where
114+
rnf (HAR m hf rm im) = rnf m `seq` rwhnf hf `seq` rnf rm `seq` rnf im
115+
116+
instance Show HieAstResult where
117+
show = show . hieModule
118+
101119
-- | The type checked version of this file, requires TypeCheck+
102120
type instance RuleResult TypeCheck = TcModuleResult
103121

104-
-- | Information about what spans occur where, requires TypeCheck
105-
type instance RuleResult GetSpanInfo = SpansInfo
122+
-- | The uncompressed HieAST
123+
type instance RuleResult GetHieAst = HieAstResult
124+
125+
-- | A IntervalMap telling us what is in scope at each point
126+
type instance RuleResult GetBindings = Bindings
127+
128+
data DocAndKindMap = DKMap {getDocMap :: !DocMap, getKindMap :: !KindMap}
129+
instance NFData DocAndKindMap where
130+
rnf (DKMap a b) = rnf a `seq` rnf b
131+
132+
instance Show DocAndKindMap where
133+
show = const "docmap"
134+
135+
type instance RuleResult GetDocMap = DocAndKindMap
106136

107137
-- | Convert to Core, requires TypeCheck*
108138
type instance RuleResult GenerateCore = (SafeHaskellMode, CgGuts, ModDetails)
@@ -196,11 +226,23 @@ instance Hashable TypeCheck
196226
instance NFData TypeCheck
197227
instance Binary TypeCheck
198228

199-
data GetSpanInfo = GetSpanInfo
229+
data GetDocMap = GetDocMap
230+
deriving (Eq, Show, Typeable, Generic)
231+
instance Hashable GetDocMap
232+
instance NFData GetDocMap
233+
instance Binary GetDocMap
234+
235+
data GetHieAst = GetHieAst
236+
deriving (Eq, Show, Typeable, Generic)
237+
instance Hashable GetHieAst
238+
instance NFData GetHieAst
239+
instance Binary GetHieAst
240+
241+
data GetBindings = GetBindings
200242
deriving (Eq, Show, Typeable, Generic)
201-
instance Hashable GetSpanInfo
202-
instance NFData GetSpanInfo
203-
instance Binary GetSpanInfo
243+
instance Hashable GetBindings
244+
instance NFData GetBindings
245+
instance Binary GetBindings
204246

205247
data GenerateCore = GenerateCore
206248
deriving (Eq, Show, Typeable, Generic)
@@ -262,4 +304,4 @@ instance Hashable GetClientSettings
262304
instance NFData GetClientSettings
263305
instance Binary GetClientSettings
264306

265-
type instance RuleResult GetClientSettings = Hashed (Maybe Value)
307+
type instance RuleResult GetClientSettings = Hashed (Maybe Value)

0 commit comments

Comments
 (0)