]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool/Create.hs
module splitting
[hs-rrdtool.git] / Database / RRDtool / Create.hs
diff --git a/Database/RRDtool/Create.hs b/Database/RRDtool/Create.hs
new file mode 100644 (file)
index 0000000..e0146c0
--- /dev/null
@@ -0,0 +1,177 @@
+module Database.RRDtool.Create
+    ( DataSource(..)
+    , createRRD
+
+    -- Data.HList
+    , (.*.)    
+    , HNil(..)
+
+    -- Database.RRDtool.Expression
+    , Constant(..)
+    , IsVarName(..)
+    , Variable(..)
+    , CommonUnaryOp(..)
+    , CommonBinaryOp(..)
+    , CommonTrinaryOp(..)
+    , CommonSetOp(..)
+    , TrendOp(..)
+    , VariableShiftPredictOp(..)
+    , FixedShiftPredictOp(..)
+    , CommonValue(..)
+    )
+    where
+
+import Data.HList
+import Data.Time.Clock
+import Data.Time.Clock.POSIX
+import Database.RRDtool.Expression
+
+
+-- |A single RRD can accept input from several data sources (DS), for
+-- example incoming and outgoing traffic on a specific communication
+-- line. With the DS configuration option you must define some basic
+-- properties of each data source you want to store in the RRD.
+--
+-- /NOTE on COUNTER vs DERIVE/
+--
+-- by Don Baarda <don.baarda@baesystems.com>
+--
+-- If you cannot tolerate ever mistaking the occasional counter reset
+-- for a legitimate counter wrap, and would prefer \"Unknowns\" for
+-- all legitimate counter wraps and resets, always use DERIVE with
+-- @'dsMin' = 0@. Otherwise, using COUNTER with a suitable max will
+-- return correct values for all legitimate counter wraps, mark some
+-- counter resets as \"Unknown\", but can mistake some counter resets
+-- for a legitimate counter wrap.
+--
+-- For a 5 minute step and 32-bit counter, the probability of
+-- mistaking a counter reset for a legitimate wrap is arguably about
+-- 0.8% per 1Mbps of maximum bandwidth. Note that this equates to 80%
+-- for 100Mbps interfaces, so for high bandwidth interfaces and a
+-- 32bit counter, DERIVE with @'dsMin' = 0@ is probably preferable. If
+-- you are using a 64bit counter, just about any max setting will
+-- eliminate the possibility of mistaking a reset for a counter wrap.
+data DataSource
+    = -- |GAUGE is for things like temperatures or number of people in
+      -- a room or the value of a RedHat share.
+    GAUGE {
+        -- |The name you will use to reference this particular data
+        -- source from an RRD. A ds-name must be 1 to 19 characters
+        -- long in the characters @[a-zA-Z0-9_]@.
+        dsName :: !String
+        -- |Defines the maximum number of seconds that may
+        -- pass between two updates of this data source before the
+        -- value of the data source is assumed to be @*UNKNOWN*@.
+      , dsHeartbeat :: !NominalDiffTime
+        -- |'dsMin' and 'dsMax' Define the expected range values for
+        -- data supplied by a data source. If 'dsMin' and\/or 'dsMax'
+        -- any value outside the defined range will be regarded as
+        -- @*UNKNOWN*@. If you do not know or care about 'dsMin' and
+        -- 'dsMax', set them to 'Nothing' for unknown. Note that
+        -- 'dsMin' and 'dsMax' always refer to the processed values of
+        -- the DS. For a traffic-'COUNTER' type DS this would be the
+        -- maximum and minimum data-rate expected from the device.
+        --
+        -- If information on minimal\/maximal expected values is
+        -- available, always set the min and\/or max properties. This
+        -- will help RRDtool in doing a simple sanity check on the
+        -- data supplied when running update.
+      , dsMin :: !(Maybe Double)
+        -- |See 'dsMin'.
+      , dsMax :: !(Maybe Double)
+    }
+    -- |COUNTER is for continuous incrementing counters like the
+    -- ifInOctets counter in a router. The COUNTER data source assumes
+    -- that the counter never decreases, except when a counter
+    -- overflows. The update function takes the overflow into
+    -- account. The counter is stored as a per-second rate. When the
+    -- counter overflows, RRDtool checks if the overflow happened at
+    -- the 32bit or 64bit border and acts accordingly by adding an
+    -- appropriate value to the result.
+    | COUNTER {
+        dsName      :: !String
+      , dsHeartbeat :: !NominalDiffTime
+      , dsMin       :: !(Maybe Double)
+      , dsMax       :: !(Maybe Double)
+    }
+    -- |DERIVE will store the derivative of the line going from the
+    -- last to the current value of the data source. This can be
+    -- useful for gauges, for example, to measure the rate of people
+    -- entering or leaving a room. Internally, derive works exactly
+    -- like COUNTER but without overflow checks. So if your counter
+    -- does not reset at 32 or 64 bit you might want to use DERIVE and
+    -- combine it with a 'dsMin' value of 0.
+    | DERIVE {
+        dsName      :: !String
+      , dsHeartbeat :: !NominalDiffTime
+      , dsMin       :: !(Maybe Double)
+      , dsMax       :: !(Maybe Double)
+    }
+    -- |ABSOLUTE is for counters which get reset upon reading. This is
+    -- used for fast counters which tend to overflow. So instead of
+    -- reading them normally you reset them after every read to make
+    -- sure you have a maximum time available before the next
+    -- overflow. Another usage is for things you count like number of
+    -- messages since the last update.
+    | ABSOLUTE {
+        dsName      :: !String
+      , dsHeartbeat :: !NominalDiffTime
+      , dsMin       :: !(Maybe Double)
+      , dsMax       :: !(Maybe Double)
+    }
+    -- |COMPUTE is for storing the result of a formula applied to
+    -- other data sources in the RRD. This data source is not supplied
+    -- a value on update, but rather its Primary Data Points (PDPs)
+    -- are computed from the PDPs of the data sources according to the
+    -- rpn-expression that defines the formula. Consolidation
+    -- functions are then applied normally to the PDPs of the COMPUTE
+    -- data source (that is the rpn-expression is only applied to
+    -- generate PDPs). In database software, such data sets are
+    -- referred to as \"virtual\" or \"computed\" columns.
+    --
+    -- FIXME: doc links
+    | forall a. IsCommonExpr a => COMPUTE {
+        dsName :: !String
+        -- |rpn-expression defines the formula used to compute the
+        -- PDPs of a COMPUTE data source from other data sources in
+        -- the same \<RRD\>. It is similar to defining a CDEF argument
+        -- for the graph command.  For COMPUTE data sources, the
+        -- following RPN operations are not supported: COUNT, PREV,
+        -- TIME, and LTIME. In addition, in defining the RPN
+        -- expression, the COMPUTE data source may only refer to the
+        -- names of data source listed previously in the create
+        -- command. This is similar to the restriction that CDEFs must
+        -- refer only to DEFs and CDEFs previously defined in the same
+        -- graph command.
+        -- 
+        -- FIXME: doc links
+      , dsExpr :: !a
+    }
+
+dsTest :: DataSource
+dsTest = COMPUTE {
+           dsName = "foo"
+--         , dsExpr = Previous :<: Const 100
+--         , dsExpr = Var "foo" :<: Const 100
+           , dsExpr = AverageOf (Const 100 .*. Const 200 .*. HNil)
+         }
+
+-- |The 'createRRD' function lets you set up new Round Robin Database
+-- (RRD) files. The file is created at its final, full size and filled
+-- with @*UNKNOWN*@ data.
+createRRD
+    :: FilePath -- ^The name of the RRD you want to create. RRD files
+                -- should end with the extension @.rrd@. However,
+                -- RRDtool will accept any filename.
+    -> Bool -- ^Do not clobber an existing file of the same name.
+    -> Maybe POSIXTime -- ^Specifies the time in seconds since
+                       -- @1970-01-01 UTC@ when the first value should
+                       -- be added to the RRD. RRDtool will not accept
+                       -- any data timed before or at the time
+                       -- specified. (default: @now - 10s@)
+    -> Maybe NominalDiffTime -- ^Specifies the base interval in
+                             -- seconds with which data will be fed
+                             -- into the RRD. (default: 300 sec)
+    -> [DataSource] -- ^Data sources to accept input from.
+    -> IO ()
+createRRD = error "FIXME"