@@ -9,30 +9,34 @@ module Development.IDE.LSP.Outline
9
9
where
10
10
11
11
import Control.Monad.IO.Class
12
- import Data.Foldable (toList )
12
+ import Data.Foldable (toList )
13
13
import Data.Functor
14
- import Data.Generics hiding (Prefix )
15
- import Data.List.NonEmpty (nonEmpty )
14
+ import Data.Generics hiding (Prefix )
15
+ import Data.List.NonEmpty (nonEmpty )
16
+ import Data.List.Extra (nubOrdOn )
16
17
import Data.Maybe
17
18
import Development.IDE.Core.Rules
19
+ import Development.IDE.Core.RuleTypes
18
20
import Development.IDE.Core.Shake
19
21
import Development.IDE.GHC.Compat
20
- import Development.IDE.GHC.Error (rangeToRealSrcSpan ,
21
- realSrcSpanToRange )
22
+ import Development.IDE.GHC.Error (rangeToRealSrcSpan ,
23
+ realSrcSpanToRange ,
24
+ realSrcLocToPosition )
25
+ import Development.IDE.Spans.LocalBindings (getFuzzyScope , bindings )
22
26
import Development.IDE.Types.Location
23
- import Development.IDE.GHC.Util (printOutputable )
27
+ import Development.IDE.GHC.Util (printOutputable )
24
28
import Ide.Types
25
- import Language.LSP.Protocol.Types (DocumentSymbol (.. ),
26
- DocumentSymbolParams (DocumentSymbolParams , _textDocument ),
27
- SymbolKind (.. ),
28
- TextDocumentIdentifier (TextDocumentIdentifier ),
29
- type (|? ) (InL , InR ), uriToFilePath )
29
+ import Language.LSP.Protocol.Types (DocumentSymbol (.. ),
30
+ DocumentSymbolParams (DocumentSymbolParams , _textDocument ),
31
+ SymbolKind (.. ),
32
+ TextDocumentIdentifier (TextDocumentIdentifier ),
33
+ type (|? ) (InL , InR ), uriToFilePath )
30
34
import Language.LSP.Protocol.Message
31
35
32
36
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
33
37
34
38
#if !MIN_VERSION_ghc(9,3,0)
35
- import qualified Data.Text as T
39
+ import qualified Data.Text as T
36
40
#endif
37
41
38
42
moduleOutline
@@ -41,11 +45,13 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
41
45
= liftIO $ case uriToFilePath uri of
42
46
Just (toNormalizedFilePath' -> fp) -> do
43
47
mb_decls <- fmap fst <$> runAction " Outline" ideState (useWithStale GetParsedModule fp)
48
+ mb_hieAst <- fmap fst <$> runAction " Outline" ideState (useWithStale GetHieAst fp)
44
49
pure $ case mb_decls of
45
50
Nothing -> InL []
46
51
Just ParsedModule { pm_parsed_source = L _ltop HsModule { hsmodName, hsmodDecls, hsmodImports } }
47
52
-> let
48
- declSymbols = mapMaybe documentSymbolForDecl hsmodDecls
53
+ refMap = maybe mempty getRefMap mb_hieAst
54
+ declSymbols = mapMaybe (documentSymbolForDecl refMap) hsmodDecls
49
55
moduleSymbol = hsmodName >>= \ case
50
56
(L (locA -> (RealSrcSpan l _)) m) -> Just $
51
57
(defDocumentSymbol l :: DocumentSymbol )
@@ -66,11 +72,16 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
66
72
in
67
73
InR (InL allSymbols)
68
74
69
-
70
75
Nothing -> pure $ InL []
71
76
72
- documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
73
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
77
+ getRefMap :: HieAstResult -> RefMap Type
78
+ getRefMap HAR {refMap= refMap, hieKind= hieKind} =
79
+ case hieKind of
80
+ HieFromDisk _ -> mempty
81
+ HieFresh -> refMap
82
+
83
+ documentSymbolForDecl :: RefMap Type -> LHsDecl GhcPs -> Maybe DocumentSymbol
84
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
74
85
= Just (defDocumentSymbol l :: DocumentSymbol )
75
86
{ _name = printOutputable n
76
87
<> (case printOutputable fdTyVars of
@@ -80,7 +91,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam =
80
91
, _detail = Just $ printOutputable fdInfo
81
92
, _kind = SymbolKind_Function
82
93
}
83
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
94
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
84
95
= Just (defDocumentSymbol l :: DocumentSymbol )
85
96
{ _name = printOutputable name
86
97
<> (case printOutputable tcdTyVars of
@@ -100,7 +111,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
100
111
, L (locA -> (RealSrcSpan l'' _)) n <- names
101
112
]
102
113
}
103
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
114
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
104
115
= Just (defDocumentSymbol l :: DocumentSymbol )
105
116
{ _name = printOutputable name
106
117
, _kind = SymbolKind_Struct
@@ -136,16 +147,16 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
136
147
, _kind = SymbolKind_Field
137
148
}
138
149
cvtFld _ = Nothing
139
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
150
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
140
151
(defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputable n
141
152
, _kind = SymbolKind_TypeParameter
142
153
, _selectionRange = realSrcSpanToRange l'
143
154
}
144
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
155
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
145
156
= Just (defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputable cid_poly_ty
146
157
, _kind = SymbolKind_Interface
147
158
}
148
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl FamEqn { feqn_tycon, feqn_pats } }))
159
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl FamEqn { feqn_tycon, feqn_pats } }))
149
160
= Just (defDocumentSymbol l :: DocumentSymbol )
150
161
{ _name =
151
162
#if MIN_VERSION_ghc(9,3,0)
@@ -156,7 +167,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
156
167
#endif
157
168
, _kind = SymbolKind_Interface
158
169
}
159
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl _ FamEqn { feqn_tycon, feqn_pats } }))
170
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl _ FamEqn { feqn_tycon, feqn_pats } }))
160
171
= Just (defDocumentSymbol l :: DocumentSymbol )
161
172
{ _name =
162
173
#if MIN_VERSION_ghc(9,3,0)
@@ -167,24 +178,36 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
167
178
#endif
168
179
, _kind = SymbolKind_Interface
169
180
}
170
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
181
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
171
182
gfindtype deriv_type <&> \ (L (_ :: SrcSpan ) name) ->
172
183
(defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputable @ (HsType GhcPs )
173
184
name
174
185
, _kind = SymbolKind_Interface
175
186
}
176
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind {fun_id = L _ name})) = Just
177
- (defDocumentSymbol l :: DocumentSymbol )
178
- { _name = printOutputable name
179
- , _kind = SymbolKind_Function
180
- }
181
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind {pat_lhs})) = Just
187
+ documentSymbolForDecl refMap decl@ (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind {fun_id = L _ name})) = Just
188
+ (mkFunDocSym name)
189
+ { _children = toMaybe localDocSyms
190
+ }
191
+ where
192
+ mkFunDocSym :: Outputable n => n -> DocumentSymbol
193
+ mkFunDocSym n =
194
+ (defDocumentSymbol l :: DocumentSymbol )
195
+ { _name = printOutputable n
196
+ , _kind = SymbolKind_Function
197
+ }
198
+
199
+ toMaybe [] = Nothing
200
+ toMaybe xs = Just xs
201
+
202
+ localDocSyms = map mkFunDocSym (getLocalBindings refMap decl)
203
+
204
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind {pat_lhs})) = Just
182
205
(defDocumentSymbol l :: DocumentSymbol )
183
206
{ _name = printOutputable pat_lhs
184
207
, _kind = SymbolKind_Function
185
208
}
186
209
187
- documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
210
+ documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
188
211
(defDocumentSymbol l :: DocumentSymbol )
189
212
{ _name = case x of
190
213
ForeignImport {} -> name
@@ -196,7 +219,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
196
219
}
197
220
where name = printOutputable $ unLoc $ fd_name x
198
221
199
- documentSymbolForDecl _ = Nothing
222
+ documentSymbolForDecl _ _ = Nothing
200
223
201
224
-- | Wrap the Document imports into a hierarchical outline for
202
225
-- a better overview of symbols in scope.
@@ -282,4 +305,11 @@ hsConDeclsBinders cons
282
305
-> [LFieldOcc GhcPs ]
283
306
get_flds flds = concatMap (cd_fld_names . unLoc) (unLoc flds)
284
307
285
-
308
+ getLocalBindings :: RefMap Type -> LHsDecl GhcPs -> [Name ]
309
+ getLocalBindings refmap (L (locA -> (RealSrcSpan l _)) _) =
310
+ nubOrdOn getOccFS . filter isVarName . map fst $ locals
311
+ where
312
+ locals = getFuzzyScope (bindings refmap) start end
313
+ start = realSrcLocToPosition (realSrcSpanStart l)
314
+ end = realSrcLocToPosition (realSrcSpanEnd l)
315
+ getLocalBindings _ _ = []
0 commit comments