crucible-0.7: Crucible is a library for language-agnostic symbolic simulation
Copyright(c) Galois Inc 2018
LicenseBSD3
MaintainerRob Dockins <rdockins@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.Simulator.Profiling

Description

 
Synopsis

Documentation

profilingFeature :: ProfilingTable -> EventFilter -> Maybe ProfilingOptions -> IO (GenericExecutionFeature sym) Source #

This feature will pay attention to function call entry/exit events and track the elapsed time and various other metrics in the given profiling table. The ProfilingOptions can be used to export intermediate profiling data at regular intervals, if desired.

profilingEventFilter :: EventFilter Source #

An EventFilter that enables only Crucible profiling.

data CrucibleProfile Source #

Instances

Instances details
Generic CrucibleProfile Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Associated Types

type Rep CrucibleProfile :: Type -> Type #

Show CrucibleProfile Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep CrucibleProfile Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep CrucibleProfile = D1 ('MetaData "CrucibleProfile" "Lang.Crucible.Simulator.Profiling" "crucible-0.7-8cOLouRuT7vG1hxVUUUvCh" 'False) (C1 ('MetaCons "CrucibleProfile" 'PrefixI 'True) (S1 ('MetaSel ('Just "crucibleProfileTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "crucibleProfileCGEvents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CGEvent]) :*: S1 ('MetaSel ('Just "crucibleProfileSolverEvents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SolverEvent]))))

writeProfileReport Source #

Arguments

:: FilePath

File to write

-> String

"name" for the report

-> String

"source" for the report

-> ProfilingTable

profiling data to populate the report

-> IO () 

Write a profiling report file in the JS/JSON format expected by tye symProUI front end.

Profiling data structures

data CGEvent Source #

Instances

Instances details
Generic CGEvent Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Associated Types

type Rep CGEvent :: Type -> Type #

Methods

from :: CGEvent -> Rep CGEvent x #

to :: Rep CGEvent x -> CGEvent #

Show CGEvent Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep CGEvent Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

data CGEventType Source #

Constructors

ENTER 
EXIT 
BLOCK 
BRANCH 

Instances

Instances details
Generic CGEventType Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Associated Types

type Rep CGEventType :: Type -> Type #

Show CGEventType Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Eq CGEventType Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Ord CGEventType Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep CGEventType Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep CGEventType = D1 ('MetaData "CGEventType" "Lang.Crucible.Simulator.Profiling" "crucible-0.7-8cOLouRuT7vG1hxVUUUvCh" 'False) ((C1 ('MetaCons "ENTER" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EXIT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BLOCK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BRANCH" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype Metric p sym ext Source #

Constructors

Metric 

Fields

data Metrics f Source #

Instances

Instances details
FoldableF Metrics Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Methods

foldMapF :: Monoid m => (forall (s :: k). e s -> m) -> Metrics e -> m #

foldrF :: (forall (s :: k). e s -> b -> b) -> b -> Metrics e -> b #

foldlF :: (forall (s :: k). b -> e s -> b) -> b -> Metrics e -> b #

foldrF' :: (forall (s :: k). e s -> b -> b) -> b -> Metrics e -> b #

foldlF' :: (forall (s :: k). b -> e s -> b) -> b -> Metrics e -> b #

toListF :: (forall (tp :: k). f tp -> a) -> Metrics f -> [a] #

FunctorF Metrics Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Methods

fmapF :: (forall (x :: k). f x -> g x) -> Metrics f -> Metrics g #

TraversableF Metrics Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Methods

traverseF :: Applicative m => (forall (s :: k). e s -> m (f s)) -> Metrics e -> m (Metrics f) #

Generic (Metrics Identity) Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

Associated Types

type Rep (Metrics Identity) :: Type -> Type #

Show (Metrics Identity) Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep (Metrics Identity) Source # 
Instance details

Defined in Lang.Crucible.Simulator.Profiling

type Rep (Metrics Identity) = D1 ('MetaData "Metrics" "Lang.Crucible.Simulator.Profiling" "crucible-0.7-8cOLouRuT7vG1hxVUUUvCh" 'False) (C1 ('MetaCons "Metrics" 'PrefixI 'True) ((S1 ('MetaSel ('Just "metricSplits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identity Integer)) :*: S1 ('MetaSel ('Just "metricMerges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identity Integer))) :*: (S1 ('MetaSel ('Just "metricAborts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identity Integer)) :*: (S1 ('MetaSel ('Just "metricSolverStats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identity Statistics)) :*: S1 ('MetaSel ('Just "metricExtraMetrics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identity (Map Text Integer)))))))