Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit 3e38e39

Browse files
authored
Merge pull request #1107 from fendor/type-definition-request
Add ReqTypeDefinition to reactor
2 parents dad1635 + 6c59170 commit 3e38e39

18 files changed

+344
-57
lines changed

.gitmodules

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,4 +36,3 @@
3636
path = submodules/floskell
3737
url = https://github.com/ennocramer/floskell
3838
# url = https://github.com/alanz/floskell
39-

haskell-ide-engine.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,6 +265,7 @@ test-suite func-test
265265
, ReferencesSpec
266266
, RenameSpec
267267
, SymbolsSpec
268+
, TypeDefinitionSpec
268269
, Utils
269270
-- This cannot currently be handled by hie (cabal-helper)
270271
-- build-tool-depends: haskell-ide-engine:hie

src/Haskell/Ide/Engine/Support/HieExtras.hs

Lines changed: 98 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE ScopedTypeVariables #-}
44
{-# LANGUAGE OverloadedStrings #-}
55
{-# LANGUAGE TypeFamilies #-}
6+
{-# LANGUAGE LambdaCase #-}
67
module Haskell.Ide.Engine.Support.HieExtras
78
( getDynFlags
89
, WithSnippets(..)
@@ -12,6 +13,7 @@ module Haskell.Ide.Engine.Support.HieExtras
1213
, getReferencesInDoc
1314
, getModule
1415
, findDef
16+
, findTypeDef
1517
, showName
1618
, safeTyThingId
1719
, PosPrefixInfo(..)
@@ -28,6 +30,7 @@ import Control.Lens.Prism ( _Just )
2830
import Control.Lens.Setter ((%~))
2931
import Control.Lens.Traversal (traverseOf)
3032
import Control.Monad.Reader
33+
import Control.Monad.Except
3134
import Data.Aeson
3235
import qualified Data.Aeson.Types as J
3336
import Data.Char
@@ -476,6 +479,9 @@ getTypeForName n = do
476479
getSymbolsAtPoint :: Position -> CachedInfo -> [(Range,Name)]
477480
getSymbolsAtPoint pos info = maybe [] (`getArtifactsAtPos` locMap info) $ newPosToOld info pos
478481

482+
-- |Get a symbol from the given location map at the given location.
483+
-- Retrieves the name and range of the symbol at the given location
484+
-- from the cached location map.
479485
symbolFromTypecheckedModule
480486
:: LocMap
481487
-> Position
@@ -538,6 +544,51 @@ getModule df n = do
538544

539545
-- ---------------------------------------------------------------------
540546

547+
-- | Return the type definition of the symbol at the given position.
548+
-- Works for Datatypes, Newtypes and Type Definitions, as well as paremterized types.
549+
-- Type Definitions can only be looked up, if the corresponding type is defined in the project.
550+
-- Sum Types can also be searched.
551+
findTypeDef :: Uri -> Position -> IdeDeferM (IdeResult [Location])
552+
findTypeDef uri pos = pluginGetFile "findTypeDef: " uri $ \file ->
553+
withCachedInfo
554+
file
555+
(IdeResultOk []) -- Default result
556+
(\info -> do
557+
let rfm = revMap info
558+
tmap = typeMap info
559+
oldPos = newPosToOld info pos
560+
561+
-- | Get SrcSpan of the name at the given position.
562+
-- If the old position is Nothing, e.g. there is no cached info about it,
563+
-- Nothing is returned.
564+
--
565+
-- Otherwise, searches for the Type of the given position
566+
-- and retrieves its SrcSpan.
567+
getTypeSrcSpanFromPosition
568+
:: Maybe Position -> ExceptT () IdeDeferM SrcSpan
569+
getTypeSrcSpanFromPosition maybeOldPosition = do
570+
oldPosition <- liftMaybe maybeOldPosition
571+
let tmapRes = getArtifactsAtPos oldPosition tmap
572+
case tmapRes of
573+
[] -> throwError ()
574+
a -> do
575+
-- take last type since this is always the most accurate one
576+
tyCon <- liftMaybe $ tyConAppTyCon_maybe (snd $ last a)
577+
case nameSrcSpan (getName tyCon) of
578+
UnhelpfulSpan _ -> throwError ()
579+
realSpan -> return realSpan
580+
581+
liftMaybe :: Monad m => Maybe a -> ExceptT () m a
582+
liftMaybe val = liftEither $ case val of
583+
Nothing -> Left ()
584+
Just s -> Right s
585+
586+
runExceptT (getTypeSrcSpanFromPosition oldPos) >>= \case
587+
Left () -> return $ IdeResultOk []
588+
Right realSpan ->
589+
lift $ srcSpanToFileLocation "hare:findTypeDef" rfm realSpan
590+
)
591+
541592
-- | Return the definition
542593
findDef :: Uri -> Position -> IdeDeferM (IdeResult [Location])
543594
findDef uri pos = pluginGetFile "findDef: " uri $ \file ->
@@ -554,46 +605,53 @@ findDef uri pos = pluginGetFile "findDef: " uri $ \file ->
554605
Just (_, n) ->
555606
case nameSrcSpan n of
556607
UnhelpfulSpan _ -> return $ IdeResultOk []
557-
realSpan -> do
558-
res <- srcSpan2Loc rfm realSpan
559-
case res of
560-
Right l@(J.Location luri range) ->
561-
case uriToFilePath luri of
562-
Nothing -> return $ IdeResultOk [l]
563-
Just fp -> ifCachedModule fp (IdeResultOk [l]) $ \(_ :: ParsedModule) info' ->
564-
case oldRangeToNew info' range of
565-
Just r -> return $ IdeResultOk [J.Location luri r]
566-
Nothing -> return $ IdeResultOk [l]
567-
Left x -> do
568-
debugm "findDef: name srcspan not found/valid"
569-
pure (IdeResultFail
570-
(IdeError PluginError
571-
("hare:findDef" <> ": \"" <> x <> "\"")
572-
Null)))
573-
where
574-
gotoModule :: (FilePath -> FilePath) -> ModuleName -> IdeDeferM (IdeResult [Location])
575-
gotoModule rfm mn = do
576-
577-
hscEnvRef <- ghcSession <$> readMTS
578-
mHscEnv <- liftIO $ traverse readIORef hscEnvRef
579-
580-
case mHscEnv of
581-
Just env -> do
582-
fr <- liftIO $ do
583-
-- Flush cache or else we get temporary files
584-
flushFinderCaches env
585-
findImportedModule env mn Nothing
586-
case fr of
587-
Found (ModLocation (Just src) _ _) _ -> do
588-
fp <- reverseMapFile rfm src
589-
590-
let r = Range (Position 0 0) (Position 0 0)
591-
loc = Location (filePathToUri fp) r
592-
return (IdeResultOk [loc])
593-
_ -> return (IdeResultOk [])
594-
Nothing -> return $ IdeResultFail
595-
(IdeError PluginError "Couldn't get hscEnv when finding import" Null)
596-
608+
realSpan -> lift $ srcSpanToFileLocation "hare:findDef" rfm realSpan
609+
)
610+
611+
-- | Resolve the given SrcSpan to a Location in a file.
612+
-- Takes the name of the invoking function for error display.
613+
--
614+
-- If the SrcSpan can not be resolved, an error will be returned.
615+
srcSpanToFileLocation :: T.Text -> (FilePath -> FilePath) -> SrcSpan -> IdeM (IdeResult [Location])
616+
srcSpanToFileLocation invoker rfm srcSpan = do
617+
-- Since we found a real SrcSpan, try to map it to real files
618+
res <- srcSpan2Loc rfm srcSpan
619+
case res of
620+
Right l@(J.Location luri range) ->
621+
case uriToFilePath luri of
622+
Nothing -> return $ IdeResultOk [l]
623+
Just fp -> ifCachedModule fp (IdeResultOk [l]) $ \(_ :: ParsedModule) info' ->
624+
case oldRangeToNew info' range of
625+
Just r -> return $ IdeResultOk [J.Location luri r]
626+
Nothing -> return $ IdeResultOk [l]
627+
Left x -> do
628+
debugm (T.unpack invoker <> ": name srcspan not found/valid")
629+
pure (IdeResultFail
630+
(IdeError PluginError
631+
(invoker <> ": \"" <> x <> "\"")
632+
Null))
633+
634+
-- | Goto given module.
635+
gotoModule :: (FilePath -> FilePath) -> ModuleName -> IdeDeferM (IdeResult [Location])
636+
gotoModule rfm mn = do
637+
hscEnvRef <- ghcSession <$> readMTS
638+
mHscEnv <- liftIO $ traverse readIORef hscEnvRef
639+
case mHscEnv of
640+
Just env -> do
641+
fr <- liftIO $ do
642+
-- Flush cache or else we get temporary files
643+
flushFinderCaches env
644+
findImportedModule env mn Nothing
645+
case fr of
646+
Found (ModLocation (Just src) _ _) _ -> do
647+
fp <- reverseMapFile rfm src
648+
649+
let r = Range (Position 0 0) (Position 0 0)
650+
loc = Location (filePathToUri fp) r
651+
return (IdeResultOk [loc])
652+
_ -> return (IdeResultOk [])
653+
Nothing -> return $ IdeResultFail
654+
(IdeError PluginError "Couldn't get hscEnv when finding import" Null)
597655
-- ---------------------------------------------------------------------
598656

599657
data HarePoint =

src/Haskell/Ide/Engine/Transport/LspStdio.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -706,6 +706,16 @@ reactor inp diagIn = do
706706
$ fmap J.MultiLoc <$> Hie.findDef doc pos
707707
makeRequest hreq
708708

709+
ReqTypeDefinition req -> do
710+
liftIO $ U.logs $ "reactor:got DefinitionTypeRequest:" ++ show req
711+
let params = req ^. J.params
712+
doc = params ^. J.textDocument . J.uri
713+
pos = params ^. J.position
714+
callback = reactorSend . RspTypeDefinition . Core.makeResponseMessage req
715+
let hreq = IReq tn (req ^. J.id) callback
716+
$ fmap J.MultiLoc <$> Hie.findTypeDef doc pos
717+
makeRequest hreq
718+
709719
ReqFindReferences req -> do
710720
liftIO $ U.logs $ "reactor:got FindReferences:" ++ show req
711721
-- TODO: implement project-wide references
@@ -971,6 +981,7 @@ hieHandlers rin
971981
= def { Core.initializedHandler = Just $ passHandler rin NotInitialized
972982
, Core.renameHandler = Just $ passHandler rin ReqRename
973983
, Core.definitionHandler = Just $ passHandler rin ReqDefinition
984+
, Core.typeDefinitionHandler = Just $ passHandler rin ReqTypeDefinition
974985
, Core.referencesHandler = Just $ passHandler rin ReqFindReferences
975986
, Core.hoverHandler = Just $ passHandler rin ReqHover
976987
, Core.didOpenTextDocumentNotificationHandler = Just $ passHandler rin NotDidOpenTextDocument

stack-8.2.1.yaml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,12 +19,13 @@ extra-deps:
1919
- ghc-exactprint-0.5.8.2
2020
- haddock-api-2.18.1
2121
- haddock-library-1.4.4
22-
- haskell-lsp-0.8.0.1
22+
- haskell-lsp-0.8.1.0
2323
- haskell-lsp-types-0.8.0.1
2424
- hlint-2.0.11
2525
- hsimport-0.8.6
26-
- lsp-test-0.5.0.2
26+
- lsp-test-0.5.1.0
2727
- monad-dijkstra-0.1.1.2
28+
- mtl-2.2.2
2829
- pretty-show-1.8.2
2930
- sorted-list-0.2.1.0
3031
- syz-0.2.0.0

stack-8.2.2.yaml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,13 +20,13 @@ extra-deps:
2020
- ghc-exactprint-0.5.8.2
2121
- haddock-api-2.18.1
2222
- haddock-library-1.4.4
23-
- haskell-lsp-0.8.0.1
23+
- haskell-lsp-0.8.1.0
2424
- haskell-lsp-types-0.8.0.1
2525
- haskell-src-exts-1.21.0
2626
- hlint-2.1.15
2727
- hoogle-5.0.17.5
2828
- hsimport-0.8.8
29-
- lsp-test-0.5.0.2
29+
- lsp-test-0.5.1.0
3030
- monad-dijkstra-0.1.1.2
3131
- pretty-show-1.8.2
3232
- sorted-list-0.2.1.0

stack-8.4.2.yaml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,13 +18,13 @@ extra-deps:
1818
- ghc-exactprint-0.5.8.2
1919
- haddock-api-2.20.0
2020
- haddock-library-1.6.0
21-
- haskell-lsp-0.8.0.1
21+
- haskell-lsp-0.8.1.0
2222
- haskell-lsp-types-0.8.0.1
2323
- haskell-src-exts-1.21.0
2424
- hlint-2.1.15
2525
- hoogle-5.0.17.5
2626
- hsimport-0.8.8
27-
- lsp-test-0.5.0.2
27+
- lsp-test-0.5.1.0
2828
- monad-dijkstra-0.1.1.2
2929
- pretty-show-1.8.2
3030
- syz-0.2.0.0

stack-8.4.3.yaml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,13 @@ extra-deps:
1717
- ghc-exactprint-0.5.8.2
1818
- haddock-api-2.20.0
1919
- haddock-library-1.6.0
20-
- haskell-lsp-0.8.0.1
20+
- haskell-lsp-0.8.1.0
2121
- haskell-lsp-types-0.8.0.1
2222
- haskell-src-exts-1.21.0
2323
- hlint-2.1.15
2424
- hoogle-5.0.17.5
2525
- hsimport-0.8.8
26-
- lsp-test-0.5.0.2
26+
- lsp-test-0.5.1.0
2727
- monad-dijkstra-0.1.1.2
2828
- pretty-show-1.8.2
2929
- syz-0.2.0.0

stack-8.4.4.yaml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,13 @@ extra-deps:
1717
- ghc-exactprint-0.5.8.2
1818
- haddock-api-2.20.0
1919
- haddock-library-1.6.0
20-
- haskell-lsp-0.8.0.1
20+
- haskell-lsp-0.8.1.0
2121
- haskell-lsp-types-0.8.0.1
2222
- haskell-src-exts-1.21.0
2323
- hlint-2.1.15
2424
- hoogle-5.0.17.5
2525
- hsimport-0.8.8
26-
- lsp-test-0.5.0.2
26+
- lsp-test-0.5.1.0
2727
- monad-dijkstra-0.1.1.2
2828
- optparse-simple-0.1.0
2929
- pretty-show-1.9.5

stack-8.6.1.yaml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,13 +19,13 @@ extra-deps:
1919
- czipwith-1.0.1.1
2020
- data-tree-print-0.1.0.2
2121
- haddock-api-2.21.0
22-
- haskell-lsp-0.8.0.1
22+
- haskell-lsp-0.8.1.0
2323
- haskell-lsp-types-0.8.0.1
2424
- haskell-src-exts-1.21.0
2525
- hlint-2.1.15
2626
- hoogle-5.0.17.5
2727
- hsimport-0.8.8
28-
- lsp-test-0.5.0.2
28+
- lsp-test-0.5.1.0
2929
- monad-dijkstra-0.1.1.2
3030
- monad-memo-0.4.1
3131
- monoid-subclasses-0.4.6.1

stack-8.6.2.yaml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,11 @@ extra-deps:
1616
- constrained-dynamic-0.1.0.0
1717
- haddock-api-2.21.0
1818
- haskell-src-exts-1.21.0
19+
- haskell-lsp-0.8.1.0
1920
- hlint-2.1.15
2021
- hoogle-5.0.17.5
2122
- hsimport-0.8.8
23+
- lsp-test-0.5.1.0
2224
- monad-dijkstra-0.1.1.2
2325
- monad-memo-0.4.1
2426
- multistate-0.8.0.1

stack-8.6.3.yaml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,11 @@ extra-deps:
1616
- constrained-dynamic-0.1.0.0
1717
- haddock-api-2.21.0
1818
- haskell-src-exts-1.21.0
19+
- haskell-lsp-0.8.1.0
1920
- hlint-2.1.15
2021
- hoogle-5.0.17.5
2122
- hsimport-0.8.8
23+
- lsp-test-0.5.1.0
2224
- monad-dijkstra-0.1.1.2
2325
- monad-memo-0.4.1
2426
- multistate-0.8.0.1

stack-8.6.4.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ extra-deps:
1919
- hlint-2.1.15
2020
- hsimport-0.8.8
2121
- hoogle-5.0.17.6
22+
- lsp-test-0.5.1.0
2223
- monad-dijkstra-0.1.1.2@rev:1
2324
- monad-memo-0.4.1
2425
- multistate-0.8.0.1

stack.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ extra-deps:
2020
- haddock-api-2.22.0
2121
- hlint-2.1.15
2222
- hsimport-0.8.8
23+
- lsp-test-0.5.1.0
2324
- monad-dijkstra-0.1.1.2@rev:1
2425
- monad-memo-0.4.1
2526
- multistate-0.8.0.1

0 commit comments

Comments
 (0)