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