-- 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 {
+data DataSource where
+ -- |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_]@.
, 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 {
+ } -> DataSource
+ -- |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 {
+ } -> DataSource
+ -- |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 {
+ } -> DataSource
+ -- |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 {
+ } -> DataSource
+ -- |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 :: CommonExpr a => {
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)
+ -- |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
+ } -> DataSource
-data Expr
- = UNK
- deriving (Show, Eq, Ord)
+dsTest :: DataSource
+dsTest = COMPUTE {
+ dsName = "foo"
+ , dsExpr = Var "foo" :<: Const 100
+-- , dsExpr = Previous
+ }
+
+{-
+data Value
+data Expr r where
+ (:<: ) :: Expr Value -> Expr Value -> Expr Bool
+ (:<=:) :: Expr Value -> Expr Value -> Expr Bool
+ (:>: ) :: Expr Value -> Expr Value -> Expr Bool
+ (:>=:) :: Expr Value -> Expr Value -> Expr Bool
+ (:==:) :: Expr Value -> Expr Value -> Expr Bool
+ (:/=:) :: Expr Value -> Expr Value -> Expr Bool
+ IsUnknown :: Expr Value -> Expr Bool
+ IsInfinity :: Expr Value -> Expr Bool
+ If :: Expr Bool -> Expr a -> Expr a -> Expr a
+ Min :: Expr Value -> Expr Value -> Expr Value
+ Max :: Expr Value -> Expr Value -> Expr Value
+-}
+class Expr a
+class Expr a => CommonExpr a
+class Expr a => IterativeExpr a
+class Expr a => AggregativeExpr a
+instance CommonExpr a => IterativeExpr a
+instance CommonExpr a => AggregativeExpr a
+
+-- Constants and variable names
+data Constant where
+ Const :: !Double -> Constant
+ Var :: !String -> Constant
+instance Expr Constant
+instance CommonExpr Constant
+
+-- Common operators
+data CommonBinaryOp a b where
+ (:<: ) :: !a -> !b -> CommonBinaryOp a b
+ (:<=:) :: !a -> !b -> CommonBinaryOp a b
+instance (Expr a, Expr b) => Expr (CommonBinaryOp a b)
+instance (CommonExpr a, CommonExpr b) => CommonExpr (CommonBinaryOp a b)
+
+-- Iterative special values
+data IterativeValue where
+ Previous :: IterativeValue
+instance Expr IterativeValue
+instance IterativeExpr IterativeValue
+
+-- Aggregative operators
+data AggregativeUnaryOp a where
+ Maximum :: !a -> AggregativeUnaryOp a
+instance Expr a => Expr (AggregativeUnaryOp a)
+instance AggregativeExpr a => AggregativeExpr (AggregativeUnaryOp a)
-- |The 'createRRD' function lets you set up new Round Robin Database
-- (RRD) files. The file is created at its final, full size and filled