]> 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     , IterativeValue(..)
21     , AggregativeUnaryOp(..)
22
23     , createRRD
24     )
25     where
26
27 import Data.HList
28 import Data.Time.Clock
29 import Data.Time.Clock.POSIX
30
31
32 -- |A single RRD can accept input from several data sources (DS), for
33 -- example incoming and outgoing traffic on a specific communication
34 -- line. With the DS configuration option you must define some basic
35 -- properties of each data source you want to store in the RRD.
36 --
37 -- /NOTE on COUNTER vs DERIVE/
38 --
39 -- by Don Baarda <don.baarda@baesystems.com>
40 --
41 -- If you cannot tolerate ever mistaking the occasional counter reset
42 -- for a legitimate counter wrap, and would prefer \"Unknowns\" for
43 -- all legitimate counter wraps and resets, always use DERIVE with
44 -- @'dsMin' = 0@. Otherwise, using COUNTER with a suitable max will
45 -- return correct values for all legitimate counter wraps, mark some
46 -- counter resets as \"Unknown\", but can mistake some counter resets
47 -- for a legitimate counter wrap.
48 --
49 -- For a 5 minute step and 32-bit counter, the probability of
50 -- mistaking a counter reset for a legitimate wrap is arguably about
51 -- 0.8% per 1Mbps of maximum bandwidth. Note that this equates to 80%
52 -- for 100Mbps interfaces, so for high bandwidth interfaces and a
53 -- 32bit counter, DERIVE with @'dsMin' = 0@ is probably preferable. If
54 -- you are using a 64bit counter, just about any max setting will
55 -- eliminate the possibility of mistaking a reset for a counter wrap.
56 data DataSource
57     = -- |GAUGE is for things like temperatures or number of people in
58       -- a room or the value of a RedHat share.
59     GAUGE {
60         -- |The name you will use to reference this particular data
61         -- source from an RRD. A ds-name must be 1 to 19 characters
62         -- long in the characters @[a-zA-Z0-9_]@.
63         dsName :: !String
64         -- |Defines the maximum number of seconds that may
65         -- pass between two updates of this data source before the
66         -- value of the data source is assumed to be @*UNKNOWN*@.
67       , dsHeartbeat :: !NominalDiffTime
68         -- |'dsMin' and 'dsMax' Define the expected range values for
69         -- data supplied by a data source. If 'dsMin' and\/or 'dsMax'
70         -- any value outside the defined range will be regarded as
71         -- @*UNKNOWN*@. If you do not know or care about 'dsMin' and
72         -- 'dsMax', set them to 'Nothing' for unknown. Note that
73         -- 'dsMin' and 'dsMax' always refer to the processed values of
74         -- the DS. For a traffic-'COUNTER' type DS this would be the
75         -- maximum and minimum data-rate expected from the device.
76         --
77         -- If information on minimal\/maximal expected values is
78         -- available, always set the min and\/or max properties. This
79         -- will help RRDtool in doing a simple sanity check on the
80         -- data supplied when running update.
81       , dsMin :: !(Maybe Double)
82         -- |See 'dsMin'.
83       , dsMax :: !(Maybe Double)
84     }
85     -- |COUNTER is for continuous incrementing counters like the
86     -- ifInOctets counter in a router. The COUNTER data source assumes
87     -- that the counter never decreases, except when a counter
88     -- overflows. The update function takes the overflow into
89     -- account. The counter is stored as a per-second rate. When the
90     -- counter overflows, RRDtool checks if the overflow happened at
91     -- the 32bit or 64bit border and acts accordingly by adding an
92     -- appropriate value to the result.
93     | COUNTER {
94         dsName      :: !String
95       , dsHeartbeat :: !NominalDiffTime
96       , dsMin       :: !(Maybe Double)
97       , dsMax       :: !(Maybe Double)
98     }
99     -- |DERIVE will store the derivative of the line going from the
100     -- last to the current value of the data source. This can be
101     -- useful for gauges, for example, to measure the rate of people
102     -- entering or leaving a room. Internally, derive works exactly
103     -- like COUNTER but without overflow checks. So if your counter
104     -- does not reset at 32 or 64 bit you might want to use DERIVE and
105     -- combine it with a 'dsMin' value of 0.
106     | DERIVE {
107         dsName      :: !String
108       , dsHeartbeat :: !NominalDiffTime
109       , dsMin       :: !(Maybe Double)
110       , dsMax       :: !(Maybe Double)
111     }
112     -- |ABSOLUTE is for counters which get reset upon reading. This is
113     -- used for fast counters which tend to overflow. So instead of
114     -- reading them normally you reset them after every read to make
115     -- sure you have a maximum time available before the next
116     -- overflow. Another usage is for things you count like number of
117     -- messages since the last update.
118     | ABSOLUTE {
119         dsName      :: !String
120       , dsHeartbeat :: !NominalDiffTime
121       , dsMin       :: !(Maybe Double)
122       , dsMax       :: !(Maybe Double)
123     }
124     -- |COMPUTE is for storing the result of a formula applied to
125     -- other data sources in the RRD. This data source is not supplied
126     -- a value on update, but rather its Primary Data Points (PDPs)
127     -- are computed from the PDPs of the data sources according to the
128     -- rpn-expression that defines the formula. Consolidation
129     -- functions are then applied normally to the PDPs of the COMPUTE
130     -- data source (that is the rpn-expression is only applied to
131     -- generate PDPs). In database software, such data sets are
132     -- referred to as \"virtual\" or \"computed\" columns.
133     --
134     -- FIXME: doc links
135     | forall a. CommonExpr a => COMPUTE {
136         dsName :: !String
137         -- |rpn-expression defines the formula used to compute the
138         -- PDPs of a COMPUTE data source from other data sources in
139         -- the same \<RRD\>. It is similar to defining a CDEF argument
140         -- for the graph command.  For COMPUTE data sources, the
141         -- following RPN operations are not supported: COUNT, PREV,
142         -- TIME, and LTIME. In addition, in defining the RPN
143         -- expression, the COMPUTE data source may only refer to the
144         -- names of data source listed previously in the create
145         -- command. This is similar to the restriction that CDEFs must
146         -- refer only to DEFs and CDEFs previously defined in the same
147         -- graph command.
148         -- 
149         -- FIXME: doc links
150       , dsExpr :: !a
151     }
152
153 dsTest :: DataSource
154 dsTest = COMPUTE {
155            dsName = "foo"
156 --         , dsExpr = Previous :<: Const 100
157 --         , dsExpr = Var "foo" :<: Const 100
158            , dsExpr = Average (Const 100 .*. Const 200 .*. HNil)
159          }
160
161 class (Show e, Eq e) => Expr e
162 class Expr e => CommonExpr e
163 class Expr e => IterativeExpr e
164 class Expr e => AggregativeExpr e
165 instance CommonExpr e => IterativeExpr e
166 instance CommonExpr e => AggregativeExpr 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     = Average !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 -- Iterative special values
271 data IterativeValue
272     = Previous
273     deriving (Show, Eq, Ord)
274 instance Expr IterativeValue
275 instance IterativeExpr IterativeValue
276
277 -- Aggregative operators
278 data AggregativeUnaryOp a
279     = Maximum !a
280     deriving (Show, Eq, Ord)
281 instance Expr a => Expr (AggregativeUnaryOp a)
282 instance AggregativeExpr a => AggregativeExpr (AggregativeUnaryOp a)
283
284 -- |The 'createRRD' function lets you set up new Round Robin Database
285 -- (RRD) files. The file is created at its final, full size and filled
286 -- with @*UNKNOWN*@ data.
287 createRRD
288     :: FilePath -- ^The name of the RRD you want to create. RRD files
289                 -- should end with the extension @.rrd@. However,
290                 -- RRDtool will accept any filename.
291     -> Bool -- ^Do not clobber an existing file of the same name.
292     -> Maybe POSIXTime -- ^Specifies the time in seconds since
293                        -- @1970-01-01 UTC@ when the first value should
294                        -- be added to the RRD. RRDtool will not accept
295                        -- any data timed before or at the time
296                        -- specified. (default: @now - 10s@)
297     -> Maybe NominalDiffTime -- ^Specifies the base interval in
298                              -- seconds with which data will be fed
299                              -- into the RRD. (default: 300 sec)
300     -> [DataSource] -- ^Data sources to accept input from.
301     -> IO ()
302 createRRD = error "FIXME"