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