Skip to content

Commit a799e8d

Browse files
committed
[feat] replace usages of NormalizedFilePath with NormalizedUri wherever possible
1 parent cfeced8 commit a799e8d

File tree

72 files changed

+1244
-1159
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

72 files changed

+1244
-1159
lines changed

ghcide-test/exe/Progress.hs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Progress (tests) where
44
import Control.Concurrent.STM
55
import Data.Foldable (for_)
66
import qualified Data.HashMap.Strict as Map
7-
import Development.IDE (NormalizedFilePath)
7+
import Development.IDE
88
import Development.IDE.Core.ProgressReporting
99
import qualified "list-t" ListT
1010
import qualified StmContainers.Map as STM
@@ -18,7 +18,7 @@ tests = testGroup "Progress"
1818

1919
data InProgressModel = InProgressModel {
2020
done, todo :: Int,
21-
current :: Map.HashMap NormalizedFilePath Int
21+
current :: Map.HashMap NormalizedUri Int
2222
}
2323

2424
reportProgressTests :: TestTree
@@ -30,10 +30,11 @@ reportProgressTests = testGroup "recordProgress"
3030
]
3131
where
3232
p0 = pure $ InProgressModel 0 0 mempty
33-
addNew = recordProgressModel "A" succ p0
34-
increase = recordProgressModel "A" succ addNew
35-
decrease = recordProgressModel "A" succ increase
36-
done = recordProgressModel "A" pred decrease
33+
aUri = filePathToUri' "A"
34+
addNew = recordProgressModel aUri succ p0
35+
increase = recordProgressModel aUri succ addNew
36+
decrease = recordProgressModel aUri succ increase
37+
done = recordProgressModel aUri pred decrease
3738
recordProgressModel key change state =
3839
model state $ \st -> recordProgress st key change
3940
model stateModelIO k = do

