{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TemplateHaskell #-} module GHC.RTS.Events.Analyze.Types ( -- * Events EventId(..) , EventLabel , EventSubscript , isUserEvent , isThreadEvent , parseUserEvent , showEventId -- * Options , TimelineGranularity(..) , Options(..) -- * Analysis state , RunningThreads , ThreadLabels , threadIds , ThreadInfo , EventAnalysis(..) , AnalysisState(..) , mkThreadFilter -- ** EventAnalysis lenses , events , windowThreadInfo , openEvents , startup , shutdown , inWindow -- ** AnalysisState lenses , runningThreads , windowAnalyses -- * Analysis result , Quantized(..) , ThreadId ) where import Control.Lens import Data.Char import Data.Hashable import Data.HashMap.Strict (HashMap) import Data.IntMap.Strict (IntMap) import Data.List.NonEmpty (NonEmpty) import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.Read as TR import GHC.Generics import GHC.RTS.Events (Timestamp, ThreadId) import Text.Regex.PCRE import Text.Regex.PCRE.Text () -- for RegexLike Regex Text import GHC.RTS.Events.Analyze.Utils (showThreadId) {------------------------------------------------------------------------------- Event identifiers -------------------------------------------------------------------------------} -- | Event identifiers -- -- The order of the constructors matters because it dictates the default -- ordering in the output SVG data EventId = -- | Garbage collection EventGC -- | User events -- -- To use user events, do -- -- > traceEventIO "START