diff --git a/.gitmodules b/.gitmodules index 9a1155a22..96fb9f937 100644 --- a/.gitmodules +++ b/.gitmodules @@ -36,4 +36,3 @@ path = submodules/floskell url = https://github.com/ennocramer/floskell # url = https://github.com/alanz/floskell - diff --git a/haskell-ide-engine.cabal b/haskell-ide-engine.cabal index 0416cea1f..e116c9c72 100644 --- a/haskell-ide-engine.cabal +++ b/haskell-ide-engine.cabal @@ -265,6 +265,7 @@ test-suite func-test , ReferencesSpec , RenameSpec , SymbolsSpec + , TypeDefinitionSpec , Utils -- This cannot currently be handled by hie (cabal-helper) -- build-tool-depends: haskell-ide-engine:hie diff --git a/src/Haskell/Ide/Engine/Support/HieExtras.hs b/src/Haskell/Ide/Engine/Support/HieExtras.hs index b8926b2f3..c4807f126 100644 --- a/src/Haskell/Ide/Engine/Support/HieExtras.hs +++ b/src/Haskell/Ide/Engine/Support/HieExtras.hs @@ -3,6 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE LambdaCase #-} module Haskell.Ide.Engine.Support.HieExtras ( getDynFlags , WithSnippets(..) @@ -12,6 +13,7 @@ module Haskell.Ide.Engine.Support.HieExtras , getReferencesInDoc , getModule , findDef + , findTypeDef , showName , safeTyThingId , PosPrefixInfo(..) @@ -28,6 +30,7 @@ import Control.Lens.Prism ( _Just ) import Control.Lens.Setter ((%~)) import Control.Lens.Traversal (traverseOf) import Control.Monad.Reader +import Control.Monad.Except import Data.Aeson import qualified Data.Aeson.Types as J import Data.Char @@ -476,6 +479,9 @@ getTypeForName n = do getSymbolsAtPoint :: Position -> CachedInfo -> [(Range,Name)] getSymbolsAtPoint pos info = maybe [] (`getArtifactsAtPos` locMap info) $ newPosToOld info pos +-- |Get a symbol from the given location map at the given location. +-- Retrieves the name and range of the symbol at the given location +-- from the cached location map. symbolFromTypecheckedModule :: LocMap -> Position @@ -538,6 +544,51 @@ getModule df n = do -- --------------------------------------------------------------------- +-- | Return the type definition of the symbol at the given position. +-- Works for Datatypes, Newtypes and Type Definitions, as well as paremterized types. +-- Type Definitions can only be looked up, if the corresponding type is defined in the project. +-- Sum Types can also be searched. +findTypeDef :: Uri -> Position -> IdeDeferM (IdeResult [Location]) +findTypeDef uri pos = pluginGetFile "findTypeDef: " uri $ \file -> + withCachedInfo + file + (IdeResultOk []) -- Default result + (\info -> do + let rfm = revMap info + tmap = typeMap info + oldPos = newPosToOld info pos + + -- | Get SrcSpan of the name at the given position. + -- If the old position is Nothing, e.g. there is no cached info about it, + -- Nothing is returned. + -- + -- Otherwise, searches for the Type of the given position + -- and retrieves its SrcSpan. + getTypeSrcSpanFromPosition + :: Maybe Position -> ExceptT () IdeDeferM SrcSpan + getTypeSrcSpanFromPosition maybeOldPosition = do + oldPosition <- liftMaybe maybeOldPosition + let tmapRes = getArtifactsAtPos oldPosition tmap + case tmapRes of + [] -> throwError () + a -> do + -- take last type since this is always the most accurate one + tyCon <- liftMaybe $ tyConAppTyCon_maybe (snd $ last a) + case nameSrcSpan (getName tyCon) of + UnhelpfulSpan _ -> throwError () + realSpan -> return realSpan + + liftMaybe :: Monad m => Maybe a -> ExceptT () m a + liftMaybe val = liftEither $ case val of + Nothing -> Left () + Just s -> Right s + + runExceptT (getTypeSrcSpanFromPosition oldPos) >>= \case + Left () -> return $ IdeResultOk [] + Right realSpan -> + lift $ srcSpanToFileLocation "hare:findTypeDef" rfm realSpan + ) + -- | Return the definition findDef :: Uri -> Position -> IdeDeferM (IdeResult [Location]) findDef uri pos = pluginGetFile "findDef: " uri $ \file -> @@ -554,46 +605,53 @@ findDef uri pos = pluginGetFile "findDef: " uri $ \file -> Just (_, n) -> case nameSrcSpan n of UnhelpfulSpan _ -> return $ IdeResultOk [] - realSpan -> do - res <- srcSpan2Loc rfm realSpan - case res of - Right l@(J.Location luri range) -> - case uriToFilePath luri of - Nothing -> return $ IdeResultOk [l] - Just fp -> ifCachedModule fp (IdeResultOk [l]) $ \(_ :: ParsedModule) info' -> - case oldRangeToNew info' range of - Just r -> return $ IdeResultOk [J.Location luri r] - Nothing -> return $ IdeResultOk [l] - Left x -> do - debugm "findDef: name srcspan not found/valid" - pure (IdeResultFail - (IdeError PluginError - ("hare:findDef" <> ": \"" <> x <> "\"") - Null))) - where - gotoModule :: (FilePath -> FilePath) -> ModuleName -> IdeDeferM (IdeResult [Location]) - gotoModule rfm mn = do - - hscEnvRef <- ghcSession <$> readMTS - mHscEnv <- liftIO $ traverse readIORef hscEnvRef - - case mHscEnv of - Just env -> do - fr <- liftIO $ do - -- Flush cache or else we get temporary files - flushFinderCaches env - findImportedModule env mn Nothing - case fr of - Found (ModLocation (Just src) _ _) _ -> do - fp <- reverseMapFile rfm src - - let r = Range (Position 0 0) (Position 0 0) - loc = Location (filePathToUri fp) r - return (IdeResultOk [loc]) - _ -> return (IdeResultOk []) - Nothing -> return $ IdeResultFail - (IdeError PluginError "Couldn't get hscEnv when finding import" Null) - + realSpan -> lift $ srcSpanToFileLocation "hare:findDef" rfm realSpan + ) + +-- | Resolve the given SrcSpan to a Location in a file. +-- Takes the name of the invoking function for error display. +-- +-- If the SrcSpan can not be resolved, an error will be returned. +srcSpanToFileLocation :: T.Text -> (FilePath -> FilePath) -> SrcSpan -> IdeM (IdeResult [Location]) +srcSpanToFileLocation invoker rfm srcSpan = do + -- Since we found a real SrcSpan, try to map it to real files + res <- srcSpan2Loc rfm srcSpan + case res of + Right l@(J.Location luri range) -> + case uriToFilePath luri of + Nothing -> return $ IdeResultOk [l] + Just fp -> ifCachedModule fp (IdeResultOk [l]) $ \(_ :: ParsedModule) info' -> + case oldRangeToNew info' range of + Just r -> return $ IdeResultOk [J.Location luri r] + Nothing -> return $ IdeResultOk [l] + Left x -> do + debugm (T.unpack invoker <> ": name srcspan not found/valid") + pure (IdeResultFail + (IdeError PluginError + (invoker <> ": \"" <> x <> "\"") + Null)) + +-- | Goto given module. +gotoModule :: (FilePath -> FilePath) -> ModuleName -> IdeDeferM (IdeResult [Location]) +gotoModule rfm mn = do + hscEnvRef <- ghcSession <$> readMTS + mHscEnv <- liftIO $ traverse readIORef hscEnvRef + case mHscEnv of + Just env -> do + fr <- liftIO $ do + -- Flush cache or else we get temporary files + flushFinderCaches env + findImportedModule env mn Nothing + case fr of + Found (ModLocation (Just src) _ _) _ -> do + fp <- reverseMapFile rfm src + + let r = Range (Position 0 0) (Position 0 0) + loc = Location (filePathToUri fp) r + return (IdeResultOk [loc]) + _ -> return (IdeResultOk []) + Nothing -> return $ IdeResultFail + (IdeError PluginError "Couldn't get hscEnv when finding import" Null) -- --------------------------------------------------------------------- data HarePoint = diff --git a/src/Haskell/Ide/Engine/Transport/LspStdio.hs b/src/Haskell/Ide/Engine/Transport/LspStdio.hs index 498a967c9..d87d58b9f 100644 --- a/src/Haskell/Ide/Engine/Transport/LspStdio.hs +++ b/src/Haskell/Ide/Engine/Transport/LspStdio.hs @@ -706,6 +706,16 @@ reactor inp diagIn = do $ fmap J.MultiLoc <$> Hie.findDef doc pos makeRequest hreq + ReqTypeDefinition req -> do + liftIO $ U.logs $ "reactor:got DefinitionTypeRequest:" ++ show req + let params = req ^. J.params + doc = params ^. J.textDocument . J.uri + pos = params ^. J.position + callback = reactorSend . RspTypeDefinition . Core.makeResponseMessage req + let hreq = IReq tn (req ^. J.id) callback + $ fmap J.MultiLoc <$> Hie.findTypeDef doc pos + makeRequest hreq + ReqFindReferences req -> do liftIO $ U.logs $ "reactor:got FindReferences:" ++ show req -- TODO: implement project-wide references @@ -971,6 +981,7 @@ hieHandlers rin = def { Core.initializedHandler = Just $ passHandler rin NotInitialized , Core.renameHandler = Just $ passHandler rin ReqRename , Core.definitionHandler = Just $ passHandler rin ReqDefinition + , Core.typeDefinitionHandler = Just $ passHandler rin ReqTypeDefinition , Core.referencesHandler = Just $ passHandler rin ReqFindReferences , Core.hoverHandler = Just $ passHandler rin ReqHover , Core.didOpenTextDocumentNotificationHandler = Just $ passHandler rin NotDidOpenTextDocument diff --git a/stack-8.2.1.yaml b/stack-8.2.1.yaml index 7bc04083d..8a4d2377c 100644 --- a/stack-8.2.1.yaml +++ b/stack-8.2.1.yaml @@ -19,12 +19,13 @@ extra-deps: - ghc-exactprint-0.5.8.2 - haddock-api-2.18.1 - haddock-library-1.4.4 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - hlint-2.0.11 - hsimport-0.8.6 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 +- mtl-2.2.2 - pretty-show-1.8.2 - sorted-list-0.2.1.0 - syz-0.2.0.0 diff --git a/stack-8.2.2.yaml b/stack-8.2.2.yaml index c8b9522c6..de309f9a5 100644 --- a/stack-8.2.2.yaml +++ b/stack-8.2.2.yaml @@ -20,13 +20,13 @@ extra-deps: - ghc-exactprint-0.5.8.2 - haddock-api-2.18.1 - haddock-library-1.4.4 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - haskell-src-exts-1.21.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - pretty-show-1.8.2 - sorted-list-0.2.1.0 diff --git a/stack-8.4.2.yaml b/stack-8.4.2.yaml index a8271094e..ebf88652c 100644 --- a/stack-8.4.2.yaml +++ b/stack-8.4.2.yaml @@ -18,13 +18,13 @@ extra-deps: - ghc-exactprint-0.5.8.2 - haddock-api-2.20.0 - haddock-library-1.6.0 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - haskell-src-exts-1.21.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - pretty-show-1.8.2 - syz-0.2.0.0 diff --git a/stack-8.4.3.yaml b/stack-8.4.3.yaml index 693a96f44..37d1afc45 100644 --- a/stack-8.4.3.yaml +++ b/stack-8.4.3.yaml @@ -17,13 +17,13 @@ extra-deps: - ghc-exactprint-0.5.8.2 - haddock-api-2.20.0 - haddock-library-1.6.0 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - haskell-src-exts-1.21.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - pretty-show-1.8.2 - syz-0.2.0.0 diff --git a/stack-8.4.4.yaml b/stack-8.4.4.yaml index 37feb5a9d..cb41a4926 100644 --- a/stack-8.4.4.yaml +++ b/stack-8.4.4.yaml @@ -17,13 +17,13 @@ extra-deps: - ghc-exactprint-0.5.8.2 - haddock-api-2.20.0 - haddock-library-1.6.0 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - haskell-src-exts-1.21.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - optparse-simple-0.1.0 - pretty-show-1.9.5 diff --git a/stack-8.6.1.yaml b/stack-8.6.1.yaml index 699868d27..9fca2af6f 100644 --- a/stack-8.6.1.yaml +++ b/stack-8.6.1.yaml @@ -19,13 +19,13 @@ extra-deps: - czipwith-1.0.1.1 - data-tree-print-0.1.0.2 - haddock-api-2.21.0 -- haskell-lsp-0.8.0.1 +- haskell-lsp-0.8.1.0 - haskell-lsp-types-0.8.0.1 - haskell-src-exts-1.21.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 -- lsp-test-0.5.0.2 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - monad-memo-0.4.1 - monoid-subclasses-0.4.6.1 diff --git a/stack-8.6.2.yaml b/stack-8.6.2.yaml index a9ab46edf..1f8fac53f 100644 --- a/stack-8.6.2.yaml +++ b/stack-8.6.2.yaml @@ -16,9 +16,11 @@ extra-deps: - constrained-dynamic-0.1.0.0 - haddock-api-2.21.0 - haskell-src-exts-1.21.0 +- haskell-lsp-0.8.1.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - monad-memo-0.4.1 - multistate-0.8.0.1 diff --git a/stack-8.6.3.yaml b/stack-8.6.3.yaml index 0e1d3170d..2b1faaea4 100644 --- a/stack-8.6.3.yaml +++ b/stack-8.6.3.yaml @@ -16,9 +16,11 @@ extra-deps: - constrained-dynamic-0.1.0.0 - haddock-api-2.21.0 - haskell-src-exts-1.21.0 +- haskell-lsp-0.8.1.0 - hlint-2.1.15 - hoogle-5.0.17.5 - hsimport-0.8.8 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2 - monad-memo-0.4.1 - multistate-0.8.0.1 diff --git a/stack-8.6.4.yaml b/stack-8.6.4.yaml index 403cbeadc..1573197c9 100644 --- a/stack-8.6.4.yaml +++ b/stack-8.6.4.yaml @@ -19,6 +19,7 @@ extra-deps: - hlint-2.1.15 - hsimport-0.8.8 - hoogle-5.0.17.6 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2@rev:1 - monad-memo-0.4.1 - multistate-0.8.0.1 diff --git a/stack.yaml b/stack.yaml index 728414e8d..dc9d50e4e 100644 --- a/stack.yaml +++ b/stack.yaml @@ -20,6 +20,7 @@ extra-deps: - haddock-api-2.22.0 - hlint-2.1.15 - hsimport-0.8.8 +- lsp-test-0.5.1.0 - monad-dijkstra-0.1.1.2@rev:1 - monad-memo-0.4.1 - multistate-0.8.0.1 diff --git a/test/functional/TypeDefinitionSpec.hs b/test/functional/TypeDefinitionSpec.hs new file mode 100644 index 000000000..03c389658 --- /dev/null +++ b/test/functional/TypeDefinitionSpec.hs @@ -0,0 +1,99 @@ +module TypeDefinitionSpec where + +import Control.Monad.IO.Class +import Language.Haskell.LSP.Test +import Language.Haskell.LSP.Types +import Haskell.Ide.Engine.PluginUtils +import System.Directory +import Test.Hspec +import TestUtils + +spec :: Spec +spec = describe "type definitions" $ do + it "finds local definition of record variable" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (11, 23)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (8, 1)) (toPos (8, 29))) + ] + it "finds local definition of newtype variable" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (16, 21)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (13, 1)) (toPos (13, 30))) + ] + it "finds local definition of sum type variable" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (21, 13)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + it "finds local definition of sum type contructor" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (24, 7)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + it "can not find non-local definition of type def" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (30, 17)) + liftIO $ defs `shouldBe` [] + + it "find local definition of type def" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (35, 16)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + + it "find type-definition of type def in component" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib2.hs" "haskell" + otherDoc <- openDoc "src/Lib.hs" "haskell" + closeDoc otherDoc + defs <- getTypeDefinitions doc (toPos (13, 20)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (8, 1)) (toPos (8, 29))) + ] + it "find definition of parameterized data type" + $ runSession hieCommand fullCaps "test/testdata/gototest" + $ do + doc <- openDoc "src/Lib.hs" "haskell" + defs <- getTypeDefinitions doc (toPos (40, 19)) + liftIO $ do + fp <- canonicalizePath "test/testdata/gototest/src/Lib.hs" + defs + `shouldBe` [ Location (filePathToUri fp) + (Range (toPos (37, 1)) (toPos (37, 31))) + ] diff --git a/test/testdata/gototest/src/Lib.hs b/test/testdata/gototest/src/Lib.hs index d36ff2714..4575b32d8 100644 --- a/test/testdata/gototest/src/Lib.hs +++ b/test/testdata/gototest/src/Lib.hs @@ -1,6 +1,40 @@ module Lib - ( someFunc - ) where + + where someFunc :: IO () someFunc = putStrLn "someFunc" + +data DataType = DataType Int + +dataTypeId :: DataType -> DataType +dataTypeId dataType = dataType + +newtype NewType = NewType Int + +newTypeId :: NewType -> NewType +newTypeId newType = newType + +data Enu = First | Second + +enuId :: Enu -> Enu +enuId enu = enu + +toNum :: Enu -> Int +toNum First = 1 +toNum Second = 2 + +type MyInt = Int + +myIntId :: MyInt -> MyInt +myIntId myInt = myInt + +type TypEnu = Enu + +typEnuId :: TypEnu -> TypEnu +typEnuId enu = enu + +data Parameter a = Parameter a + +parameterId :: Parameter a -> Parameter a +parameterId pid = pid \ No newline at end of file diff --git a/test/testdata/gototest/src/Lib2.hs b/test/testdata/gototest/src/Lib2.hs index a51362195..c0ef7d46b 100644 --- a/test/testdata/gototest/src/Lib2.hs +++ b/test/testdata/gototest/src/Lib2.hs @@ -8,3 +8,6 @@ g = do where z = 1+2 y = z+z x = y*z + +otherId :: DataType -> DataType +otherId dataType = dataType \ No newline at end of file diff --git a/test/unit/HaRePluginSpec.hs b/test/unit/HaRePluginSpec.hs index 7067fee5b..6a4824355 100644 --- a/test/unit/HaRePluginSpec.hs +++ b/test/unit/HaRePluginSpec.hs @@ -199,12 +199,87 @@ hareSpec = do req = liftToGhc $ TestDeferM $ findDef u (toPos (7,11)) r <- dispatchRequestPGoto $ lreq >> req r `shouldBe` IdeResultOk [Location (filePathToUri $ cwd "test/testdata/gototest/src/Lib2.hs") - (Range (toPos (10,9)) (toPos (10,10)))] + (Range (toPos (10,9)) (toPos (10,10)))] let req2 = liftToGhc $ TestDeferM $ findDef u (toPos (10,13)) r2 <- dispatchRequestPGoto $ lreq >> req2 r2 `shouldBe` IdeResultOk [Location (filePathToUri $ cwd "test/testdata/gototest/src/Lib2.hs") (Range (toPos (9,9)) (toPos (9,10)))] - + it "finds local definition of record variable" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (11, 23)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (8, 1)) (toPos (8, 29))) + ] + it "finds local definition of newtype variable" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (16, 21)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (13, 1)) (toPos (13, 30))) + ] + it "finds local definition of sum type variable" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (21, 13)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + it "finds local definition of sum type contructor" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (24, 7)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + it "can not find non-local definition of type def" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (30, 17)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk [] + it "find local definition of type def" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (35, 16)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (18, 1)) (toPos (18, 26))) + ] + it "find type-definition of type def in component" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib2.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (13, 20)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (8, 1)) (toPos (8, 29))) + ] + it "find definition of parameterized data type" $ do + let u = filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs" + lreq = setTypecheckedModule u + req = liftToGhc $ TestDeferM $ findTypeDef u (toPos (40, 19)) + r <- dispatchRequestPGoto $ lreq >> req + r `shouldBe` IdeResultOk + [ Location + (filePathToUri $ cwd "test/testdata/gototest/src/Lib.hs") + (Range (toPos (37, 1)) (toPos (37, 31))) + ] -- ---------------------------------