5
5
module Development.IDE.Core.Tracing
6
6
( otTracedHandler
7
7
, otTracedAction
8
- , startProfilingTelemetry
9
- , measureMemory
10
- , getInstrumentCached
11
8
, otTracedProvider
12
9
, otSetUri
13
10
, otTracedGarbageCollection
@@ -17,56 +14,28 @@ module Development.IDE.Core.Tracing
17
14
)
18
15
where
19
16
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 )
28
18
import Control.Monad.Catch (ExitCase (.. ), MonadMask )
29
- import Control.Monad.Extra (whenJust )
30
19
import Control.Monad.IO.Unlift
31
- import Control.Monad.STM (atomically )
32
- import Control.Seq (r0 , seqList , seqTuple2 ,
33
- using )
34
20
import Data.ByteString (ByteString )
35
21
import Data.ByteString.Char8 (pack )
36
- import qualified Data.HashMap.Strict as HMap
37
- import Data.IORef (modifyIORef' , newIORef ,
38
- readIORef , writeIORef )
39
22
import Data.String (IsString (fromString ))
40
23
import qualified Data.Text as T
41
24
import Data.Text.Encoding (encodeUtf8 )
42
- import Data.Typeable (TypeRep , typeOf )
43
25
import Data.Word (Word16 )
44
26
import Debug.Trace.Flags (userTracingEnabled )
45
- import Development.IDE.Core.RuleTypes (GhcSession (GhcSession ),
46
- GhcSessionDeps (GhcSessionDeps ),
47
- GhcSessionIO (GhcSessionIO ))
48
27
import Development.IDE.Graph (Action )
49
28
import Development.IDE.Graph.Rule
50
29
import Development.IDE.Types.Diagnostics (FileDiagnostic ,
51
30
showDiagnostics )
52
31
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 ))
60
33
import Ide.Types (PluginId (.. ))
61
34
import Language.LSP.Types (NormalizedFilePath ,
62
35
fromNormalizedFilePath )
63
- import qualified "list-t" ListT
64
- import Numeric.Natural (Natural )
65
36
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 )
70
39
71
40
#if MIN_VERSION_ghc(8,8,0)
72
41
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
@@ -178,126 +147,3 @@ otTracedProvider (PluginId pluginName) provider act
178
147
| otherwise = act
179
148
180
149
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
-
0 commit comments