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