@@ -31,9 +31,7 @@ import Development.IDE.Types.Location
31
31
import GHC.Iface.Ext.Types (Identifier )
32
32
import qualified HieDb
33
33
import Language.LSP.Protocol.Types (DocumentHighlight (.. ),
34
- SymbolInformation (.. ),
35
- normalizedFilePathToUri ,
36
- uriToNormalizedFilePath )
34
+ SymbolInformation (.. ))
37
35
38
36
39
37
-- | 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
56
54
-- block waiting for the rule to be properly computed.
57
55
58
56
-- | 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
61
59
ide <- ask
62
60
opts <- liftIO $ getIdeOptionsIO ide
63
61
64
- (hf, mapping) <- useWithStaleFastMT GetHieAst file
65
- env <- hscEnv . fst <$> useWithStaleFastMT GhcSession file
66
- dkMap <- lift $ maybe (DKMap 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 ) fst <$> runMaybeT (useWithStaleFastMT GetDocMap uri )
67
65
68
66
! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
69
67
MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<< )) <$> AtPoint. atPoint opts hf dkMap env pos'
@@ -72,79 +70,78 @@ getAtPoint file pos = runMaybeT $ do
72
70
-- taking into account changes that may have occurred due to edits.
73
71
toCurrentLocation
74
72
:: PositionMapping
75
- -> NormalizedFilePath
73
+ -> NormalizedUri
76
74
-> Location
77
75
-> IdeAction (Maybe Location )
78
- toCurrentLocation mapping file (Location uri range ) =
76
+ toCurrentLocation mapping uri (Location locUri locRange ) =
79
77
-- The Location we are going to might be in a different
80
78
-- file than the one we are calling gotoDefinition from.
81
79
-- So we check that the location file matches the file
82
80
-- we are in.
83
- if nUri == normalizedFilePathToUri file
81
+ if nUri == uri
84
82
-- The Location matches the file, so use the PositionMapping
85
83
-- we have.
86
- then pure $ Location uri <$> toCurrentRange mapping range
84
+ then pure $ Location locUri <$> toCurrentRange mapping locRange
87
85
-- The Location does not match the file, so get the correct
88
86
-- PositionMapping and use that instead.
89
87
else do
90
88
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)
94
91
where
95
92
nUri :: NormalizedUri
96
- nUri = toNormalizedUri uri
93
+ nUri = toNormalizedUri locUri
97
94
98
95
-- | 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
101
98
ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
102
99
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
105
102
! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
106
103
locationsWithIdentifier <- AtPoint. gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
107
104
mapMaybeM (\ (location, identifier) -> do
108
- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
105
+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
109
106
pure $ Just (fixedLocation, identifier)
110
107
) locationsWithIdentifier
111
108
112
109
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
115
112
ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
116
113
opts <- liftIO $ getIdeOptionsIO ide
117
- (hf, mapping) <- useWithStaleFastMT GetHieAst file
114
+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
118
115
! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
119
116
locationsWithIdentifier <- AtPoint. gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
120
117
mapMaybeM (\ (location, identifier) -> do
121
- fixedLocation <- MaybeT $ toCurrentLocation mapping file location
118
+ fixedLocation <- MaybeT $ toCurrentLocation mapping uri location
122
119
pure $ Just (fixedLocation, identifier)
123
120
) locationsWithIdentifier
124
121
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
127
124
ide@ ShakeExtras { withHieDb, hiedbWriter } <- ask
128
125
opts <- liftIO $ getIdeOptionsIO ide
129
- (hf, mapping) <- useWithStaleFastMT GetHieAst file
126
+ (hf, mapping) <- useWithStaleFastMT GetHieAst uri
130
127
! pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
131
128
locs <- AtPoint. gotoImplementation withHieDb (lookupMod hiedbWriter) opts hf pos'
132
- traverse (MaybeT . toCurrentLocation mapping file ) locs
129
+ traverse (MaybeT . toCurrentLocation mapping uri ) locs
133
130
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
137
134
! pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
138
135
let toCurrentHighlight (DocumentHighlight range t) = flip DocumentHighlight t <$> toCurrentRange mapping range
139
136
mapMaybe toCurrentHighlight <$> AtPoint. documentHighlight hf rf pos'
140
137
141
138
-- 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
144
141
ShakeExtras {withHieDb} <- getShakeExtras
145
142
fs <- HM. keys <$> getFilesOfInterestUntracked
146
143
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)
148
145
149
146
workspaceSymbols :: T. Text -> IdeAction (Maybe [SymbolInformation ])
150
147
workspaceSymbols query = runMaybeT $ do
0 commit comments