Skip to content

Commit 7f33b41

Browse files
committed
Clean up heapsize bits
1 parent 41c978d commit 7f33b41

File tree

9 files changed

+7
-193
lines changed

9 files changed

+7
-193
lines changed

Diff for: ghcide/exe/Main.hs

-1
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,6 @@ main = withTelemetryLogger $ \telemetryLogger -> do
144144
let defOptions = IDEMain.argsIdeOptions arguments config sessionLoader
145145
in defOptions
146146
{ optShakeProfiling = argsShakeProfiling
147-
, optOTMemoryProfiling = IdeOTMemoryProfiling argsOTMemoryProfiling
148147
, optCheckParents = pure $ checkParents config
149148
, optCheckProject = pure $ checkProject config
150149
, optRunSubset = not argsConservativeChangeTracking

Diff for: ghcide/ghcide.cabal

-1
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,6 @@ library
9595
Diff ^>=0.4.0,
9696
vector,
9797
opentelemetry >=0.6.1,
98-
heapsize ==0.3.*,
9998
unliftio >= 0.2.6,
10099
unliftio-core,
101100
ghc-boot-th,

Diff for: ghcide/src/Development/IDE/Core/Shake.hs

+3-6
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4+
{-# LANGUAGE CPP #-}
45
{-# LANGUAGE ConstraintKinds #-}
56
{-# LANGUAGE DerivingStrategies #-}
67
{-# LANGUAGE DuplicateRecordFields #-}
@@ -10,7 +11,6 @@
1011
{-# LANGUAGE RankNTypes #-}
1112
{-# LANGUAGE RecursiveDo #-}
1213
{-# LANGUAGE TypeFamilies #-}
13-
{-# LANGUAGE CPP #-}
1414

1515
-- | A Shake implementation of the compiler service.
1616
--
@@ -162,7 +162,7 @@ import GHC.Stack (HasCallStack)
162162
import HieDb.Types
163163
import Ide.Plugin.Config
164164
import qualified Ide.PluginUtils as HLS
165-
import Ide.Types (PluginId, IdePlugins)
165+
import Ide.Types (IdePlugins, PluginId)
166166
import Language.LSP.Diagnostics
167167
import qualified Language.LSP.Server as LSP
168168
import Language.LSP.Types
@@ -630,13 +630,10 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
630630
shakeDatabaseProfile <- shakeDatabaseProfileIO shakeProfileDir
631631

632632
IdeOptions
633-
{ optOTMemoryProfiling = IdeOTMemoryProfiling otProfilingEnabled
634-
, optProgressStyle
633+
{ optProgressStyle
635634
, optCheckParents
636635
} <- getIdeOptionsIO shakeExtras
637636

638-
startProfilingTelemetry otProfilingEnabled logger $ state shakeExtras
639-
640637
checkParents <- optCheckParents
641638

642639
-- monitoring

Diff for: ghcide/src/Development/IDE/Core/Tracing.hs

+4-158
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,6 @@
55
module Development.IDE.Core.Tracing
66
( otTracedHandler
77
, otTracedAction
8-
, startProfilingTelemetry
9-
, measureMemory
10-
, getInstrumentCached
118
, otTracedProvider
129
, otSetUri
1310
, otTracedGarbageCollection
@@ -17,56 +14,28 @@ module Development.IDE.Core.Tracing
1714
)
1815
where
1916

20-
import Control.Concurrent.Async (Async, async)
21-
import Control.Concurrent.Extra (modifyVar_, newVar, readVar,
22-
threadDelay)
23-
import Control.Exception (evaluate)
24-
import Control.Exception.Safe (SomeException, catch,
25-
generalBracket)
26-
import Control.Monad (forM_, forever, void, when,
27-
(>=>))
17+
import Control.Exception.Safe (generalBracket)
2818
import Control.Monad.Catch (ExitCase (..), MonadMask)
29-
import Control.Monad.Extra (whenJust)
3019
import Control.Monad.IO.Unlift
31-
import Control.Monad.STM (atomically)
32-
import Control.Seq (r0, seqList, seqTuple2,
33-
using)
3420
import Data.ByteString (ByteString)
3521
import Data.ByteString.Char8 (pack)
36-
import qualified Data.HashMap.Strict as HMap
37-
import Data.IORef (modifyIORef', newIORef,
38-
readIORef, writeIORef)
3922
import Data.String (IsString (fromString))
4023
import qualified Data.Text as T
4124
import Data.Text.Encoding (encodeUtf8)
42-
import Data.Typeable (TypeRep, typeOf)
4325
import Data.Word (Word16)
4426
import Debug.Trace.Flags (userTracingEnabled)
45-
import Development.IDE.Core.RuleTypes (GhcSession (GhcSession),
46-
GhcSessionDeps (GhcSessionDeps),
47-
GhcSessionIO (GhcSessionIO))
4827
import Development.IDE.Graph (Action)
4928
import Development.IDE.Graph.Rule
5029
import Development.IDE.Types.Diagnostics (FileDiagnostic,
5130
showDiagnostics)
5231
import Development.IDE.Types.Location (Uri (..))
53-
import Development.IDE.Types.Logger (Logger (Logger), logDebug,
54-
logInfo)
55-
import Development.IDE.Types.Shake (ValueWithDiagnostics (..),
56-
Values, fromKeyType)
57-
import Foreign.Storable (Storable (sizeOf))
58-
import HeapSize (recursiveSize, runHeapsize)
59-
import Ide.PluginUtils (installSigUsr1Handler)
32+
import Development.IDE.Types.Logger (Logger (Logger))
6033
import Ide.Types (PluginId (..))
6134
import Language.LSP.Types (NormalizedFilePath,
6235
fromNormalizedFilePath)
63-
import qualified "list-t" ListT
64-
import Numeric.Natural (Natural)
6536
import OpenTelemetry.Eventlog (SpanInFlight (..), addEvent,
66-
beginSpan, endSpan,
67-
mkValueObserver, observe,
68-
setTag, withSpan, withSpan_)
69-
import qualified StmContainers.Map as STM
37+
beginSpan, endSpan, setTag,
38+
withSpan)
7039

7140
#if MIN_VERSION_ghc(8,8,0)
7241
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
@@ -178,126 +147,3 @@ otTracedProvider (PluginId pluginName) provider act
178147
| otherwise = act
179148

180149

181-
startProfilingTelemetry :: Bool -> Logger -> Values -> IO ()
182-
startProfilingTelemetry allTheTime logger state = do
183-
instrumentFor <- getInstrumentCached
184-
185-
installSigUsr1Handler $ do
186-
logInfo logger "SIGUSR1 received: performing memory measurement"
187-
performMeasurement logger state instrumentFor
188-
189-
when allTheTime $ void $ regularly (1 * seconds) $
190-
performMeasurement logger state instrumentFor
191-
where
192-
seconds = 1000000
193-
194-
regularly :: Int -> IO () -> IO (Async ())
195-
regularly delay act = async $ forever (act >> threadDelay delay)
196-
197-
198-
performMeasurement ::
199-
Logger ->
200-
Values ->
201-
(Maybe String -> IO OurValueObserver) ->
202-
IO ()
203-
performMeasurement logger values instrumentFor = do
204-
contents <- atomically $ ListT.toList $ STM.listT values
205-
let keys = typeOf GhcSession
206-
: typeOf GhcSessionDeps
207-
-- TODO restore
208-
: [ kty
209-
| (k,_) <- contents
210-
, Just (kty,_) <- [fromKeyType k]
211-
-- do GhcSessionIO last since it closes over stateRef itself
212-
, kty /= typeOf GhcSession
213-
, kty /= typeOf GhcSessionDeps
214-
, kty /= typeOf GhcSessionIO
215-
]
216-
++ [typeOf GhcSessionIO]
217-
groupedForSharing <- evaluate (keys `using` seqList r0)
218-
measureMemory logger [groupedForSharing] instrumentFor values
219-
`catch` \(e::SomeException) ->
220-
logInfo logger ("MEMORY PROFILING ERROR: " <> fromString (show e))
221-
222-
223-
type OurValueObserver = Int -> IO ()
224-
225-
getInstrumentCached :: IO (Maybe String -> IO OurValueObserver)
226-
getInstrumentCached = do
227-
instrumentMap <- newVar HMap.empty
228-
mapBytesInstrument <- mkValueObserver "value map size_bytes"
229-
230-
let instrumentFor k = do
231-
mb_inst <- HMap.lookup k <$> readVar instrumentMap
232-
case mb_inst of
233-
Nothing -> do
234-
instrument <- mkValueObserver (fromString (show k ++ " size_bytes"))
235-
modifyVar_ instrumentMap (return . HMap.insert k instrument)
236-
return $ observe instrument
237-
Just v -> return $ observe v
238-
return $ maybe (return $ observe mapBytesInstrument) instrumentFor
239-
240-
whenNothing :: IO () -> IO (Maybe a) -> IO ()
241-
whenNothing act mb = mb >>= f
242-
where f Nothing = act
243-
f Just{} = return ()
244-
245-
measureMemory
246-
:: Logger
247-
-> [[TypeRep]] -- ^ Grouping of keys for the sharing-aware analysis
248-
-> (Maybe String -> IO OurValueObserver)
249-
-> Values
250-
-> IO ()
251-
measureMemory logger groups instrumentFor values = withSpan_ "Measure Memory" $ do
252-
contents <- atomically $ ListT.toList $ STM.listT values
253-
valuesSizeRef <- newIORef $ Just 0
254-
let !groupsOfGroupedValues = groupValues contents
255-
logDebug logger "STARTING MEMORY PROFILING"
256-
forM_ groupsOfGroupedValues $ \groupedValues -> do
257-
keepGoing <- readIORef valuesSizeRef
258-
whenJust keepGoing $ \_ ->
259-
whenNothing (writeIORef valuesSizeRef Nothing) $
260-
repeatUntilJust 3 $ do
261-
-- logDebug logger (fromString $ show $ map fst groupedValues)
262-
runHeapsize 25000000 $
263-
forM_ groupedValues $ \(k,v) -> withSpan ("Measure " <> fromString k) $ \sp -> do
264-
acc <- liftIO $ newIORef 0
265-
observe <- liftIO $ instrumentFor $ Just k
266-
mapM_ (recursiveSize >=> \x -> liftIO (modifyIORef' acc (+ x))) v
267-
size <- liftIO $ readIORef acc
268-
let !byteSize = sizeOf (undefined :: Word) * size
269-
setTag sp "size" (fromString (show byteSize ++ " bytes"))
270-
() <- liftIO $ observe byteSize
271-
liftIO $ modifyIORef' valuesSizeRef (fmap (+ byteSize))
272-
273-
mbValuesSize <- readIORef valuesSizeRef
274-
case mbValuesSize of
275-
Just valuesSize -> do
276-
observe <- instrumentFor Nothing
277-
observe valuesSize
278-
logDebug logger "MEMORY PROFILING COMPLETED"
279-
Nothing ->
280-
logInfo logger "Memory profiling could not be completed: increase the size of your nursery (+RTS -Ax) and try again"
281-
282-
where
283-
-- groupValues :: Values -> [ [(String, [Value Dynamic])] ]
284-
groupValues contents =
285-
let !groupedValues =
286-
[ [ (show ty, vv)
287-
| ty <- groupKeys
288-
, let vv = [ v | (fromKeyType -> Just (kty,_), ValueWithDiagnostics v _) <- contents
289-
, kty == ty]
290-
]
291-
| groupKeys <- groups
292-
]
293-
-- force the spine of the nested lists
294-
in groupedValues `using` seqList (seqList (seqTuple2 r0 (seqList r0)))
295-
296-
repeatUntilJust :: Monad m => Natural -> m (Maybe a) -> m (Maybe a)
297-
repeatUntilJust 0 _ = return Nothing
298-
repeatUntilJust nattempts action = do
299-
res <- action
300-
case res of
301-
Nothing -> repeatUntilJust (nattempts-1) action
302-
Just{} -> return res
303-

Diff for: ghcide/src/Development/IDE/Main.hs

-18
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,6 @@ import Development.IDE.Core.Shake (IdeState (shakeExtras
6464
shakeSessionInit,
6565
uses)
6666
import qualified Development.IDE.Core.Shake as Shake
67-
import Development.IDE.Core.Tracing (measureMemory)
6867
import Development.IDE.Graph (action)
6968
import Development.IDE.LSP.LanguageServer (runLanguageServer,
7069
setupLSP)
@@ -234,7 +233,6 @@ commandP plugins =
234233

235234
data Arguments = Arguments
236235
{ argsProjectRoot :: Maybe FilePath
237-
, argsOTMemoryProfiling :: Bool
238236
, argCommand :: Command
239237
, argsLogger :: IO Logger
240238
, argsRules :: Rules ()
@@ -255,7 +253,6 @@ data Arguments = Arguments
255253
defaultArguments :: Recorder (WithPriority Log) -> Logger -> Arguments
256254
defaultArguments recorder logger = Arguments
257255
{ argsProjectRoot = Nothing
258-
, argsOTMemoryProfiling = False
259256
, argCommand = LSP
260257
, argsLogger = pure logger
261258
, argsRules = mainRule (cmapWithPrio LogRules recorder) def >> action kick
@@ -439,21 +436,6 @@ defaultMain recorder Arguments{..} = withHeapStats (cmapWithPrio LogHeapStats re
439436
let nfiles xs = let n = length xs in if n == 1 then "1 file" else show n ++ " files"
440437
putStrLn $ "\nCompleted (" ++ nfiles worked ++ " worked, " ++ nfiles failed ++ " failed)"
441438

442-
when argsOTMemoryProfiling $ do
443-
let values = state $ shakeExtras ide
444-
let consoleObserver Nothing = return $ \size -> printf "Total: %.2fMB\n" (fromIntegral @Int @Double size / 1e6)
445-
consoleObserver (Just k) = return $ \size -> printf " - %s: %.2fKB\n" (show k) (fromIntegral @Int @Double size / 1e3)
446-
447-
stateContents <- atomically $ ListT.toList $ STM.listT values
448-
printf "# Shake value store contents(%d):\n" (length stateContents)
449-
let keys =
450-
nub $
451-
typeOf GhcSession :
452-
typeOf GhcSessionDeps :
453-
[kty | (fromKeyType -> Just (kty,_), _) <- stateContents, kty /= typeOf GhcSessionIO] ++
454-
[typeOf GhcSessionIO]
455-
measureMemory logger [keys] consoleObserver values
456-
457439
unless (null failed) (exitWith $ ExitFailure (length failed))
458440
Db opts cmd -> do
459441
root <- maybe IO.getCurrentDirectory return argsProjectRoot

Diff for: ghcide/src/Development/IDE/Types/Options.hs

-4
Original file line numberDiff line numberDiff line change
@@ -43,9 +43,6 @@ data IdeOptions = IdeOptions
4343
-- ^ File extensions to search for code, defaults to Haskell sources (including @.hs@)
4444
, optShakeProfiling :: Maybe FilePath
4545
-- ^ Set to 'Just' to create a directory of profiling reports.
46-
, optOTMemoryProfiling :: IdeOTMemoryProfiling
47-
-- ^ Whether to record profiling information with OpenTelemetry. You must
48-
-- also enable the -l RTS flag for this to have any effect
4946
, optTesting :: IdeTesting
5047
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
5148
, optReportProgress :: IdeReportProgress
@@ -123,7 +120,6 @@ defaultIdeOptions session = IdeOptions
123120
,optPkgLocationOpts = defaultIdePkgLocationOptions
124121
,optShakeOptions = shakeOptions
125122
,optShakeProfiling = Nothing
126-
,optOTMemoryProfiling = IdeOTMemoryProfiling False
127123
,optReportProgress = IdeReportProgress False
128124
,optLanguageSyntax = "haskell"
129125
,optNewColonConvention = False

Diff for: stack-lts16.yaml

-1
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,6 @@ extra-deps:
5757
- ghc-source-gen-0.4.1.0
5858
- ghc-trace-events-0.1.2.1
5959
- haskell-src-exts-1.21.1
60-
- heapsize-0.3.0
6160
- hlint-3.2.8
6261
- HsYAML-aeson-0.2.0.0@rev:2
6362
- hoogle-5.0.17.11

Diff for: stack-lts19.yaml

-3
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,6 @@ extra-deps:
4545
- ghc-lib-9.2.4.20220729
4646
- ghc-lib-parser-9.2.4.20220729
4747
- ghc-lib-parser-ex-9.2.0.4
48-
- heapsize-0.3.0.1@sha256:0b69aa97a46d819b700ac7b145f3b5493c3565cf2c5b8298682238d405d0326e,1417
4948
- hiedb-0.4.2.0
5049
- hlint-3.4
5150
- implicit-hie-0.1.2.7@sha256:82bbbb1a8c05f99c8af3c16ac53e80c8648d8bf047b25ed5ce45a135bd736907,3122
@@ -66,8 +65,6 @@ configure-options:
6665
- --disable-library-for-ghci
6766
haskell-language-server:
6867
- --disable-library-for-ghci
69-
heapsize:
70-
- --disable-library-for-ghci
7168

7269
flags:
7370
haskell-language-server:

Diff for: stack.yaml

-1
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,6 @@ packages:
3737

3838
extra-deps:
3939
- floskell-0.10.6@sha256:e77d194189e8540abe2ace2c7cb8efafc747ca35881a2fefcbd2d40a1292e036,3819
40-
- heapsize-0.3.0.1@sha256:0b69aa97a46d819b700ac7b145f3b5493c3565cf2c5b8298682238d405d0326e,1417
4140
- hiedb-0.4.2.0
4241
- implicit-hie-0.1.2.7@sha256:82bbbb1a8c05f99c8af3c16ac53e80c8648d8bf047b25ed5ce45a135bd736907,3122
4342
- implicit-hie-cradle-0.5.0.0@sha256:4276f60f3a59bc22df03fd918f73bca9f777de9568f85e3a8be8bd7566234a59,2368

0 commit comments

Comments
 (0)