hdr-histogram-0.1.0.0: Haskell implementation of High Dynamic Range (HDR) Histograms

Copyright(c) Josh Bohde 2015
LicenseGPL-3
Maintainerjosh@joshbohde.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Data.HdrHistogram.Mutable

Contents

Description

A Haskell implementation of HdrHistogram. It allows storing counts of observed values within a range, while maintaining precision to a configurable number of significant digits.

The mutable histogram allows only writes, and conversion to and from pure histograms. It follows the original implementation, and has similar performance characteristics. Current recording benchmarks take about 9ns, and allocates 16 bytes.

Synopsis

Histogram

data Histogram s c value count Source #

A mutable Histogram

Constructors

Histogram 

Fields

Instances

Generic (Histogram s c value count) Source # 

Associated Types

type Rep (Histogram s c value count) :: * -> * #

Methods

from :: Histogram s c value count -> Rep (Histogram s c value count) x #

to :: Rep (Histogram s c value count) x -> Histogram s c value count #

(NFData value, NFData count) => NFData (Histogram s config value count) Source # 

Methods

rnf :: Histogram s config value count -> () #

type Rep (Histogram s c value count) Source # 
type Rep (Histogram s c value count) = D1 (MetaData "Histogram" "Data.HdrHistogram.Mutable" "hdr-histogram-0.1.0.0-XlzMRMPJ4Q8dpA2YJm49p" False) (C1 (MetaCons "Histogram" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_config") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HistogramConfig value))) ((:*:) (S1 (MetaSel (Just Symbol "totalCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (MutVar s count))) (S1 (MetaSel (Just Symbol "counts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (MVector s count))))))

new :: forall m config a count. (PrimMonad m, HasConfig config, Integral a, FiniteBits a, Unbox count, Integral count) => m (Histogram (PrimState m) config a count) Source #

Construct a Histogram

fromConfig :: (PrimMonad m, Unbox count, Integral count) => Tagged c (HistogramConfig value) -> m (Histogram (PrimState m) c value count) Source #

Construct a Histogram from the given HistogramConfig. In this case c is a phantom type.

Writing

record :: (Integral value, Integral count, FiniteBits value, Unbox count, PrimMonad m) => Histogram (PrimState m) c value count -> value -> m () Source #

Record value single value to the Histogram

recordValues :: (Integral value, Integral count, FiniteBits value, Unbox count, PrimMonad m) => Histogram (PrimState m) config value count -> value -> count -> m () Source #

Record a multiple instances of a value value to the Histogram

Converting

freeze :: (Unbox count, PrimMonad m) => Histogram (PrimState m) config value count -> m (Histogram config value count) Source #

Convert a mutable Histogram to a pure Histogram

unsafeFreeze :: (Unbox count, PrimMonad m) => Histogram (PrimState m) config value count -> m (Histogram config value count) Source #

Convert a mutable Histogram to a pure Histogram. The mutable cannot counte reused after this.

thaw :: (Unbox count, PrimMonad m) => Histogram config value count -> m (Histogram (PrimState m) config value count) Source #

Convert a pure Histogram to a mutable Histogram.

unsafeThaw :: (Unbox count, PrimMonad m) => Histogram config value count -> m (Histogram (PrimState m) config value count) Source #

Convert a pure Histogram to a mutable Histogram. The pure cannot counte reused after this.

Re-exports

data Config lowest highest sig Source #

Type-safe configuration for a Histogram

Instances

(KnownNat low, KnownNat high, KnownNat sig, HighLow low high, SigBounds sig) => HasConfig (Config low high sig) Source # 

Methods

getConfig :: (Integral a, FiniteBits a) => Proxy * (Config low high sig) -> HistogramConfig a Source #

class HasConfig s Source #

Typeclass to specify the types which can produce a HistogramConfig

Minimal complete definition

getConfig

Instances

(KnownNat low, KnownNat high, KnownNat sig, HighLow low high, SigBounds sig) => HasConfig (Config low high sig) Source # 

Methods

getConfig :: (Integral a, FiniteBits a) => Proxy * (Config low high sig) -> HistogramConfig a Source #