Skip to content

Commit 62fb5c1

Browse files
committed
Add local definitions to outline
1 parent 597da9d commit 62fb5c1

File tree

2 files changed

+75
-33
lines changed

2 files changed

+75
-33
lines changed

ghcide/src/Development/IDE/LSP/Outline.hs

+62-32
Original file line numberDiff line numberDiff line change
@@ -9,30 +9,34 @@ module Development.IDE.LSP.Outline
99
where
1010

1111
import Control.Monad.IO.Class
12-
import Data.Foldable (toList)
12+
import Data.Foldable (toList)
1313
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)
1617
import Data.Maybe
1718
import Development.IDE.Core.Rules
19+
import Development.IDE.Core.RuleTypes
1820
import Development.IDE.Core.Shake
1921
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)
2226
import Development.IDE.Types.Location
23-
import Development.IDE.GHC.Util (printOutputable)
27+
import Development.IDE.GHC.Util (printOutputable)
2428
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)
3034
import Language.LSP.Protocol.Message
3135

3236
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
3337

3438
#if !MIN_VERSION_ghc(9,3,0)
35-
import qualified Data.Text as T
39+
import qualified Data.Text as T
3640
#endif
3741

3842
moduleOutline
@@ -41,11 +45,13 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
4145
= liftIO $ case uriToFilePath uri of
4246
Just (toNormalizedFilePath' -> fp) -> do
4347
mb_decls <- fmap fst <$> runAction "Outline" ideState (useWithStale GetParsedModule fp)
48+
mb_hieAst <- fmap fst <$> runAction "Outline" ideState (useWithStale GetHieAst fp)
4449
pure $ case mb_decls of
4550
Nothing -> InL []
4651
Just ParsedModule { pm_parsed_source = L _ltop HsModule { hsmodName, hsmodDecls, hsmodImports } }
4752
-> let
48-
declSymbols = mapMaybe documentSymbolForDecl hsmodDecls
53+
refMap = maybe mempty getRefMap mb_hieAst
54+
declSymbols = mapMaybe (documentSymbolForDecl refMap) hsmodDecls
4955
moduleSymbol = hsmodName >>= \case
5056
(L (locA -> (RealSrcSpan l _)) m) -> Just $
5157
(defDocumentSymbol l :: DocumentSymbol)
@@ -66,11 +72,16 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
6672
in
6773
InR (InL allSymbols)
6874

69-
7075
Nothing -> pure $ InL []
7176

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 } }))
7485
= Just (defDocumentSymbol l :: DocumentSymbol)
7586
{ _name = printOutputable n
7687
<> (case printOutputable fdTyVars of
@@ -80,7 +91,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam =
8091
, _detail = Just $ printOutputable fdInfo
8192
, _kind = SymbolKind_Function
8293
}
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 }))
8495
= Just (defDocumentSymbol l :: DocumentSymbol)
8596
{ _name = printOutputable name
8697
<> (case printOutputable tcdTyVars of
@@ -100,7 +111,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
100111
, L (locA -> (RealSrcSpan l'' _)) n <- names
101112
]
102113
}
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 } }))
104115
= Just (defDocumentSymbol l :: DocumentSymbol)
105116
{ _name = printOutputable name
106117
, _kind = SymbolKind_Struct
@@ -136,16 +147,16 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
136147
, _kind = SymbolKind_Field
137148
}
138149
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
140151
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable n
141152
, _kind = SymbolKind_TypeParameter
142153
, _selectionRange = realSrcSpanToRange l'
143154
}
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 } }))
145156
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable cid_poly_ty
146157
, _kind = SymbolKind_Interface
147158
}
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 } }))
149160
= Just (defDocumentSymbol l :: DocumentSymbol)
150161
{ _name =
151162
#if MIN_VERSION_ghc(9,3,0)
@@ -156,7 +167,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
156167
#endif
157168
, _kind = SymbolKind_Interface
158169
}
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 } }))
160171
= Just (defDocumentSymbol l :: DocumentSymbol)
161172
{ _name =
162173
#if MIN_VERSION_ghc(9,3,0)
@@ -167,24 +178,36 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
167178
#endif
168179
, _kind = SymbolKind_Interface
169180
}
170-
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
181+
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
171182
gfindtype deriv_type <&> \(L (_ :: SrcSpan) name) ->
172183
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable @(HsType GhcPs)
173184
name
174185
, _kind = SymbolKind_Interface
175186
}
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
182205
(defDocumentSymbol l :: DocumentSymbol)
183206
{ _name = printOutputable pat_lhs
184207
, _kind = SymbolKind_Function
185208
}
186209

187-
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
210+
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
188211
(defDocumentSymbol l :: DocumentSymbol)
189212
{ _name = case x of
190213
ForeignImport{} -> name
@@ -196,7 +219,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
196219
}
197220
where name = printOutputable $ unLoc $ fd_name x
198221

199-
documentSymbolForDecl _ = Nothing
222+
documentSymbolForDecl _ _ = Nothing
200223

201224
-- | Wrap the Document imports into a hierarchical outline for
202225
-- a better overview of symbols in scope.
@@ -282,4 +305,11 @@ hsConDeclsBinders cons
282305
-> [LFieldOcc GhcPs]
283306
get_flds flds = concatMap (cd_fld_names . unLoc) (unLoc flds)
284307

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 _ _ = []

ghcide/test/exe/OutlineTests.hs

+13-1
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,19 @@ tests =
6565
testSymbolsA "constant" ["a = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 6)],
6666
testSymbolsA "pattern" ["Just foo = Just 21"] [docSymbol "Just foo" SymbolKind_Function (R 0 0 0 18)],
6767
testSymbolsA "pattern with type signature" ["{-# language ScopedTypeVariables #-}", "a :: () = ()"] [docSymbol "a :: ()" SymbolKind_Function (R 1 0 1 12)],
68-
testSymbolsA "function" ["a _x = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 9)],
68+
testSymbolsA
69+
"function"
70+
["a _x = ()"]
71+
[ docSymbolWithChildren
72+
"a"
73+
SymbolKind_Function
74+
(R 0 0 0 9)
75+
[ docSymbol
76+
"_x"
77+
SymbolKind_Function
78+
(R 0 0 0 9)
79+
]
80+
],
6981
testSymbolsA "type synonym" ["type A = Bool"] [docSymbol' "A" SymbolKind_TypeParameter (R 0 0 0 13) (R 0 5 0 6)],
7082
testSymbolsA "datatype" ["data A = C"] [docSymbolWithChildren "A" SymbolKind_Struct (R 0 0 0 10) [docSymbol "C" SymbolKind_Constructor (R 0 9 0 10)]],
7183
testSymbolsA

0 commit comments

Comments
 (0)