@@ -31,9 +31,7 @@ import Development.IDE.Types.Location
3131import GHC.Iface.Ext.Types (Identifier )
3232import qualified HieDb
3333import Language.LSP.Protocol.Types (DocumentHighlight (.. ),
34- SymbolInformation (.. ),
35- normalizedFilePathToUri ,
36- uriToNormalizedFilePath )
34+ SymbolInformation (.. ))
3735
3836
3937-- | Eventually this will lookup/generate URIs for files in dependencies, but not in the
@@ -56,14 +54,14 @@ lookupMod _dbchan _hie_f _mod _uid _boot = MaybeT $ pure Nothing
5654-- block waiting for the rule to be properly computed.
5755
5856-- | Try to get hover text for the name under point.
59- getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range , [T. Text ]))
60- getAtPoint file pos = runMaybeT $ do
57+ getAtPoint :: NormalizedUri -> Position -> IdeAction (Maybe (Maybe Range , [T. Text ]))
58+ getAtPoint uri pos = runMaybeT $ do
6159 ide <- ask
6260 opts <- liftIO $ getIdeOptionsIO ide
6361
64- (hf, mapping) <- useWithStaleFastMT GetHieAst file
65- env <- hscEnv . fst <$> useWithStaleFastMT GhcSession file
66- dkMap <- lift $ maybe (DKMap mempty mempty mempty ) fst <$> runMaybeT (useWithStaleFastMT GetDocMap file )
62+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
63+ env <- hscEnv . fst <$> useWithStaleFastMT GhcSession uri
64+ dkMap <- lift $ maybe (DKMap mempty mempty mempty ) fst <$> runMaybeT (useWithStaleFastMT GetDocMap uri )
6765
6866 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
6967 MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<< )) <$> AtPoint. atPoint opts hf dkMap env pos'
@@ -72,79 +70,78 @@ getAtPoint file pos = runMaybeT $ do
7270-- taking into account changes that may have occurred due to edits.
7371toCurrentLocation
7472 :: PositionMapping
75- -> NormalizedFilePath
73+ -> NormalizedUri
7674 -> Location
7775 -> IdeAction (Maybe Location )
78- toCurrentLocation mapping file (Location uri range ) =
76+ toCurrentLocation mapping uri (Location locUri locRange ) =
7977 -- The Location we are going to might be in a different
8078 -- file than the one we are calling gotoDefinition from.
8179 -- So we check that the location file matches the file
8280 -- we are in.
83- if nUri == normalizedFilePathToUri file
81+ if nUri == uri
8482 -- The Location matches the file, so use the PositionMapping
8583 -- we have.
86- then pure $ Location uri <$> toCurrentRange mapping range
84+ then pure $ Location locUri <$> toCurrentRange mapping locRange
8785 -- The Location does not match the file, so get the correct
8886 -- PositionMapping and use that instead.
8987 else do
9088 otherLocationMapping <- fmap (fmap snd ) $ runMaybeT $ do
91- otherLocationFile <- MaybeT $ pure $ uriToNormalizedFilePath nUri
92- useWithStaleFastMT GetHieAst otherLocationFile
93- pure $ Location uri <$> (flip toCurrentRange range =<< otherLocationMapping)
89+ useWithStaleFastMT GetHieAst nUri
90+ pure $ Location locUri <$> (flip toCurrentRange locRange =<< otherLocationMapping)
9491 where
9592 nUri :: NormalizedUri
96- nUri = toNormalizedUri uri
93+ nUri = toNormalizedUri locUri
9794
9895-- | Goto Definition.
99- getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location , Identifier )])
100- getDefinition file pos = runMaybeT $ do
96+ getDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [(Location , Identifier )])
97+ getDefinition uri pos = runMaybeT $ do
10198 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
10299 opts <- liftIO $ getIdeOptionsIO ide
103- (hf, mapping) <- useWithStaleFastMT GetHieAst file
104- (ImportMap imports, _) <- useWithStaleFastMT GetImportMap file
100+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
101+ (ImportMap imports, _) <- useWithStaleFastMT GetImportMap uri
105102 ! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
106103 locationsWithIdentifier <- AtPoint. gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
107104 mapMaybeM (\ (location, identifier) -> do
108- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
105+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
109106 pure $ Just (fixedLocation, identifier)
110107 ) locationsWithIdentifier
111108
112109
113- getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location , Identifier )])
114- getTypeDefinition file pos = runMaybeT $ do
110+ getTypeDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [(Location , Identifier )])
111+ getTypeDefinition uri pos = runMaybeT $ do
115112 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
116113 opts <- liftIO $ getIdeOptionsIO ide
117- (hf, mapping) <- useWithStaleFastMT GetHieAst file
114+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
118115 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
119116 locationsWithIdentifier <- AtPoint. gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
120117 mapMaybeM (\ (location, identifier) -> do
121- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
118+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
122119 pure $ Just (fixedLocation, identifier)
123120 ) locationsWithIdentifier
124121
125- getImplementationDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location ])
126- getImplementationDefinition file pos = runMaybeT $ do
122+ getImplementationDefinition :: NormalizedUri -> Position -> IdeAction (Maybe [Location ])
123+ getImplementationDefinition uri pos = runMaybeT $ do
127124 ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
128125 opts <- liftIO $ getIdeOptionsIO ide
129- (hf, mapping) <- useWithStaleFastMT GetHieAst file
126+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
130127 ! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
131128 locs <- AtPoint. gotoImplementation withHieDb (lookupMod hiedbWriter) opts hf pos'
132- traverse (MaybeT . toCurrentLocation mapping file ) locs
129+ traverse (MaybeT . toCurrentLocation mapping uri ) locs
133130
134- highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight ])
135- highlightAtPoint file pos = runMaybeT $ do
136- (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst file
131+ highlightAtPoint :: NormalizedUri -> Position -> IdeAction (Maybe [DocumentHighlight ])
132+ highlightAtPoint uri pos = runMaybeT $ do
133+ (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst uri
137134 ! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
138135 let toCurrentHighlight (DocumentHighlight range t) = flip DocumentHighlight t <$> toCurrentRange mapping range
139136 mapMaybe toCurrentHighlight <$> AtPoint. documentHighlight hf rf pos'
140137
141138-- Refs are not an IDE action, so it is OK to be slow and (more) accurate
142- refsAtPoint :: NormalizedFilePath -> Position -> Action [Location ]
143- refsAtPoint file pos = do
139+ refsAtPoint :: NormalizedUri -> Position -> Action [Location ]
140+ refsAtPoint uri pos = do
144141 ShakeExtras {withHieDb} <- getShakeExtras
145142 fs <- HM. keys <$> getFilesOfInterestUntracked
146143 asts <- HM. fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst fs
147- AtPoint. referencesAtPoint withHieDb file pos (AtPoint. FOIReferences asts)
144+ AtPoint. referencesAtPoint withHieDb uri pos (AtPoint. BOIReferences asts)
148145
149146workspaceSymbols :: T. Text -> IdeAction (Maybe [SymbolInformation ])
150147workspaceSymbols query = runMaybeT $ do
0 commit comments