Skip to content

Commit 3145830

Browse files
authored
Fix space leak on cradle reloads (#1316)
* Move PackageExports to HscEnvEq This is necessary to prevent leaking the package exports * [ghcide-bench] drop redundant argument * [experiments] hover after cradle edit * [benchmark] code actions after cradle edit * Disable 'hover after cradle edit' example Expensive and already covered by 'code actions after cradle edit' * [benchmark] add the completions experiment This was missing from the list * Drop redundant argument * Fix ordering of completions in test * Exclude package exports from NFData.rnf This fixes the th-linking-test because it restores the previous dynamic semantics in which the package exports are only evaluated when code actions are requested.
1 parent e7a75c1 commit 3145830

File tree

18 files changed

+226
-186
lines changed

18 files changed

+226
-186
lines changed

ghcide/bench/config.yaml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,11 +29,14 @@ experiments:
2929
- "edit"
3030
- "hover"
3131
- "hover after edit"
32+
# - "hover after cradle edit"
3233
- "getDefinition"
3334
- "getDefinition after edit"
35+
- "completions"
3436
- "completions after edit"
3537
- "code actions"
3638
- "code actions after edit"
39+
- "code actions after cradle edit"
3740
- "documentSymbols after edit"
3841

3942
# An ordered list of versions to analyze

ghcide/bench/lib/Experiments.hs

Lines changed: 45 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -62,52 +62,51 @@ allWithIdentifierPos f docs = allM f (filter (isJust . identifierP) docs)
6262
experiments :: [Bench]
6363
experiments =
6464
[ ---------------------------------------------------------------------------------------
65-
bench "hover" 10 $ allWithIdentifierPos $ \DocumentPositions{..} ->
65+
bench "hover" $ allWithIdentifierPos $ \DocumentPositions{..} ->
6666
isJust <$> getHover doc (fromJust identifierP),
6767
---------------------------------------------------------------------------------------
68-
bench "edit" 10 $ \docs -> do
68+
bench "edit" $ \docs -> do
6969
forM_ docs $ \DocumentPositions{..} ->
7070
changeDoc doc [charEdit stringLiteralP]
7171
waitForProgressDone -- TODO check that this waits for all of them
7272
return True,
7373
---------------------------------------------------------------------------------------
74-
bench "hover after edit" 10 $ \docs -> do
74+
bench "hover after edit" $ \docs -> do
7575
forM_ docs $ \DocumentPositions{..} ->
7676
changeDoc doc [charEdit stringLiteralP]
7777
flip allWithIdentifierPos docs $ \DocumentPositions{..} ->
7878
isJust <$> getHover doc (fromJust identifierP),
7979
---------------------------------------------------------------------------------------
80-
bench "getDefinition" 10 $ allWithIdentifierPos $ \DocumentPositions{..} ->
80+
bench "getDefinition" $ allWithIdentifierPos $ \DocumentPositions{..} ->
8181
not . null <$> getDefinitions doc (fromJust identifierP),
8282
---------------------------------------------------------------------------------------
83-
bench "getDefinition after edit" 10 $ \docs -> do
83+
bench "getDefinition after edit" $ \docs -> do
8484
forM_ docs $ \DocumentPositions{..} ->
8585
changeDoc doc [charEdit stringLiteralP]
8686
flip allWithIdentifierPos docs $ \DocumentPositions{..} ->
8787
not . null <$> getDefinitions doc (fromJust identifierP),
8888
---------------------------------------------------------------------------------------
89-
bench "documentSymbols" 100 $ allM $ \DocumentPositions{..} -> do
89+
bench "documentSymbols" $ allM $ \DocumentPositions{..} -> do
9090
fmap (either (not . null) (not . null)) . getDocumentSymbols $ doc,
9191
---------------------------------------------------------------------------------------
92-
bench "documentSymbols after edit" 100 $ \docs -> do
92+
bench "documentSymbols after edit" $ \docs -> do
9393
forM_ docs $ \DocumentPositions{..} ->
9494
changeDoc doc [charEdit stringLiteralP]
9595
flip allM docs $ \DocumentPositions{..} ->
9696
either (not . null) (not . null) <$> getDocumentSymbols doc,
9797
---------------------------------------------------------------------------------------
98-
bench "completions" 10 $ \docs -> do
98+
bench "completions" $ \docs -> do
9999
flip allWithIdentifierPos docs $ \DocumentPositions{..} ->
100100
not . null <$> getCompletions doc (fromJust identifierP),
101101
---------------------------------------------------------------------------------------
102-
bench "completions after edit" 10 $ \docs -> do
102+
bench "completions after edit" $ \docs -> do
103103
forM_ docs $ \DocumentPositions{..} ->
104104
changeDoc doc [charEdit stringLiteralP]
105105
flip allWithIdentifierPos docs $ \DocumentPositions{..} ->
106106
not . null <$> getCompletions doc (fromJust identifierP),
107107
---------------------------------------------------------------------------------------
108108
benchWithSetup
109109
"code actions"
110-
10
111110
( \docs -> do
112111
unless (any (isJust . identifierP) docs) $
113112
error "None of the example modules is suitable for this experiment"
@@ -122,7 +121,6 @@ experiments =
122121
---------------------------------------------------------------------------------------
123122
benchWithSetup
124123
"code actions after edit"
125-
10
126124
( \docs -> do
127125
unless (any (isJust . identifierP) docs) $
128126
error "None of the example modules is suitable for this experiment"
@@ -136,6 +134,37 @@ experiments =
136134
not . null . catMaybes <$> forM docs (\DocumentPositions{..} -> do
137135
forM identifierP $ \p ->
138136
getCodeActions doc (Range p p))
137+
),
138+
---------------------------------------------------------------------------------------
139+
benchWithSetup
140+
"code actions after cradle edit"
141+
( \docs -> do
142+
unless (any (isJust . identifierP) docs) $
143+
error "None of the example modules is suitable for this experiment"
144+
forM_ docs $ \DocumentPositions{..} ->
145+
forM_ identifierP $ \p -> changeDoc doc [charEdit p]
146+
)
147+
( \docs -> do
148+
Just hieYaml <- uriToFilePath <$> getDocUri "hie.yaml"
149+
liftIO $ appendFile hieYaml "##\n"
150+
sendNotification WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
151+
List [ FileEvent (filePathToUri "hie.yaml") FcChanged ]
152+
forM_ docs $ \DocumentPositions{..} ->
153+
changeDoc doc [charEdit stringLiteralP]
154+
waitForProgressDone
155+
not . null . catMaybes <$> forM docs (\DocumentPositions{..} -> do
156+
forM identifierP $ \p ->
157+
getCodeActions doc (Range p p))
158+
),
159+
---------------------------------------------------------------------------------------
160+
bench
161+
"hover after cradle edit"
162+
(\docs -> do
163+
Just hieYaml <- uriToFilePath <$> getDocUri "hie.yaml"
164+
liftIO $ appendFile hieYaml "##\n"
165+
sendNotification WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
166+
List [ FileEvent (filePathToUri "hie.yaml") FcChanged ]
167+
flip allWithIdentifierPos docs $ \DocumentPositions{..} -> isJust <$> getHover doc (fromJust identifierP)
139168
)
140169
]
141170

@@ -208,21 +237,20 @@ select Bench {name, enabled} =
208237

209238
benchWithSetup ::
210239
String ->
211-
Natural ->
212240
([DocumentPositions] -> Session ()) ->
213241
Experiment ->
214242
Bench
215-
benchWithSetup name samples benchSetup experiment = Bench {..}
243+
benchWithSetup name benchSetup experiment = Bench {..}
216244
where
217245
enabled = True
246+
samples = 100
218247

219-
bench :: String -> Natural -> Experiment -> Bench
220-
bench name defSamples =
221-
benchWithSetup name defSamples (const $ pure ())
248+
bench :: String -> Experiment -> Bench
249+
bench name = benchWithSetup name (const $ pure ())
222250

223251
runBenchmarksFun :: HasConfig => FilePath -> [Bench] -> IO ()
224252
runBenchmarksFun dir allBenchmarks = do
225-
let benchmarks = [ b{samples = fromMaybe (samples b) (repetitions ?config) }
253+
let benchmarks = [ b{samples = fromMaybe 100 (repetitions ?config) }
226254
| b <- allBenchmarks
227255
, select b ]
228256

ghcide/ghcide.cabal

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -166,6 +166,7 @@ library
166166
Development.IDE.Spans.LocalBindings
167167
Development.IDE.Types.Diagnostics
168168
Development.IDE.Types.Exports
169+
Development.IDE.Types.HscEnvEq
169170
Development.IDE.Types.KnownTargets
170171
Development.IDE.Types.Location
171172
Development.IDE.Types.Logger
@@ -202,8 +203,6 @@ library
202203
Development.IDE.Import.FindImports
203204
Development.IDE.LSP.Notifications
204205
Development.IDE.Plugin.CodeAction.PositionIndexed
205-
Development.IDE.Plugin.CodeAction.Rules
206-
Development.IDE.Plugin.CodeAction.RuleTypes
207206
Development.IDE.Plugin.Completions.Logic
208207
Development.IDE.Plugin.HLS.Formatter
209208
Development.IDE.Types.Action

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ import Development.IDE.GHC.Util
4949
import Development.IDE.Session.VersionCheck
5050
import Development.IDE.Types.Diagnostics
5151
import Development.IDE.Types.Exports
52+
import Development.IDE.Types.HscEnvEq (HscEnvEq, newHscEnvEqPreserveImportPaths, newHscEnvEq)
5253
import Development.IDE.Types.Location
5354
import Development.IDE.Types.Logger
5455
import Development.IDE.Types.Options

ghcide/src/Development/IDE.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ import Development.IDE.GHC.Error as X
4040
import Development.IDE.GHC.Util as X
4141
import Development.IDE.Plugin as X
4242
import Development.IDE.Types.Diagnostics as X
43+
import Development.IDE.Types.HscEnvEq as X (HscEnvEq(..), hscEnv, hscEnvWithImportPaths)
4344
import Development.IDE.Types.Location as X
4445
import Development.IDE.Types.Logger as X
4546
import Development.Shake as X (Action, action, Rules, RuleResult)

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import Data.Binary
2222
import Development.IDE.Import.DependencyInformation
2323
import Development.IDE.GHC.Compat hiding (HieFileResult)
2424
import Development.IDE.GHC.Util
25+
import Development.IDE.Types.HscEnvEq (HscEnvEq)
2526
import Development.IDE.Types.KnownTargets
2627
import Data.Hashable
2728
import Data.Typeable
@@ -191,10 +192,10 @@ data HieKind a where
191192
instance NFData (HieKind a) where
192193
rnf (HieFromDisk hf) = rnf hf
193194
rnf HieFresh = ()
194-
195+
195196
instance NFData HieAstResult where
196197
rnf (HAR m hf _rm _tr kind) = rnf m `seq` rwhnf hf `seq` rnf kind
197-
198+
198199
instance Show HieAstResult where
199200
show = show . hieModule
200201

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,7 @@ import qualified Development.IDE.Spans.AtPoint as AtPoint
112112
import Development.IDE.Core.IdeConfiguration
113113
import Development.IDE.Core.Service
114114
import Development.IDE.Core.Shake
115+
import Development.IDE.Types.HscEnvEq
115116
import Development.Shake.Classes hiding (get, put)
116117
import Control.Monad.Trans.Except (runExceptT,ExceptT,except)
117118
import Control.Concurrent.Async (concurrently)

ghcide/src/Development/IDE/GHC/Util.hs

Lines changed: 2 additions & 83 deletions
Original file line numberDiff line numberDiff line change
@@ -4,14 +4,8 @@
44

55
-- | General utility functions, mostly focused around GHC operations.
66
module Development.IDE.GHC.Util(
7-
-- * HcsEnv and environment
8-
HscEnvEq,
9-
hscEnv, newHscEnvEq,
10-
hscEnvWithImportPaths,
11-
envImportPaths,
127
modifyDynFlags,
138
evalGhcEnv,
14-
deps,
159
-- * GHC wrappers
1610
prettyPrint,
1711
unsafePrintSDoc,
@@ -32,8 +26,7 @@ module Development.IDE.GHC.Util(
3226
setHieDir,
3327
dontWriteHieFiles,
3428
disableWarningsAsErrors,
35-
newHscEnvEqPreserveImportPaths,
36-
newHscEnvEqWithImportPaths) where
29+
) where
3730

3831
import Control.Concurrent
3932
import Data.List.Extra
@@ -56,8 +49,6 @@ import GHC.IO.Encoding
5649
import GHC.IO.Exception
5750
import GHC.IO.Handle.Types
5851
import GHC.IO.Handle.Internals
59-
import Data.Unique
60-
import Development.Shake.Classes
6152
import qualified Data.Text as T
6253
import qualified Data.Text.Encoding as T
6354
import qualified Data.Text.Encoding.Error as T
@@ -71,13 +62,12 @@ import Outputable (SDoc, showSDocUnsafe, ppr, Outputable, mkUserStyle, renderWit
7162
import Packages (getPackageConfigMap, lookupPackage')
7263
import SrcLoc (mkRealSrcLoc)
7364
import FastString (mkFastString)
74-
import Module (moduleNameSlashes, InstalledUnitId)
65+
import Module (moduleNameSlashes)
7566
import OccName (parenSymOcc)
7667
import RdrName (nameRdrName, rdrNameOcc)
7768

7869
import Development.IDE.GHC.Compat as GHC
7970
import Development.IDE.Types.Location
80-
import System.Directory (canonicalizePath)
8171

8272

8373
----------------------------------------------------------------------
@@ -178,77 +168,6 @@ moduleImportPath (takeDirectory . fromNormalizedFilePath -> pathDir) mn
178168
fromNormalizedFilePath $ toNormalizedFilePath' $
179169
moduleNameSlashes mn
180170

181-
-- | An 'HscEnv' with equality. Two values are considered equal
182-
-- if they are created with the same call to 'newHscEnvEq'.
183-
data HscEnvEq = HscEnvEq
184-
{ envUnique :: !Unique
185-
, hscEnv :: !HscEnv
186-
, deps :: [(InstalledUnitId, DynFlags)]
187-
-- ^ In memory components for this HscEnv
188-
-- This is only used at the moment for the import dirs in
189-
-- the DynFlags
190-
, envImportPaths :: Maybe [String]
191-
-- ^ If Just, import dirs originally configured in this env
192-
-- If Nothing, the env import dirs are unaltered
193-
}
194-
195-
-- | Wrap an 'HscEnv' into an 'HscEnvEq'.
196-
newHscEnvEq :: FilePath -> HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
197-
newHscEnvEq cradlePath hscEnv0 deps = do
198-
envUnique <- newUnique
199-
let relativeToCradle = (takeDirectory cradlePath </>)
200-
hscEnv = removeImportPaths hscEnv0
201-
202-
-- Canonicalize import paths since we also canonicalize targets
203-
importPathsCanon <-
204-
mapM canonicalizePath $ relativeToCradle <$> importPaths (hsc_dflags hscEnv0)
205-
let envImportPaths = Just importPathsCanon
206-
207-
return HscEnvEq{..}
208-
209-
newHscEnvEqWithImportPaths :: Maybe [String] -> HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
210-
newHscEnvEqWithImportPaths envImportPaths hscEnv deps = do
211-
envUnique <- newUnique
212-
return HscEnvEq{..}
213-
214-
-- | Wrap an 'HscEnv' into an 'HscEnvEq'.
215-
newHscEnvEqPreserveImportPaths
216-
:: HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
217-
newHscEnvEqPreserveImportPaths hscEnv deps = do
218-
let envImportPaths = Nothing
219-
envUnique <- newUnique
220-
return HscEnvEq{..}
221-
222-
-- | Unwrap the 'HscEnv' with the original import paths.
223-
-- Used only for locating imports
224-
hscEnvWithImportPaths :: HscEnvEq -> HscEnv
225-
hscEnvWithImportPaths HscEnvEq{..}
226-
| Just imps <- envImportPaths
227-
= hscEnv{hsc_dflags = (hsc_dflags hscEnv){importPaths = imps}}
228-
| otherwise
229-
= hscEnv
230-
231-
removeImportPaths :: HscEnv -> HscEnv
232-
removeImportPaths hsc = hsc{hsc_dflags = (hsc_dflags hsc){importPaths = []}}
233-
234-
instance Show HscEnvEq where
235-
show HscEnvEq{envUnique} = "HscEnvEq " ++ show (hashUnique envUnique)
236-
237-
instance Eq HscEnvEq where
238-
a == b = envUnique a == envUnique b
239-
240-
instance NFData HscEnvEq where
241-
rnf (HscEnvEq a b c d) = rnf (hashUnique a) `seq` b `seq` c `seq` rnf d
242-
243-
instance Hashable HscEnvEq where
244-
hashWithSalt s = hashWithSalt s . envUnique
245-
246-
-- Fake instance needed to persuade Shake to accept this type as a key.
247-
-- No harm done as ghcide never persists these keys currently
248-
instance Binary HscEnvEq where
249-
put _ = error "not really"
250-
get = error "not really"
251-
252171
-- | Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.
253172
readFileUtf8 :: FilePath -> IO T.Text
254173
readFileUtf8 f = T.decodeUtf8With T.lenientDecode <$> BS.readFile f

0 commit comments

Comments
 (0)