Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Add local definitions to outline #4312

Open
wants to merge 2 commits into
base: master
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
94 changes: 62 additions & 32 deletions ghcide/src/Development/IDE/LSP/Outline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,30 +9,34 @@ module Development.IDE.LSP.Outline
where

import Control.Monad.IO.Class
import Data.Foldable (toList)
import Data.Foldable (toList)
import Data.Functor
import Data.Generics hiding (Prefix)
import Data.List.NonEmpty (nonEmpty)
import Data.Generics hiding (Prefix)
import Data.List.NonEmpty (nonEmpty)
import Data.List.Extra (nubOrdOn)
import Data.Maybe
import Development.IDE.Core.Rules
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Shake
import Development.IDE.GHC.Compat
import Development.IDE.GHC.Error (rangeToRealSrcSpan,
realSrcSpanToRange)
import Development.IDE.GHC.Error (rangeToRealSrcSpan,
realSrcSpanToRange,
realSrcLocToPosition)
import Development.IDE.Spans.LocalBindings (getFuzzyScope, bindings)
import Development.IDE.Types.Location
import Development.IDE.GHC.Util (printOutputable)
import Development.IDE.GHC.Util (printOutputable)
import Ide.Types
import Language.LSP.Protocol.Types (DocumentSymbol (..),
DocumentSymbolParams (DocumentSymbolParams, _textDocument),
SymbolKind (..),
TextDocumentIdentifier (TextDocumentIdentifier),
type (|?) (InL, InR), uriToFilePath)
import Language.LSP.Protocol.Types (DocumentSymbol (..),
DocumentSymbolParams (DocumentSymbolParams, _textDocument),
SymbolKind (..),
TextDocumentIdentifier (TextDocumentIdentifier),
type (|?) (InL, InR), uriToFilePath)
import Language.LSP.Protocol.Message

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

#if !MIN_VERSION_ghc(9,3,0)
import qualified Data.Text as T
import qualified Data.Text as T
#endif

moduleOutline
Expand All @@ -41,11 +45,13 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
= liftIO $ case uriToFilePath uri of
Just (toNormalizedFilePath' -> fp) -> do
mb_decls <- fmap fst <$> runAction "Outline" ideState (useWithStale GetParsedModule fp)
mb_hieAst <- fmap fst <$> runAction "Outline" ideState (useWithStale GetHieAst fp)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hmmm, these are both ignoring the position mapping, which is probably risky? It means we might create document symbols with out-of-date locations.

pure $ case mb_decls of
Nothing -> InL []
Just ParsedModule { pm_parsed_source = L _ltop HsModule { hsmodName, hsmodDecls, hsmodImports } }
-> let
declSymbols = mapMaybe documentSymbolForDecl hsmodDecls
refMap = maybe mempty getRefMap mb_hieAst
declSymbols = mapMaybe (documentSymbolForDecl refMap) hsmodDecls
moduleSymbol = hsmodName >>= \case
(L (locA -> (RealSrcSpan l _)) m) -> Just $
(defDocumentSymbol l :: DocumentSymbol)
Expand All @@ -66,11 +72,16 @@ moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdent
in
InR (InL allSymbols)


Nothing -> pure $ InL []

documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
getRefMap :: HieAstResult -> RefMap Type
getRefMap HAR{refMap=refMap, hieKind=hieKind} =
case hieKind of
HieFromDisk _ -> mempty
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I have a question, why we use mempty for HieFromDisk here

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This is mostly because I needed a RefMap Type, and I didn't know how to get there from RefMap TypeIndex. If this is important, I can keep hacking.

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Maybe you can find some inspiration for how to recover full types here?

HieFresh -> printOutputable t
HieFromDisk full_file -> printOutputable $ hieTypeToIface $ recoverFullType t (hie_types full_file)

HieFresh -> refMap

documentSymbolForDecl :: RefMap Type -> LHsDecl GhcPs -> Maybe DocumentSymbol
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
= Just (defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable n
<> (case printOutputable fdTyVars of
Expand All @@ -80,7 +91,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam =
, _detail = Just $ printOutputable fdInfo
, _kind = SymbolKind_Function
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
= Just (defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable name
<> (case printOutputable tcdTyVars of
Expand All @@ -100,7 +111,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
, L (locA -> (RealSrcSpan l'' _)) n <- names
]
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
= Just (defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable name
, _kind = SymbolKind_Struct
Expand Down Expand Up @@ -136,16 +147,16 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
, _kind = SymbolKind_Field
}
cvtFld _ = Nothing
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable n
, _kind = SymbolKind_TypeParameter
, _selectionRange = realSrcSpanToRange l'
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable cid_poly_ty
, _kind = SymbolKind_Interface
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl FamEqn { feqn_tycon, feqn_pats } }))
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl FamEqn { feqn_tycon, feqn_pats } }))
= Just (defDocumentSymbol l :: DocumentSymbol)
{ _name =
#if MIN_VERSION_ghc(9,3,0)
Expand All @@ -156,7 +167,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
#endif
, _kind = SymbolKind_Interface
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl _ FamEqn { feqn_tycon, feqn_pats } }))
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl _ FamEqn { feqn_tycon, feqn_pats } }))
= Just (defDocumentSymbol l :: DocumentSymbol)
{ _name =
#if MIN_VERSION_ghc(9,3,0)
Expand All @@ -167,24 +178,36 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
#endif
, _kind = SymbolKind_Interface
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
gfindtype deriv_type <&> \(L (_ :: SrcSpan) name) ->
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable @(HsType GhcPs)
name
, _kind = SymbolKind_Interface
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind{fun_id = L _ name})) = Just
(defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable name
, _kind = SymbolKind_Function
}
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind{pat_lhs})) = Just
documentSymbolForDecl refMap decl@(L (locA -> (RealSrcSpan l _)) (ValD _ FunBind{fun_id = L _ name})) = Just
(mkFunDocSym name)
{ _children = toMaybe localDocSyms
}
where
mkFunDocSym :: Outputable n => n -> DocumentSymbol
mkFunDocSym n =
(defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable n
, _kind = SymbolKind_Function
}

