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