]> gitweb @ CieloNegro.org - hs-rrdtool.git/blob - Database/RRDtool.hs
do not use IncoherentInstances
[hs-rrdtool.git] / Database / RRDtool.hs
1 module Database.RRDtool
2     ( DataSource(..)
3
4     , MentionedVars(..)
5     , ApplyMentionedVarsOf(..)
6
7     , Expr
8     , CommonExpr
9     , IterativeExpr
10     , AggregativeExpr
11
12     , ExprSet
13     , CommonExprSet
14
15     , Constant(..)
16     , VarName(..)
17     , Variable(..)
18     , VariableSet
19     , CommonUnaryOp(..)
20     , CommonBinaryOp(..)
21     , CommonTrinaryOp(..)
22     , CommonSetOp(..)
23     , TrendOp(..)
24     , VariableShiftPredictOp(..)
25     , FixedShiftPredictOp(..)
26     , CommonValue(..)
27     , IterativeValue(..)
28     , IterativeValueOf(..)
29     , AggregativeUnaryOp(..)
30
31     , createRRD
32     )
33     where
34
35 import Data.HList
36 import Data.Time.Clock
37 import Data.Time.Clock.POSIX
38
39
40 -- |A single RRD can accept input from several data sources (DS), for
41 -- example incoming and outgoing traffic on a specific communication
42 -- line. With the DS configuration option you must define some basic
43 -- properties of each data source you want to store in the RRD.
44 --
45 -- /NOTE on COUNTER vs DERIVE/
46 --
47 -- by Don Baarda <don.baarda@baesystems.com>
48 --
49 -- If you cannot tolerate ever mistaking the occasional counter reset
50 -- for a legitimate counter wrap, and would prefer \"Unknowns\" for
51 -- all legitimate counter wraps and resets, always use DERIVE with
52 -- @'dsMin' = 0@. Otherwise, using COUNTER with a suitable max will
53 -- return correct values for all legitimate counter wraps, mark some
54 -- counter resets as \"Unknown\", but can mistake some counter resets
55 -- for a legitimate counter wrap.
56 --
57 -- For a 5 minute step and 32-bit counter, the probability of
58 -- mistaking a counter reset for a legitimate wrap is arguably about
59 -- 0.8% per 1Mbps of maximum bandwidth. Note that this equates to 80%
60 -- for 100Mbps interfaces, so for high bandwidth interfaces and a
61 -- 32bit counter, DERIVE with @'dsMin' = 0@ is probably preferable. If
62 -- you are using a 64bit counter, just about any max setting will
63 -- eliminate the possibility of mistaking a reset for a counter wrap.
64 data DataSource
65     = -- |GAUGE is for things like temperatures or number of people in
66       -- a room or the value of a RedHat share.
67     GAUGE {
68         -- |The name you will use to reference this particular data
69         -- source from an RRD. A ds-name must be 1 to 19 characters
70         -- long in the characters @[a-zA-Z0-9_]@.
71         dsName :: !String
72         -- |Defines the maximum number of seconds that may
73         -- pass between two updates of this data source before the
74         -- value of the data source is assumed to be @*UNKNOWN*@.
75       , dsHeartbeat :: !NominalDiffTime
76         -- |'dsMin' and 'dsMax' Define the expected range values for
77         -- data supplied by a data source. If 'dsMin' and\/or 'dsMax'
78         -- any value outside the defined range will be regarded as
79         -- @*UNKNOWN*@. If you do not know or care about 'dsMin' and
80         -- 'dsMax', set them to 'Nothing' for unknown. Note that
81         -- 'dsMin' and 'dsMax' always refer to the processed values of
82         -- the DS. For a traffic-'COUNTER' type DS this would be the
83         -- maximum and minimum data-rate expected from the device.
84         --
85         -- If information on minimal\/maximal expected values is
86         -- available, always set the min and\/or max properties. This
87         -- will help RRDtool in doing a simple sanity check on the
88         -- data supplied when running update.
89       , dsMin :: !(Maybe Double)
90         -- |See 'dsMin'.
91       , dsMax :: !(Maybe Double)
92     }
93     -- |COUNTER is for continuous incrementing counters like the
94     -- ifInOctets counter in a router. The COUNTER data source assumes
95     -- that the counter never decreases, except when a counter
96     -- overflows. The update function takes the overflow into
97     -- account. The counter is stored as a per-second rate. When the
98     -- counter overflows, RRDtool checks if the overflow happened at
99     -- the 32bit or 64bit border and acts accordingly by adding an
100     -- appropriate value to the result.
101     | COUNTER {
102         dsName      :: !String
103       , dsHeartbeat :: !NominalDiffTime
104       , dsMin       :: !(Maybe Double)
105       , dsMax       :: !(Maybe Double)
106     }
107     -- |DERIVE will store the derivative of the line going from the
108     -- last to the current value of the data source. This can be
109     -- useful for gauges, for example, to measure the rate of people
110     -- entering or leaving a room. Internally, derive works exactly
111     -- like COUNTER but without overflow checks. So if your counter
112     -- does not reset at 32 or 64 bit you might want to use DERIVE and
113     -- combine it with a 'dsMin' value of 0.
114     | DERIVE {
115         dsName      :: !String
116       , dsHeartbeat :: !NominalDiffTime
117       , dsMin       :: !(Maybe Double)
118       , dsMax       :: !(Maybe Double)
119     }
120     -- |ABSOLUTE is for counters which get reset upon reading. This is
121     -- used for fast counters which tend to overflow. So instead of
122     -- reading them normally you reset them after every read to make
123     -- sure you have a maximum time available before the next
124     -- overflow. Another usage is for things you count like number of
125     -- messages since the last update.
126     | ABSOLUTE {
127         dsName      :: !String
128       , dsHeartbeat :: !NominalDiffTime
129       , dsMin       :: !(Maybe Double)
130       , dsMax       :: !(Maybe Double)
131     }
132     -- |COMPUTE is for storing the result of a formula applied to
133     -- other data sources in the RRD. This data source is not supplied
134     -- a value on update, but rather its Primary Data Points (PDPs)
135     -- are computed from the PDPs of the data sources according to the
136     -- rpn-expression that defines the formula. Consolidation
137     -- functions are then applied normally to the PDPs of the COMPUTE
138     -- data source (that is the rpn-expression is only applied to
139     -- generate PDPs). In database software, such data sets are
140     -- referred to as \"virtual\" or \"computed\" columns.
141     --
142     -- FIXME: doc links
143     | forall a. CommonExpr a => COMPUTE {
144         dsName :: !String
145         -- |rpn-expression defines the formula used to compute the
146         -- PDPs of a COMPUTE data source from other data sources in
147         -- the same \<RRD\>. It is similar to defining a CDEF argument
148         -- for the graph command.  For COMPUTE data sources, the
149         -- following RPN operations are not supported: COUNT, PREV,
150         -- TIME, and LTIME. In addition, in defining the RPN
151         -- expression, the COMPUTE data source may only refer to the
152         -- names of data source listed previously in the create
153         -- command. This is similar to the restriction that CDEFs must
154         -- refer only to DEFs and CDEFs previously defined in the same
155         -- graph command.
156         -- 
157         -- FIXME: doc links
158       , dsExpr :: !a
159     }
160
161 dsTest :: DataSource
162 dsTest = COMPUTE {
163            dsName = "foo"
164 --         , dsExpr = Previous :<: Const 100
165 --         , dsExpr = Var "foo" :<: Const 100
166            , dsExpr = AverageOf (Const 100 .*. Const 200 .*. HNil)
167          }
168
169 -- MentionedVars
170 class VariableSet (MentionedVarsOf a) => MentionedVars a where
171     type MentionedVarsOf a
172
173 -- ApplyMentionedVarsOf
174 data ApplyMentionedVarsOf = ApplyMentionedVarsOf
175
176 instance Applyable ApplyMentionedVarsOf a where
177     type Apply ApplyMentionedVarsOf a = MentionedVarsOf a
178     apply = undefined
179
180 -- Expr
181 class (Show e, Eq e) => Expr e
182 class Expr e => CommonExpr e
183 class Expr e => IterativeExpr e
184 class Expr e => AggregativeExpr e
185
186 class (Show es, Eq es, HList es) => ExprSet es
187 instance ExprSet HNil
188 instance (Expr e, ExprSet es) => ExprSet (e :*: es)
189
190 class (Show es, Eq es, HList es) => CommonExprSet es
191 instance CommonExprSet HNil
192 instance (CommonExpr e, CommonExprSet es) => CommonExprSet (e :*: es)
193
194
195 -- Constants and variable names
196 data Constant
197     = Const !Double
198     deriving (Show, Eq, Ord)
199 instance Expr Constant
200 instance CommonExpr Constant
201 instance MentionedVars Constant where
202     type MentionedVarsOf Constant = HNil
203
204 class (Show a, Eq a, Ord a) => VarName a where
205     varName :: a -> String
206
207 data Variable vn
208     = Variable !vn
209     deriving (Show, Eq, Ord)
210
211 instance VarName vn => Expr (Variable vn)
212 instance VarName vn => CommonExpr (Variable vn)
213 instance VarName vn => MentionedVars (Variable vn) where
214     type MentionedVarsOf (Variable vn) = vn :*: HNil
215
216 class HList vs => VariableSet vs
217 instance VariableSet HNil
218 instance (VarName v, VariableSet vs) => VariableSet (v :*: vs)
219
220 -- Common operators
221 data CommonUnaryOp a
222     = IsUnknown  !a
223     | IsInfinity !a
224     | Sin        !a
225     | Cos        !a
226     | Log        !a
227     | Exp        !a
228     | Sqrt       !a
229     | Atan       !a
230     | Floor      !a
231     | Ceil       !a
232     | Deg2Rad    !a
233     | Rad2Deg    !a
234     | Abs        !a
235     deriving (Show, Eq, Ord)
236 instance Expr a => Expr (CommonUnaryOp a)
237 instance CommonExpr a => CommonExpr (CommonUnaryOp a)
238 instance VariableSet (MentionedVarsOf a) => MentionedVars (CommonUnaryOp a) where
239     type MentionedVarsOf (CommonUnaryOp a) = MentionedVarsOf a
240
241 data CommonBinaryOp a b
242     = !a :<:  !b
243     | !a :<=: !b
244     | !a :>:  !b
245     | !a :>=: !b
246     | !a :==: !b
247     | !a :/=: !b
248     | Min !a !b
249     | Max !a !b
250     | !a :+: !b
251     | !a :-: !b
252     | !a :*: !b
253     | !a :/: !b
254     | !a :%: !b
255     | AddNaN !a !b
256     | AtanXY !a !b
257     deriving (Show, Eq, Ord)
258
259 instance (Expr a, Expr b) =>
260     Expr (CommonBinaryOp a b)
261
262 instance (CommonExpr a, CommonExpr b) =>
263     CommonExpr (CommonBinaryOp a b)
264
265 instance VariableSet (MentionedVarsOf a :++: MentionedVarsOf b) =>
266     MentionedVars (CommonBinaryOp a b) where
267         type MentionedVarsOf (CommonBinaryOp a b)
268             = MentionedVarsOf a :++: MentionedVarsOf b
269         
270
271 data CommonTrinaryOp a b c
272     = If !a !b !c
273     | Limit !a !b !c
274     deriving (Show, Eq, Ord)
275
276 instance (Expr a, Expr b, Expr c)
277     => Expr (CommonTrinaryOp a b c)
278
279 instance (CommonExpr a, CommonExpr b, CommonExpr c)
280     => CommonExpr (CommonTrinaryOp a b c)
281
282 instance VariableSet (MentionedVarsOf a :++:
283                       MentionedVarsOf b :++:
284                       MentionedVarsOf c) =>
285     MentionedVars (CommonTrinaryOp a b c) where
286         type MentionedVarsOf (CommonTrinaryOp a b c)
287             = MentionedVarsOf a :++:
288               MentionedVarsOf b :++:
289               MentionedVarsOf c
290
291 -- SORT and REV can't be expressed in this way as they pushes possibly
292 -- multiple values onto the stack...
293
294 data CommonSetOp es
295     = AverageOf !es
296     deriving (Show, Eq, Ord)
297
298 instance ExprSet es => Expr (CommonSetOp es)
299 instance (ExprSet es, CommonExprSet es) => CommonExpr (CommonSetOp es)
300 instance VariableSet (HConcat (HMap ApplyMentionedVarsOf es)) =>
301     MentionedVars (CommonSetOp es) where
302         type MentionedVarsOf (CommonSetOp es)
303             = HConcat (HMap ApplyMentionedVarsOf es)
304
305 data TrendOp vn a
306     = Trend      !(Variable vn) !a
307     | TrendNan   !(Variable vn) !a
308     deriving (Show, Eq, Ord)
309 instance (VarName vn, Expr a) => Expr (TrendOp vn a)
310 instance (VarName vn, CommonExpr a) => CommonExpr (TrendOp vn a)
311 instance (VarName vn, MentionedVars a) => MentionedVars (TrendOp vn a) where
312     type MentionedVarsOf (TrendOp vn a) = vn :*: MentionedVarsOf a
313
314 data VariableShiftPredictOp ss w vn
315     = VariableShiftPredictAverage !ss !w !(Variable vn)
316     | VariableShiftPredictSigma   !ss !w !(Variable vn)
317     deriving (Show, Eq, Ord)
318 instance (ExprSet ss, Expr w, VarName vn)
319     => Expr (VariableShiftPredictOp ss w vn)
320 instance (ExprSet ss, CommonExprSet ss, CommonExpr w, VarName vn)
321     => CommonExpr (VariableShiftPredictOp ss w vn)
322 instance ( VarName vn
323          , VariableSet (MentionedVarsOf ss :++: MentionedVarsOf w)
324          ) => MentionedVars (VariableShiftPredictOp ss w vn) where
325     type MentionedVarsOf (VariableShiftPredictOp ss w vn)
326         = vn :*: (MentionedVarsOf ss :++: MentionedVarsOf w)
327
328 -- FixedShiftPredictOp
329 data FixedShiftPredictOp sm w vn
330     = FixedShiftPredictAverage !sm !w !(Variable vn)
331     | FixedShiftPredictSigma   !sm !w !(Variable vn)
332     deriving (Show, Eq, Ord)
333
334 instance (Expr sm, Expr w, VarName vn)
335     => Expr (FixedShiftPredictOp sm w vn)
336
337 instance (CommonExpr sm, CommonExpr w, VarName vn)
338     => CommonExpr (FixedShiftPredictOp sm w vn)
339
340 instance ( VarName vn
341          , VariableSet (MentionedVarsOf sm :++: MentionedVarsOf w)
342          ) => MentionedVars (FixedShiftPredictOp sm w vn) where
343     type MentionedVarsOf (FixedShiftPredictOp sm w vn)
344         = vn :*: (MentionedVarsOf sm :++: MentionedVarsOf w)
345
346 -- Common special values
347 data CommonValue
348     = Unknown
349     | Infinity
350     | NegativeInfinity
351     | Now
352     deriving (Show, Eq, Ord)
353
354 instance Expr CommonValue
355
356 instance CommonExpr CommonValue
357
358 instance MentionedVars CommonValue where
359     type MentionedVarsOf CommonValue = HNil
360
361 -- Iterative special values
362 data IterativeValue
363     = Previous
364     | Count
365     | TakenTime
366     | TakenLocalTime
367     deriving (Show, Eq, Ord)
368
369 instance Expr IterativeValue
370
371 instance IterativeExpr IterativeValue
372
373 instance MentionedVars IterativeValue where
374     type MentionedVarsOf IterativeValue = HNil
375
376 -- Iterative special values of something
377 data IterativeValueOf vn
378     = PreviousOf !(Variable vn)
379     deriving (Show, Eq, Ord)
380
381 instance VarName vn => Expr (IterativeValueOf vn)
382
383 instance VarName vn => IterativeExpr (IterativeValueOf vn)
384
385 instance VarName vn => MentionedVars (IterativeValueOf vn) where
386     type MentionedVarsOf (IterativeValueOf vn) = vn :*: HNil
387
388 -- Aggregative operators (fairly restricted due to rrdtool's
389 -- restriction)
390 data AggregativeUnaryOp vn
391     = Maximum    !(Variable vn)
392     | Minimum    !(Variable vn)
393     | Average    !(Variable vn)
394     | StandardDeviation !(Variable vn)
395     | First      !(Variable vn)
396     | Last       !(Variable vn)
397     | Total      !(Variable vn)
398     | Percent    !(Variable vn) !Constant
399     | PercentNan !(Variable vn) !Constant
400     | LSLSlope   !(Variable vn)
401     | LSLInt     !(Variable vn)
402     | LSLCorrel  !(Variable vn)
403     deriving (Show, Eq, Ord)
404
405 instance VarName vn => Expr (AggregativeUnaryOp vn)
406
407 instance VarName vn => AggregativeExpr (AggregativeUnaryOp vn)
408
409 instance VarName vn => MentionedVars (AggregativeUnaryOp vn) where
410     type MentionedVarsOf (AggregativeUnaryOp vn) = vn :*: HNil
411
412 -- |The 'createRRD' function lets you set up new Round Robin Database
413 -- (RRD) files. The file is created at its final, full size and filled
414 -- with @*UNKNOWN*@ data.
415 createRRD
416     :: FilePath -- ^The name of the RRD you want to create. RRD files
417                 -- should end with the extension @.rrd@. However,
418                 -- RRDtool will accept any filename.
419     -> Bool -- ^Do not clobber an existing file of the same name.
420     -> Maybe POSIXTime -- ^Specifies the time in seconds since
421                        -- @1970-01-01 UTC@ when the first value should
422                        -- be added to the RRD. RRDtool will not accept
423                        -- any data timed before or at the time
424                        -- specified. (default: @now - 10s@)
425     -> Maybe NominalDiffTime -- ^Specifies the base interval in
426                              -- seconds with which data will be fed
427                              -- into the RRD. (default: 300 sec)
428     -> [DataSource] -- ^Data sources to accept input from.
429     -> IO ()
430 createRRD = error "FIXME"