{-# LANGUAGE NumericUnderscores #-}
module Development.IDE.Main.HeapStats ( withHeapStats ) where
import Control.Concurrent
import Control.Concurrent.Async
import Control.Monad
import qualified Data.Text as T
import Data.Word
import Development.IDE.Types.Logger (Logger, logInfo)
import GHC.Stats
import Text.Printf (printf)
heapStatsInterval :: Int
heapStatsInterval :: Int
heapStatsInterval = Int
60_000_000
logHeapStats :: Logger -> IO ()
logHeapStats :: Logger -> IO ()
logHeapStats Logger
l = do
RTSStats
stats <- IO RTSStats
getRTSStats
let live_bytes :: Word64
live_bytes = GCDetails -> Word64
gcdetails_live_bytes (RTSStats -> GCDetails
gc RTSStats
stats)
heap_size :: Word64
heap_size = GCDetails -> Word64
gcdetails_mem_in_use_bytes (RTSStats -> GCDetails
gc RTSStats
stats)
format :: Word64 -> T.Text
format :: Word64 -> Text
format Word64
m = String -> Text
T.pack (String -> Double -> String
forall r. PrintfType r => String -> r
printf String
"%.2fMB" (Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word64 @Double Word64
m Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1e6))
message :: Text
message = Text
"Live bytes: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Word64 -> Text
format Word64
live_bytes Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"Heap size: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Word64 -> Text
format Word64
heap_size
Logger -> Text -> IO ()
logInfo Logger
l Text
message
heapStatsThread :: Logger -> IO r
heapStatsThread :: Logger -> IO r
heapStatsThread Logger
l = IO () -> IO r
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO r) -> IO () -> IO r
forall a b. (a -> b) -> a -> b
$ do
Int -> IO ()
threadDelay Int
heapStatsInterval
Logger -> IO ()
logHeapStats Logger
l
withHeapStats :: Logger -> IO r -> IO r
withHeapStats :: Logger -> IO r -> IO r
withHeapStats Logger
l IO r
k = do
Bool
enabled <- IO Bool
getRTSStatsEnabled
if Bool
enabled
then do
Logger -> Text -> IO ()
logInfo Logger
l (Text
"Logging heap statistics every "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> Double -> String
forall r. PrintfType r => String -> r
printf String
"%.2fs" (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Double Int
heapStatsInterval Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1e6)))
IO Any -> (Async Any -> IO r) -> IO r
forall a b. IO a -> (Async a -> IO b) -> IO b
withAsync (Logger -> IO Any
forall r. Logger -> IO r
heapStatsThread Logger
l) (IO r -> Async Any -> IO r
forall a b. a -> b -> a
const IO r
k)
else do
Logger -> Text -> IO ()
logInfo Logger
l Text
"Heap statistics are not enabled (RTS option -T is needed)"
IO r
k