]> gitweb @ CieloNegro.org - hs-rrdtool.git/blob - Database/RRDtool.hs
major refactoring
[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 instance CommonExpr e => IterativeExpr e
186
187 class (Show es, Eq es, HList es) => ExprSet es
188 instance ExprSet HNil
189 instance (Expr e, ExprSet es) => ExprSet (e :*: es)
190
191 class (Show es, Eq es, HList es) => CommonExprSet es
192 instance CommonExprSet es => ExprSet es
193 instance CommonExprSet HNil
194 instance (CommonExpr e, CommonExprSet es) => CommonExprSet (e :*: es)
195
196
197 -- Constants and variable names
198 data Constant
199     = Const !Double
200     deriving (Show, Eq, Ord)
201 instance Expr Constant
202 instance CommonExpr Constant
203 instance MentionedVars Constant where
204     type MentionedVarsOf Constant = HNil
205
206 class (Show a, Eq a, Ord a) => VarName a where
207     varName :: a -> String
208
209 data Variable vn
210     = Variable !vn
211     deriving (Show, Eq, Ord)
212
213 instance VarName vn => Expr (Variable vn)
214 instance VarName vn => CommonExpr (Variable vn)
215 instance VarName vn => MentionedVars (Variable vn) where
216     type MentionedVarsOf (Variable vn) = vn :*: HNil
217
218 class HList vs => VariableSet vs
219 instance VariableSet HNil
220 instance (VarName v, VariableSet vs) => VariableSet (v :*: vs)
221
222 -- Common operators
223 data CommonUnaryOp a
224     = IsUnknown  !a
225     | IsInfinity !a
226     | Sin        !a
227     | Cos        !a
228     | Log        !a
229     | Exp        !a
230     | Sqrt       !a
231     | Atan       !a
232     | Floor      !a
233     | Ceil       !a
234     | Deg2Rad    !a
235     | Rad2Deg    !a
236     | Abs        !a
237     deriving (Show, Eq, Ord)
238 instance Expr a => Expr (CommonUnaryOp a)
239 instance CommonExpr a => CommonExpr (CommonUnaryOp a)
240 instance VariableSet (MentionedVarsOf a) => MentionedVars (CommonUnaryOp a) where
241     type MentionedVarsOf (CommonUnaryOp a) = MentionedVarsOf a
242
243 data CommonBinaryOp a b
244     = !a :<:  !b
245     | !a :<=: !b
246     | !a :>:  !b
247     | !a :>=: !b
248     | !a :==: !b
249     | !a :/=: !b
250     | Min !a !b
251     | Max !a !b
252     | !a :+: !b
253     | !a :-: !b
254     | !a :*: !b
255     | !a :/: !b
256     | !a :%: !b
257     | AddNaN !a !b
258     | AtanXY !a !b
259     deriving (Show, Eq, Ord)
260
261 instance (Expr a, Expr b) =>
262     Expr (CommonBinaryOp a b)
263
264 instance (CommonExpr a, CommonExpr b) =>
265     CommonExpr (CommonBinaryOp a b)
266
267 instance VariableSet (MentionedVarsOf a :++: MentionedVarsOf b) =>
268     MentionedVars (CommonBinaryOp a b) where
269         type MentionedVarsOf (CommonBinaryOp a b)
270             = MentionedVarsOf a :++: MentionedVarsOf b
271         
272
273 data CommonTrinaryOp a b c
274     = If !a !b !c
275     | Limit !a !b !c
276     deriving (Show, Eq, Ord)
277
278 instance (Expr a, Expr b, Expr c)
279     => Expr (CommonTrinaryOp a b c)
280
281 instance (CommonExpr a, CommonExpr b, CommonExpr c)
282     => CommonExpr (CommonTrinaryOp a b c)
283
284 instance VariableSet (MentionedVarsOf a :++:
285                       MentionedVarsOf b :++:
286                       MentionedVarsOf c) =>
287     MentionedVars (CommonTrinaryOp a b c) where
288         type MentionedVarsOf (CommonTrinaryOp a b c)
289             = MentionedVarsOf a :++:
290               MentionedVarsOf b :++:
291               MentionedVarsOf c
292
293 -- SORT and REV can't be expressed in this way as they pushes possibly
294 -- multiple values onto the stack...
295
296 data CommonSetOp es
297     = AverageOf !es
298     deriving (Show, Eq, Ord)
299
300 instance ExprSet es => Expr (CommonSetOp es)
301 instance CommonExprSet es => CommonExpr (CommonSetOp es)
302 instance VariableSet (HConcat (HMap ApplyMentionedVarsOf es)) =>
303     MentionedVars (CommonSetOp es) where
304         type MentionedVarsOf (CommonSetOp es)
305             = HConcat (HMap ApplyMentionedVarsOf es)
306
307 data TrendOp vn a
308     = Trend      !(Variable vn) !a
309     | TrendNan   !(Variable vn) !a
310     deriving (Show, Eq, Ord)
311 instance (VarName vn, Expr a) => Expr (TrendOp vn a)
312 instance (VarName vn, CommonExpr a) => CommonExpr (TrendOp vn a)
313 instance (VarName vn, MentionedVars a) => MentionedVars (TrendOp vn a) where
314     type MentionedVarsOf (TrendOp vn a) = vn :*: MentionedVarsOf a
315
316 data VariableShiftPredictOp ss w vn
317     = VariableShiftPredictAverage !ss !w !(Variable vn)
318     | VariableShiftPredictSigma   !ss !w !(Variable vn)
319     deriving (Show, Eq, Ord)
320 instance (ExprSet ss, Expr w, VarName vn)
321     => Expr (VariableShiftPredictOp ss w vn)
322 instance (CommonExprSet ss, CommonExpr w, VarName vn)
323     => CommonExpr (VariableShiftPredictOp ss w vn)
324 instance ( VarName vn
325          , VariableSet (MentionedVarsOf ss :++: MentionedVarsOf w)
326          ) => MentionedVars (VariableShiftPredictOp ss w vn) where
327     type MentionedVarsOf (VariableShiftPredictOp ss w vn)
328         = vn :*: (MentionedVarsOf ss :++: MentionedVarsOf w)
329
330 -- FixedShiftPredictOp
331 data FixedShiftPredictOp sm w vn
332     = FixedShiftPredictAverage !sm !w !(Variable vn)
333     | FixedShiftPredictSigma   !sm !w !(Variable vn)
334     deriving (Show, Eq, Ord)
335
336 instance (Expr sm, Expr w, VarName vn)
337     => Expr (FixedShiftPredictOp sm w vn)
338
339 instance (CommonExpr sm, CommonExpr w, VarName vn)
340     => CommonExpr (FixedShiftPredictOp sm w vn)
341
342 instance ( VarName vn
343          , VariableSet (MentionedVarsOf sm :++: MentionedVarsOf w)
344          ) => MentionedVars (FixedShiftPredictOp sm w vn) where
345     type MentionedVarsOf (FixedShiftPredictOp sm w vn)
346         = vn :*: (MentionedVarsOf sm :++: MentionedVarsOf w)
347
348 -- Common special values
349 data CommonValue
350     = Unknown
351     | Infinity
352     | NegativeInfinity
353     | Now
354     deriving (Show, Eq, Ord)
355
356 instance Expr CommonValue
357
358 instance CommonExpr CommonValue
359
360 instance MentionedVars CommonValue where
361     type MentionedVarsOf CommonValue = HNil
362
363 -- Iterative special values
364 data IterativeValue
365     = Previous
366     | Count
367     | TakenTime
368     | TakenLocalTime
369     deriving (Show, Eq, Ord)
370
371 instance Expr IterativeValue
372
373 instance IterativeExpr IterativeValue
374
375 instance MentionedVars IterativeValue where
376     type MentionedVarsOf IterativeValue = HNil
377
378 -- Iterative special values of something
379 data IterativeValueOf vn
380     = PreviousOf !(Variable vn)
381     deriving (Show, Eq, Ord)
382
383 instance VarName vn => Expr (IterativeValueOf vn)
384
385 instance VarName vn => IterativeExpr (IterativeValueOf vn)
386
387 instance VarName vn => MentionedVars (IterativeValueOf vn) where
388     type MentionedVarsOf (IterativeValueOf vn) = vn :*: HNil
389
390 -- Aggregative operators (fairly restricted due to rrdtool's
391 -- restriction)
392 data AggregativeUnaryOp vn
393     = Maximum    !(Variable vn)
394     | Minimum    !(Variable vn)
395     | Average    !(Variable vn)
396     | StandardDeviation !(Variable vn)
397     | First      !(Variable vn)
398     | Last       !(Variable vn)
399     | Total      !(Variable vn)
400     | Percent    !(Variable vn) !Constant
401     | PercentNan !(Variable vn) !Constant
402     | LSLSlope   !(Variable vn)
403     | LSLInt     !(Variable vn)
404     | LSLCorrel  !(Variable vn)
405     deriving (Show, Eq, Ord)
406
407 instance VarName vn => Expr (AggregativeUnaryOp vn)
408
409 instance VarName vn => AggregativeExpr (AggregativeUnaryOp vn)
410
411 instance VarName vn => MentionedVars (AggregativeUnaryOp vn) where
412     type MentionedVarsOf (AggregativeUnaryOp vn) = vn :*: HNil
413
414 -- |The 'createRRD' function lets you set up new Round Robin Database
415 -- (RRD) files. The file is created at its final, full size and filled
416 -- with @*UNKNOWN*@ data.
417 createRRD
418     :: FilePath -- ^The name of the RRD you want to create. RRD files
419                 -- should end with the extension @.rrd@. However,
420                 -- RRDtool will accept any filename.
421     -> Bool -- ^Do not clobber an existing file of the same name.
422     -> Maybe POSIXTime -- ^Specifies the time in seconds since
423                        -- @1970-01-01 UTC@ when the first value should
424                        -- be added to the RRD. RRDtool will not accept
425                        -- any data timed before or at the time
426                        -- specified. (default: @now - 10s@)
427     -> Maybe NominalDiffTime -- ^Specifies the base interval in
428                              -- seconds with which data will be fed
429                              -- into the RRD. (default: 300 sec)
430     -> [DataSource] -- ^Data sources to accept input from.
431     -> IO ()
432 createRRD = error "FIXME"