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