ghcide-test/exe/UnitTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ tests = do
5151
let uri = Uri "file://"
5252
uriToFilePath' uri @?= Just ""
5353
, testCase "showDiagnostics prints ranges 1-based (like vscode)" $ do
54-
let diag = Diagnostics.FileDiagnostic "" Diagnostics.ShowDiag Diagnostic
54+
let diag = Diagnostics.FileDiagnostic (filePathToUri' "") Diagnostics.ShowDiag Diagnostic
5555
{ _codeDescription = Nothing
5656
, _data_ = Nothing
5757
, _range = Range

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ data Log
138138
| LogHieDbWriterThreadSQLiteError !SQLError
139139
| LogHieDbWriterThreadException !SomeException
140140
| LogInterfaceFilesCacheDir !FilePath
141-
| LogKnownFilesUpdated !(HashMap Target (HashSet NormalizedFilePath))
141+
| LogKnownFilesUpdated !(HashMap Target (HashSet NormalizedUri))
142142
| LogMakingNewHscEnv ![UnitId]
143143
| LogDLLLoadError !String
144144
| LogCradlePath !FilePath
@@ -199,7 +199,7 @@ instance Pretty Log where
199199
nest 2 $
200200
vcat
201201
[ "Known files updated:"
202-
, viaShow $ (HM.map . Set.map) fromNormalizedFilePath targetToPathsMap
202+
, viaShow $ (HM.map . Set.map) fromNormalizedUri targetToPathsMap
203203
]
204204
LogMakingNewHscEnv inPlaceUnitIds ->
205205
"Making new HscEnv. In-place unit ids:" <+> pretty (map show inPlaceUnitIds)
@@ -477,13 +477,13 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
477477
-- 'TargetFile Foo.hs' in the 'knownTargetsVar', thus not find 'TargetFile Foo.hs-boot'
478478
-- and also not find 'TargetModule Foo'.
479479
fs <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
480-
pure $ map (\fp -> (TargetFile fp, Set.singleton fp)) (nubOrd (f:fs))
480+
pure $ map (\fp -> (TargetFile fp, Set.singleton $ filePathToUri' fp)) (nubOrd (f:fs))
481481
TargetModule _ -> do
482482
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
483-
return [(targetTarget, Set.fromList found)]
483+
return [(targetTarget, Set.fromList $ map filePathToUri' found)]
484484
hasUpdate <- atomically $ do
485485
known <- readTVar knownTargetsVar
486-
let known' = flip mapHashed known $ \k -> unionKnownTargets k (mkKnownTargets knownTargets)
486+
let known' = flip mapHashed known $ \k -> unionKnownTargets k (mkKnownTargets $ knownTargets)
487487
hasUpdate = if known /= known' then Just (unhashed known') else Nothing
488488
writeTVar knownTargetsVar known'
489489
pure hasUpdate
@@ -567,7 +567,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
567567
this_target_details = TargetDetails (TargetFile _cfp) this_error_env this_dep_info [_cfp]
568568
this_flags = (this_error_env, this_dep_info)
569569
this_error_env = ([this_error], Nothing)
570-
this_error = ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) _cfp
570+
this_error = ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) (filePathToUri' _cfp)
571571
(T.unlines
572572
[ "No cradle target found. Is this file listed in the targets of your cradle?"
573573
, "If you are using a .cabal file, please ensure that this module is listed in either the exposed-modules or other-modules section"
@@ -588,8 +588,8 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
588588
unless (null new_deps || not checkProject) $ do
589589
cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) (concatMap targetLocations all_targets)
590590
void $ shakeEnqueue extras $ mkDelayedAction "InitialLoad" Debug $ void $ do
591-
mmt <- uses GetModificationTime cfps'
592-
let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
591+
mmt <- uses GetModificationTime $ map filePathToUri' cfps'
592+
let cs_exist = mapMaybe (fmap filePathToUri') (zipWith (<$) cfps' mmt)
593593
modIfaces <- uses GetModIface cs_exist
594594
-- update exports map
595595
shakeExtras <- getShakeExtras
@@ -888,7 +888,7 @@ newComponentCache recorder exts _cfp hsc_env old_cis new_cis = do
888888
let closure_errs = maybeToList $ checkHomeUnitsClosed' (hsc_unit_env hscEnv') (hsc_all_home_unit_ids hscEnv')
889889
closure_err_to_multi_err err =
890890
ideErrorWithSource
891-
(Just "cradle") (Just DiagnosticSeverity_Warning) _cfp
891+
(Just "cradle") (Just DiagnosticSeverity_Warning) (filePathToUri' _cfp)
892892
(T.pack (Compat.printWithoutUniques (singleMessage err)))
893893
(Just (fmap GhcDriverMessage err))
894894
multi_errs = map closure_err_to_multi_err closure_errs
@@ -1255,4 +1255,4 @@ showPackageSetupException PackageSetupException{..} = unwords
12551255

12561256
renderPackageSetupException :: FilePath -> PackageSetupException -> FileDiagnostic
12571257
renderPackageSetupException fp e =
1258-
ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) (toNormalizedFilePath' fp) (T.pack $ showPackageSetupException e) Nothing
1258+
ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) (filePathToUri' $ toNormalizedFilePath' fp) (T.pack $ showPackageSetupException e) Nothing

ghcide/session-loader/Development/IDE/Session/Diagnostics.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ data CradleErrorDetails =
3030
renderCradleError :: CradleError -> Cradle a -> NormalizedFilePath -> FileDiagnostic
3131
renderCradleError cradleError cradle nfp =
3232
let noDetails =
33-
ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) nfp (T.unlines $ map T.pack userFriendlyMessage) Nothing
33+
ideErrorWithSource (Just "cradle") (Just DiagnosticSeverity_Error) (filePathToUri' nfp) (T.unlines $ map T.pack userFriendlyMessage) Nothing
3434
in
3535
if HieBios.isCabalCradle cradle
3636
then noDetails & fdLspDiagnosticL %~ \diag -> diag{_data_ = Just $ Aeson.toJSON CradleErrorDetails{cabalProjectFiles=absDeps}}

ghcide/src/Development/IDE/Core/Actions.hs

Lines changed: 32 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -31,9 +31,7 @@ import Development.IDE.Types.Location
3131
import GHC.Iface.Ext.Types (Identifier)
3232
import qualified HieDb
3333
import 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) 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)
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.
7371
toCurrentLocation
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

149146
workspaceSymbols :: T.Text -> IdeAction (Maybe [SymbolInformation])
150147
workspaceSymbols query = runMaybeT $ do

0 commit comments

Comments
 (0)