]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool.hs
major refactoring
[hs-rrdtool.git] / Database / RRDtool.hs
index 7ffef4436be2fdbf80134594598e784bba4ec7e6..df0fc4863efc084a34695bf3c8e10d44926a1eeb 100644 (file)
@@ -1,10 +1,38 @@
 module Database.RRDtool
     ( DataSource(..)
-    , Expr(..)
+
+    , MentionedVars(..)
+    , ApplyMentionedVarsOf(..)
+
+    , Expr
+    , CommonExpr
+    , IterativeExpr
+    , AggregativeExpr
+
+    , ExprSet
+    , CommonExprSet
+
+    , Constant(..)
+    , VarName(..)
+    , Variable(..)
+    , VariableSet
+    , CommonUnaryOp(..)
+    , CommonBinaryOp(..)
+    , CommonTrinaryOp(..)
+    , CommonSetOp(..)
+    , TrendOp(..)
+    , VariableShiftPredictOp(..)
+    , FixedShiftPredictOp(..)
+    , CommonValue(..)
+    , IterativeValue(..)
+    , IterativeValueOf(..)
+    , AggregativeUnaryOp(..)
+
     , createRRD
     )
     where
 
+import Data.HList
 import Data.Time.Clock
 import Data.Time.Clock.POSIX
 
@@ -36,7 +64,7 @@ import Data.Time.Clock.POSIX
 data DataSource
     = -- |GAUGE is for things like temperatures or number of people in
       -- a room or the value of a RedHat share.
-      GAUGE {
+    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_]@.
@@ -61,80 +89,328 @@ data DataSource
       , 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 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 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 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
