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