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