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