StrategyLib-4.0.0.0ContentsIndex
Data.Generics.Strafunski.StrategyLib.MetricsTheme
Portabilityportable
Stabilityexperimental
MaintainerRalf Laemmel, Joost Visser
Contents
An abstract datatype for metrics
Metrics as monoids
Strategy combinators for metrics
Generic metric algorithms
Description
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.
Synopsis
newtype Metrics = M (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
predMetric :: (MonadPlus m, Term b) => TU Metrics m -> (MetricName, b -> m ()) -> TU Metrics m
depthWith :: MonadPlus m => TU () m -> TU Int m
An abstract datatype for metrics
newtype Metrics
The type of metrics
Constructors
M (MetricName -> Integer)
show/hide Instances
type MetricName = String
The type of metric names
initMetrics :: Integer -> Metrics
Create Metrics with given initial value for all metrics.
initMetrics0 :: Metrics
Create Metrics with 0 as initial value for all metrics.
incMetrics :: MetricName -> Integer -> Metrics -> Metrics

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 -> Metrics
Increment metric with the given name by 1.
putMetricLn :: MetricName -> Metrics -> IO ()
Print value of metric with the given name.
Metrics as monoids
Strategy combinators for metrics
typeMetric
:: (MonadPlus m, Term a)
=> TU Metrics mMetric collecting strategy
-> (MetricName, a -> ())Name of the metric and type guard
-> TU Metrics mStrategy that additionally collects type-based metrics
Additionally collect type-based metrics.
predMetric
:: (MonadPlus m, Term b)
=> TU Metrics mStrategy that collects metrics
-> (MetricName, b -> m ())Name of the metric, and predicate
-> TU Metrics mStrategy that additionally collects predicate-based metric
Additionally collect predicate-based metrics.
Generic metric algorithms
depthWith
:: MonadPlus m
=> TU () mRecognize relevant contructs
-> TU Int mCount nesting depth of relevant constructs.
Generic algorithm for computing nesting depth
Produced by Haddock version 0.8