Portability | portable |
---|---|
Stability | experimental |
Maintainer | Ralf Laemmel, Joost Visser |
Safe Haskell | None |
This module is part of StrategyLib
, a library of functional strategy
combinators, including combinators for generic traversal. This module
defines combinators to define metrics extractors.
- type Metrics = MetricName -> Integer
- type MetricName = String
- initMetrics :: Integer -> Metrics
- initMetrics0 :: Metrics
- incMetrics :: MetricName -> Integer -> Metrics -> Metrics
- incMetrics1 :: MetricName -> Metrics -> Metrics
- putMetricLn :: MetricName -> Metrics -> IO ()
- typeMetric :: (MonadPlus m, Term a) => TU Metrics m -> (MetricName, a -> ()) -> TU Metrics m
- depthWith :: MonadPlus m => TU () m -> TU Int m
An abstract datatype for metrics
type Metrics = MetricName -> IntegerSource
The type of metrics
type MetricName = StringSource
The type of metric names
initMetrics :: Integer -> MetricsSource
Create Metrics
with given initial value for all metrics.
Create Metrics
with 0 as initial value for all metrics.
incMetrics :: MetricName -> Integer -> Metrics -> MetricsSource
Create Metrics
with
initTypeMetrics :: MetricName -> a -> Metrics
initTypeMetrics key _ = incMetrics1 key initMetrics0
Increment metric with the given name with the given value.
incMetrics1 :: MetricName -> Metrics -> MetricsSource
Increment metric with the given name by 1.
putMetricLn :: MetricName -> Metrics -> IO ()Source
Print value of metric with the given name.
Metrics as monoids
Strategy combinators for metrics
:: (MonadPlus m, Term a) | |
=> TU Metrics m | Metric collecting strategy |
-> (MetricName, a -> ()) | Name of the metric and type guard |
-> TU Metrics m | Strategy that additionally collects type-based metrics |
Additionally collect type-based metrics.