toMaybe [] = Nothing
toMaybe xs = Just xs

localDocSyms = map mkFunDocSym (getLocalBindings refMap decl)

documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind{pat_lhs})) = Just
(defDocumentSymbol l :: DocumentSymbol)
{ _name = printOutputable pat_lhs
, _kind = SymbolKind_Function
}

documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
documentSymbolForDecl _ (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
(defDocumentSymbol l :: DocumentSymbol)
{ _name = case x of
ForeignImport{} -> name
Expand All @@ -196,7 +219,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
}
where name = printOutputable $ unLoc $ fd_name x

documentSymbolForDecl _ = Nothing
documentSymbolForDecl _ _ = Nothing

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


getLocalBindings :: RefMap Type -> LHsDecl GhcPs -> [Name]
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This could do with some explanation: I'm not sure reading this why this is the right way to get the local bindings.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

What is confusing? Is it the use of getFuzzyScope or is it something else?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I guess I'm just rather unsure why this is the right thing to do? Why is it okay to use getFuzzyScope rather than getLocalScope? What's going on with position mapping?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

According to my testing, getLocalScope only returns symbols at the current start point (the start of the given function), which does not appear to have the locals in scope. getFuzzyScope returns all symbols that have intersecting scopes. This makes sense to me when I look at the docs for IntervalMap.FingerTree's dominator (getLocalScope) and intersections (getFuzzyScope):

dominators:

O(k log (n/k)). All intervals that contain the given interval, in lexicographical order.

intersections

O(k log (n/k)). All intervals that intersect with the given interval, in lexicographical order.

It's clear that there at least needs a comment there, but maybe it would be better to create a new function with a clearer name?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

According to my testing, getLocalScope only returns symbols at the current start point (the start of the given function), which does not appear to have the locals in scope.

I feel confused about what getLocalScope is for then, if not this? Are we using it wrong?

getLocalBindings refmap (L (locA -> (RealSrcSpan l _)) _) =
nubOrdOn getOccFS . filter isVarName . map fst $ locals
where
locals = getFuzzyScope (bindings refmap) start end
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This doesn't recurse, right? So presumably this won't handle something like:

f = ...
  where
     g = ...
       where
          h = ...

?

Worth adding as a test case even if we don't support it, but also maybe we just can support it?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It actually does recurse, I've just pushed an update that adds this and the other test case below

start = realSrcLocToPosition (realSrcSpanStart l)
end = realSrcLocToPosition (realSrcSpanEnd l)
getLocalBindings _ _ = []
35 changes: 34 additions & 1 deletion ghcide/test/exe/OutlineTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,40 @@ tests =
testSymbolsA "constant" ["a = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 6)],
testSymbolsA "pattern" ["Just foo = Just 21"] [docSymbol "Just foo" SymbolKind_Function (R 0 0 0 18)],
testSymbolsA "pattern with type signature" ["{-# language ScopedTypeVariables #-}", "a :: () = ()"] [docSymbol "a :: ()" SymbolKind_Function (R 1 0 1 12)],
testSymbolsA "function" ["a _x = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 9)],
testSymbolsA
"function"
["a _x = ()"]
[ docSymbolWithChildren
"a"
SymbolKind_Function
(R 0 0 0 9)
[ docSymbol
"_x"
SymbolKind_Function
(R 0 0 0 9)
]
],
testSymbolsA
"function with nested scope"
["a x = g x where g = h where h = id"]
[ docSymbolWithChildren
"a"
SymbolKind_Function
(R 0 0 0 34)
[ docSymbol "x" SymbolKind_Function (R 0 0 0 34)
, docSymbol "g" SymbolKind_Function (R 0 0 0 34)
, docSymbol "h" SymbolKind_Function (R 0 0 0 34)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

These locations are wrong? They all have the range of the original binding?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Also, shouldn't h be a child of g, not of a?

]
],
testSymbolsA
"function with patterns"
["f 1 = g where g = 2", "f _ = g where g = 3"]
[ docSymbolWithChildren
"f"
SymbolKind_Function
(R 0 0 1 19)
[docSymbol "g" SymbolKind_Function (R 0 0 1 19)]
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This seems wrong, there should be two gs?

],
testSymbolsA "type synonym" ["type A = Bool"] [docSymbol' "A" SymbolKind_TypeParameter (R 0 0 0 13) (R 0 5 0 6)],
testSymbolsA "datatype" ["data A = C"] [docSymbolWithChildren "A" SymbolKind_Struct (R 0 0 0 10) [docSymbol "C" SymbolKind_Constructor (R 0 9 0 10)]],
testSymbolsA
Expand Down
Loading