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