-    | COMPUTE {
+    }
+    -- |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. CommonExpr 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 :: !Expr
-      }
-    deriving (Eq, Ord, Show)
-
-data Expr
-    = UNK
+        -- |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)
+         }
+
+-- MentionedVars
+class VariableSet (MentionedVarsOf a) => MentionedVars a where
+    type MentionedVarsOf a
+
+-- ApplyMentionedVarsOf
+data ApplyMentionedVarsOf = ApplyMentionedVarsOf
+
+instance Applyable ApplyMentionedVarsOf a where
+    type Apply ApplyMentionedVarsOf a = MentionedVarsOf a
+    apply = undefined
+
+-- Expr
+class (Show e, Eq e) => Expr e
+class Expr e => CommonExpr e
+class Expr e => IterativeExpr e
+class Expr e => AggregativeExpr e
+instance CommonExpr e => IterativeExpr e
+
+class (Show es, Eq es, HList es) => ExprSet es
+instance ExprSet HNil
+instance (Expr e, ExprSet es) => ExprSet (e :*: es)
+
+class (Show es, Eq es, HList es) => CommonExprSet es
+instance CommonExprSet es => ExprSet es
+instance CommonExprSet HNil
+instance (CommonExpr e, CommonExprSet es) => CommonExprSet (e :*: es)
+
+
+-- Constants and variable names
+data Constant
+    = Const !Double
+    deriving (Show, Eq, Ord)
+instance Expr Constant
+instance CommonExpr Constant
+instance MentionedVars Constant where
+    type MentionedVarsOf Constant = HNil
+
+class (Show a, Eq a, Ord a) => VarName a where
+    varName :: a -> String
+
+data Variable vn
+    = Variable !vn
+    deriving (Show, Eq, Ord)
+
+instance VarName vn => Expr (Variable vn)
+instance VarName vn => CommonExpr (Variable vn)
+instance VarName vn => MentionedVars (Variable vn) where
+    type MentionedVarsOf (Variable vn) = vn :*: HNil
+
+class HList vs => VariableSet vs
+instance VariableSet HNil
+instance (VarName v, VariableSet vs) => VariableSet (v :*: vs)
+
+-- Common operators
+data CommonUnaryOp a
+    = IsUnknown  !a
+    | IsInfinity !a
+    | Sin        !a
+    | Cos        !a
+    | Log        !a
+    | Exp        !a
+    | Sqrt       !a
+    | Atan       !a
+    | Floor      !a
+    | Ceil       !a
+    | Deg2Rad    !a
+    | Rad2Deg    !a
+    | Abs        !a
+    deriving (Show, Eq, Ord)
+instance Expr a => Expr (CommonUnaryOp a)
+instance CommonExpr a => CommonExpr (CommonUnaryOp a)
+instance VariableSet (MentionedVarsOf a) => MentionedVars (CommonUnaryOp a) where
+    type MentionedVarsOf (CommonUnaryOp a) = MentionedVarsOf a
+
+data CommonBinaryOp a b
+    = !a :<:  !b
+    | !a :<=: !b
+    | !a :>:  !b
+    | !a :>=: !b
+    | !a :==: !b
+    | !a :/=: !b
+    | Min !a !b
+    | Max !a !b
+    | !a :+: !b
+    | !a :-: !b
+    | !a :*: !b
+    | !a :/: !b
+    | !a :%: !b
+    | AddNaN !a !b
+    | AtanXY !a !b
+    deriving (Show, Eq, Ord)
+
+instance (Expr a, Expr b) =>
+    Expr (CommonBinaryOp a b)
+
+instance (CommonExpr a, CommonExpr b) =>
+    CommonExpr (CommonBinaryOp a b)
+
+instance VariableSet (MentionedVarsOf a :++: MentionedVarsOf b) =>
+    MentionedVars (CommonBinaryOp a b) where
+        type MentionedVarsOf (CommonBinaryOp a b)
+            = MentionedVarsOf a :++: MentionedVarsOf b
+        
+
+data CommonTrinaryOp a b c
+    = If !a !b !c
+    | Limit !a !b !c
+    deriving (Show, Eq, Ord)
+
+instance (Expr a, Expr b, Expr c)
+    => Expr (CommonTrinaryOp a b c)
+
+instance (CommonExpr a, CommonExpr b, CommonExpr c)
+    => CommonExpr (CommonTrinaryOp a b c)
+
+instance VariableSet (MentionedVarsOf a :++:
+                      MentionedVarsOf b :++:
+                      MentionedVarsOf c) =>
+    MentionedVars (CommonTrinaryOp a b c) where
+        type MentionedVarsOf (CommonTrinaryOp a b c)
+            = MentionedVarsOf a :++:
+              MentionedVarsOf b :++:
+              MentionedVarsOf c
+
+-- SORT and REV can't be expressed in this way as they pushes possibly
+-- multiple values onto the stack...
+
+data CommonSetOp es
+    = AverageOf !es
+    deriving (Show, Eq, Ord)
+
+instance ExprSet es => Expr (CommonSetOp es)
+instance CommonExprSet es => CommonExpr (CommonSetOp es)
+instance VariableSet (HConcat (HMap ApplyMentionedVarsOf es)) =>
+    MentionedVars (CommonSetOp es) where
+        type MentionedVarsOf (CommonSetOp es)
+            = HConcat (HMap ApplyMentionedVarsOf es)
+
+data TrendOp vn a
+    = Trend      !(Variable vn) !a
+    | TrendNan   !(Variable vn) !a
+    deriving (Show, Eq, Ord)
+instance (VarName vn, Expr a) => Expr (TrendOp vn a)
+instance (VarName vn, CommonExpr a) => CommonExpr (TrendOp vn a)
+instance (VarName vn, MentionedVars a) => MentionedVars (TrendOp vn a) where
+    type MentionedVarsOf (TrendOp vn a) = vn :*: MentionedVarsOf a
+
+data VariableShiftPredictOp ss w vn
+    = VariableShiftPredictAverage !ss !w !(Variable vn)
+    | VariableShiftPredictSigma   !ss !w !(Variable vn)
+    deriving (Show, Eq, Ord)
+instance (ExprSet ss, Expr w, VarName vn)
+    => Expr (VariableShiftPredictOp ss w vn)
+instance (CommonExprSet ss, CommonExpr w, VarName vn)
+    => CommonExpr (VariableShiftPredictOp ss w vn)
+instance ( VarName vn
+         , VariableSet (MentionedVarsOf ss :++: MentionedVarsOf w)
+         ) => MentionedVars (VariableShiftPredictOp ss w vn) where
+    type MentionedVarsOf (VariableShiftPredictOp ss w vn)
+        = vn :*: (MentionedVarsOf ss :++: MentionedVarsOf w)
+
+-- FixedShiftPredictOp
+data FixedShiftPredictOp sm w vn
+    = FixedShiftPredictAverage !sm !w !(Variable vn)
+    | FixedShiftPredictSigma   !sm !w !(Variable vn)
+    deriving (Show, Eq, Ord)
+
+instance (Expr sm, Expr w, VarName vn)
+    => Expr (FixedShiftPredictOp sm w vn)
+
+instance (CommonExpr sm, CommonExpr w, VarName vn)
+    => CommonExpr (FixedShiftPredictOp sm w vn)
+
+instance ( VarName vn
+         , VariableSet (MentionedVarsOf sm :++: MentionedVarsOf w)
+         ) => MentionedVars (FixedShiftPredictOp sm w vn) where
+    type MentionedVarsOf (FixedShiftPredictOp sm w vn)
+        = vn :*: (MentionedVarsOf sm :++: MentionedVarsOf w)
+
+-- Common special values
+data CommonValue
+    = Unknown
+    | Infinity
+    | NegativeInfinity
+    | Now
+    deriving (Show, Eq, Ord)
+
+instance Expr CommonValue
+
+instance CommonExpr CommonValue
+
+instance MentionedVars CommonValue where
+    type MentionedVarsOf CommonValue = HNil
+
+-- Iterative special values
+data IterativeValue
+    = Previous
+    | Count
+    | TakenTime
+    | TakenLocalTime
+    deriving (Show, Eq, Ord)
+
+instance Expr IterativeValue
+
+instance IterativeExpr IterativeValue
+
+instance MentionedVars IterativeValue where
+    type MentionedVarsOf IterativeValue = HNil
+
+-- Iterative special values of something
+data IterativeValueOf vn
+    = PreviousOf !(Variable vn)
     deriving (Show, Eq, Ord)
 
+instance VarName vn => Expr (IterativeValueOf vn)
+
+instance VarName vn => IterativeExpr (IterativeValueOf vn)
+
+instance VarName vn => MentionedVars (IterativeValueOf vn) where
+    type MentionedVarsOf (IterativeValueOf vn) = vn :*: HNil
+
+-- Aggregative operators (fairly restricted due to rrdtool's
+-- restriction)
+data AggregativeUnaryOp vn
+    = Maximum    !(Variable vn)
+    | Minimum    !(Variable vn)
+    | Average    !(Variable vn)
+    | StandardDeviation !(Variable vn)
+    | First      !(Variable vn)
+    | Last       !(Variable vn)
+    | Total      !(Variable vn)
+    | Percent    !(Variable vn) !Constant
+    | PercentNan !(Variable vn) !Constant
+    | LSLSlope   !(Variable vn)
+    | LSLInt     !(Variable vn)
+    | LSLCorrel  !(Variable vn)
+    deriving (Show, Eq, Ord)
+
+instance VarName vn => Expr (AggregativeUnaryOp vn)
+
+instance VarName vn => AggregativeExpr (AggregativeUnaryOp vn)
+
+instance VarName vn => MentionedVars (AggregativeUnaryOp vn) where
+    type MentionedVarsOf (AggregativeUnaryOp vn) = vn :*: 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.