| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Instrument.Types
Synopsis
- createInstrumentPool :: ConnectInfo -> IO Connection
- type Samplers = Map (MetricName, Dimensions) Sampler
- type Counters = Map (MetricName, Dimensions) Counter
- data Instrument = I {}
- data InstrumentConfig = ICfg {}
- data SubmissionPacket = SP {
- spTimeStamp :: !Double
- spName :: !MetricName
- spPayload :: !Payload
- spDimensions :: !Dimensions
- newtype MetricName = MetricName {
- metricName :: String
- newtype DimensionName = DimensionName {}
- newtype DimensionValue = DimensionValue {}
- type Dimensions = Map DimensionName DimensionValue
- data Payload
- data Aggregated = Aggregated {}
- data AggPayload
- data Stats = Stats {}
- hostDimension :: DimensionName
- data HostDimensionPolicy
- newtype Quantile = Q {}
Documentation
type Samplers = Map (MetricName, Dimensions) Sampler Source #
type Counters = Map (MetricName, Dimensions) Counter Source #
data Instrument Source #
Constructors
| I | |
Instances
| Monad m => HasInstrument (ReaderT Instrument m) Source # | |
Defined in Instrument.ClientClass Methods | |
data InstrumentConfig Source #
Constructors
| ICfg | |
Fields | |
Instances
| Default InstrumentConfig Source # | |
Defined in Instrument.Types Methods def :: InstrumentConfig # | |
data SubmissionPacket Source #
Constructors
| SP | |
Fields
| |
Instances
newtype MetricName Source #
Constructors
| MetricName | |
Fields
| |
Instances
newtype DimensionName Source #
Constructors
| DimensionName | |
Fields | |
Instances
newtype DimensionValue Source #
Constructors
| DimensionValue | |
Fields | |
Instances
type Dimensions = Map DimensionName DimensionValue Source #
Instances
| Generic Payload Source # | |
| Show Payload Source # | |
| Serialize Payload Source # | |
| Eq Payload Source # | |
| Migrate Payload Source # | |
Defined in Instrument.Types Associated Types type MigrateFrom Payload # Methods migrate :: MigrateFrom Payload -> Payload # | |
| SafeCopy Payload Source # | |
| type Rep Payload Source # | |
Defined in Instrument.Types type Rep Payload = D1 ('MetaData "Payload" "Instrument.Types" "instrument-0.6.1.0-6Lbe4kLcaNb1isRA7npnNm" 'False) (C1 ('MetaCons "Samples" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Double])) :+: C1 ('MetaCons "Counter" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCounter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) | |
| type MigrateFrom Payload Source # | |
Defined in Instrument.Types | |
data Aggregated Source #
Constructors
| Aggregated | |
Fields
| |
Instances
data AggPayload Source #
Instances
Constructors
| Stats | |
Instances
hostDimension :: DimensionName Source #
Convention for the dimension of the hostname. Used in the client to inject hostname into the parameters map
data HostDimensionPolicy Source #
Should we automatically pull the host and add it as a
dimension. Used at the call site of the various metrics (timeI,
sampleI, etc). Hosts are basically grandfathered in as a
dimension and the functionality of automatically injecting them is
useful, but it is not relevant to some metrics and actually makes
some metrics difficult to use depending on the backend, so we made
them opt-in.
Constructors
| AddHostDimension | |
| DoNotAddHostDimension |
Instances
| Show HostDimensionPolicy Source # | |
Defined in Instrument.Types Methods showsPrec :: Int -> HostDimensionPolicy -> ShowS # show :: HostDimensionPolicy -> String # showList :: [HostDimensionPolicy] -> ShowS # | |
| Eq HostDimensionPolicy Source # | |
Defined in Instrument.Types Methods (==) :: HostDimensionPolicy -> HostDimensionPolicy -> Bool # (/=) :: HostDimensionPolicy -> HostDimensionPolicy -> Bool # | |