@@ -30,9 +30,7 @@ import Development.IDE.Types.HscEnvEq (hscEnv)
3030import Development.IDE.Types.Location
3131import qualified HieDb
3232import Language.LSP.Protocol.Types (DocumentHighlight (.. ),
33- SymbolInformation (.. ),
34- normalizedFilePathToUri ,
35- uriToNormalizedFilePath )
33+ SymbolInformation (.. ))
3634
3735
3836-- | Eventually this will lookup/generate URIs for files in dependencies, but not in the
@@ -55,14 +53,14 @@ lookupMod _dbchan _hie_f _mod _uid _boot = MaybeT $ pure Nothing
5553-- block waiting for the rule to be properly computed.
5654
5755-- | Try to get hover text for the name under point.
58- getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range , [T. Text ]))
59- getAtPoint file pos = runMaybeT $ do
56+ getAtPoint :: NormalizedUri -> Position -> IdeAction (Maybe (Maybe Range , [T. Text ]))
57+ getAtPoint uri pos = runMaybeT $ do
6058 ide <- ask
6159 opts <- liftIO $ getIdeOptionsIO ide
6260
63- (hf, mapping) <- useWithStaleFastMT GetHieAst file
64- env <- hscEnv . fst <$> useWithStaleFastMT GhcSession file
65- dkMap <- lift $ maybe (DKMap mempty mempty ) fst <$> runMaybeT (useWithStaleFastMT GetDocMap file )
61+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
62+ env <- hscEnv . fst <$> useWithStaleFastMT GhcSession uri
63+ dkMap <- lift $ maybe (DKMap mempty mempty ) fst <$> runMaybeT (useWithStaleFastMT GetDocMap uri )
6664
6765 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
6866 MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<< )) <$> AtPoint. atPoint opts hf dkMap env pos'
@@ -71,79 +69,78 @@ getAtPoint file pos = runMaybeT $ do
7169-- taking into account changes that may have occurred due to edits.
7270toCurrentLocation
7371 :: PositionMapping
74- -> NormalizedFilePath
72+ -> NormalizedUri
7573 -> Location
7674 -> IdeAction (Maybe Location )
77- toCurrentLocation mapping file (Location uri range ) =
75+ toCurrentLocation mapping uri (Location locUri locRange ) =
7876 -- The Location we are going to might be in a different
7977 -- file than the one we are calling gotoDefinition from.
8078 -- So we check that the location file matches the file
8179 -- we are in.
82- if nUri == normalizedFilePathToUri file
80+ if nUri == uri
8381 -- The Location matches the file, so use the PositionMapping
8482 -- we have.
85- then pure $ Location uri <$> toCurrentRange mapping range
83+ then pure $ Location locUri <$> toCurrentRange mapping locRange
8684 -- The Location does not match the file, so get the correct
8785 -- PositionMapping and use that instead.
8886 else do
8987 otherLocationMapping <- fmap (fmap snd ) $ runMaybeT $ do
90- otherLocationFile <- MaybeT $ pure $ uriToNormalizedFilePath nUri
91- useWithStaleFastMT GetHieAst otherLocationFile
92- pure $ Location uri <$> (flip toCurrentRange range =<< otherLocationMapping)
88+ useWithStaleFastMT GetHieAst nUri
89+ pure $ Location locUri <$> (flip toCurrentRange locRange =<< otherLocationMapping)
9390 where
9491 nUri :: NormalizedUri
95- nUri = toNormalizedUri uri
92+ nUri = toNormalizedUri locUri
9693
9794-- | Goto Definition.
98- getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location , Identifier )])
99- getDefinition file pos = runMaybeT $ do
95+ getDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [(Location , Identifier )])
96+ getDefinition uri pos = runMaybeT $ do
10097 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
10198 opts <- liftIO $ getIdeOptionsIO ide
102- (hf, mapping) <- useWithStaleFastMT GetHieAst file
103- (ImportMap imports, _) <- useWithStaleFastMT GetImportMap file
99+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
100+ (ImportMap imports, _) <- useWithStaleFastMT GetImportMap uri
104101 ! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
105102 locationsWithIdentifier <- AtPoint. gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
106103 mapMaybeM (\ (location, identifier) -> do
107- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
104+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
108105 pure $ Just (fixedLocation, identifier)
109106 ) locationsWithIdentifier
110107
111108
112- getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location , Identifier )])
113- getTypeDefinition file pos = runMaybeT $ do
109+ getTypeDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [(Location , Identifier )])
110+ getTypeDefinition uri pos = runMaybeT $ do
114111 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
115112 opts <- liftIO $ getIdeOptionsIO ide
116- (hf, mapping) <- useWithStaleFastMT GetHieAst file
113+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
117114 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
118115 locationsWithIdentifier <- AtPoint. gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
119116 mapMaybeM (\ (location, identifier) -> do
120- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
117+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
121118 pure $ Just (fixedLocation, identifier)
122119 ) locationsWithIdentifier
123120
124- getImplementationDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location ])
125- getImplementationDefinition file pos = runMaybeT $ do
121+ getImplementationDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [Location ])
122+ getImplementationDefinition uri pos = runMaybeT $ do
126123 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
127124 opts <- liftIO $ getIdeOptionsIO ide
128- (hf, mapping) <- useWithStaleFastMT GetHieAst file
125+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
129126 ! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
130127 locs <- AtPoint. gotoImplementation withHieDb (lookupMod hiedbWriter) opts hf pos'
131- traverse (MaybeT . toCurrentLocation mapping file ) locs
128+ traverse (MaybeT . toCurrentLocation mapping uri ) locs
132129
133- highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight ])
134- highlightAtPoint file pos = runMaybeT $ do
135- (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst file
130+ highlightAtPoint :: NormalizedUri -> Position -> IdeAction (Maybe [DocumentHighlight ])
131+ highlightAtPoint uri pos = runMaybeT $ do
132+ (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst uri
136133 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
137134 let toCurrentHighlight (DocumentHighlight range t) = flip DocumentHighlight t <$> toCurrentRange mapping range
138135 mapMaybe toCurrentHighlight <$> AtPoint. documentHighlight hf rf pos'
139136
140137-- Refs are not an IDE action, so it is OK to be slow and (more) accurate
141- refsAtPoint :: NormalizedFilePath -> Position -> Action [Location ]
142- refsAtPoint file pos = do
138+ refsAtPoint :: NormalizedUri -> Position -> Action [Location ]
139+ refsAtPoint uri pos = do
143140 ShakeExtras {withHieDb} <- getShakeExtras
144141 fs <- HM. keys <$> getFilesOfInterestUntracked
145142 asts <- HM. fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst fs
146- AtPoint. referencesAtPoint withHieDb file pos (AtPoint. FOIReferences asts)
143+ AtPoint. referencesAtPoint withHieDb uri pos (AtPoint. BOIReferences asts)
147144
148145workspaceSymbols :: T. Text -> IdeAction (Maybe [SymbolInformation ])
149146workspaceSymbols query = runMaybeT $ do
0 commit comments