module Database.RRDtool
- ( DataSource(..)
-
- , MentionedVars(..)
- , ApplyMentionedVarsOf(..)
-
- , IsExpr
- , IsCommonExpr
- , IterativeExpr
- , IsAggregativeExpr
-
- , IsExprSet
- , IsCommonExprSet
-
- , Constant(..)
- , IsVarName(..)
- , Variable(..)
- , IsVariableSet
- , CommonUnaryOp(..)
- , CommonBinaryOp(..)
- , CommonTrinaryOp(..)
- , CommonSetOp(..)
- , TrendOp(..)
- , VariableShiftPredictOp(..)
- , FixedShiftPredictOp(..)
- , CommonValue(..)
- , IterativeValue(..)
- , IterativeValueOf(..)
- , AggregativeUnaryOp(..)
-
- , createRRD
+ ( module Database.RRDtool.Create
)
where
-import Data.HList
-import Data.Time.Clock
-import Data.Time.Clock.POSIX
-
-
--- |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)
- }
-
--- MentionedVars
-class IsVariableSet (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
-
--- IsExpr
-class (Show e, Eq e) => IsExpr e
-class IsExpr e => IsCommonExpr e
-class IsExpr e => IterativeExpr e
-class IsExpr e => IsAggregativeExpr e
-
-class (Show es, Eq es, HList es) => IsExprSet es
-instance IsExprSet HNil
-instance (IsExpr e, IsExprSet es) => IsExprSet (e :*: es)
-
-class (Show es, Eq es, HList es) => IsCommonExprSet es
-instance IsCommonExprSet HNil
-instance (IsCommonExpr e, IsCommonExprSet es) => IsCommonExprSet (e :*: es)
-
-
--- Constants and variable names
-data Constant
- = Const !Double
- deriving (Show, Eq, Ord)
-instance IsExpr Constant
-instance IsCommonExpr Constant
-instance MentionedVars Constant where
- type MentionedVarsOf Constant = HNil
-
-class (Show a, Eq a, Ord a) => IsVarName a where
- varName :: a -> String
-
-data Variable vn
- = Variable !vn
- deriving (Show, Eq, Ord)
-
-instance IsVarName vn => IsExpr (Variable vn)
-instance IsVarName vn => IsCommonExpr (Variable vn)
-instance IsVarName vn => MentionedVars (Variable vn) where
- type MentionedVarsOf (Variable vn) = vn :*: HNil
-
-class HList vs => IsVariableSet vs
-instance IsVariableSet HNil
-instance (IsVarName v, IsVariableSet vs) => IsVariableSet (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 IsExpr a => IsExpr (CommonUnaryOp a)
-instance IsCommonExpr a => IsCommonExpr (CommonUnaryOp a)
-instance IsVariableSet (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 (IsExpr a, IsExpr b) =>
- IsExpr (CommonBinaryOp a b)
-
-instance (IsCommonExpr a, IsCommonExpr b) =>
- IsCommonExpr (CommonBinaryOp a b)
-
-instance IsVariableSet (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 (IsExpr a, IsExpr b, IsExpr c)
- => IsExpr (CommonTrinaryOp a b c)
-
-instance (IsCommonExpr a, IsCommonExpr b, IsCommonExpr c)
- => IsCommonExpr (CommonTrinaryOp a b c)
-
-instance IsVariableSet (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 IsExprSet es => IsExpr (CommonSetOp es)
-instance (IsExprSet es, IsCommonExprSet es) => IsCommonExpr (CommonSetOp es)
-instance IsVariableSet (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 (IsVarName vn, IsExpr a) => IsExpr (TrendOp vn a)
-instance (IsVarName vn, IsCommonExpr a) => IsCommonExpr (TrendOp vn a)
-instance (IsVarName 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 (IsExprSet ss, IsExpr w, IsVarName vn)
- => IsExpr (VariableShiftPredictOp ss w vn)
-instance (IsExprSet ss, IsCommonExprSet ss, IsCommonExpr w, IsVarName vn)
- => IsCommonExpr (VariableShiftPredictOp ss w vn)
-instance ( IsVarName vn
- , IsVariableSet (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 (IsExpr sm, IsExpr w, IsVarName vn)
- => IsExpr (FixedShiftPredictOp sm w vn)
-
-instance (IsCommonExpr sm, IsCommonExpr w, IsVarName vn)
- => IsCommonExpr (FixedShiftPredictOp sm w vn)
-
-instance ( IsVarName vn
- , IsVariableSet (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 IsExpr CommonValue
-
-instance IsCommonExpr CommonValue
-
-instance MentionedVars CommonValue where
- type MentionedVarsOf CommonValue = HNil
-
--- Iterative special values
-data IterativeValue
- = Previous
- | Count
- | TakenTime
- | TakenLocalTime
- deriving (Show, Eq, Ord)
-
-instance IsExpr 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 IsVarName vn => IsExpr (IterativeValueOf vn)
-
-instance IsVarName vn => IterativeExpr (IterativeValueOf vn)
-
-instance IsVarName 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 IsVarName vn => IsExpr (AggregativeUnaryOp vn)
-
-instance IsVarName vn => IsAggregativeExpr (AggregativeUnaryOp vn)
-
-instance IsVarName 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.
-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"
\ No newline at end of file
+import Database.RRDtool.Create
--- /dev/null
+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"
--- /dev/null
+module Database.RRDtool.Expression
+ ( MentionedVars(..)
+ , ApplyMentionedVarsOf(..)
+
+ , IsExpr
+ , IsCommonExpr
+ , IterativeExpr
+ , IsAggregativeExpr
+
+ , IsExprSet
+ , IsCommonExprSet
+
+ , Constant(..)
+ , IsVarName(..)
+ , Variable(..)
+ , IsVariableSet
+ , CommonUnaryOp(..)
+ , CommonBinaryOp(..)
+ , CommonTrinaryOp(..)
+ , CommonSetOp(..)
+ , TrendOp(..)
+ , VariableShiftPredictOp(..)
+ , FixedShiftPredictOp(..)
+ , CommonValue(..)
+ , IterativeValue(..)
+ , IterativeValueOf(..)
+ , AggregativeUnaryOp(..)
+ )
+ where
+
+import Data.HList
+
+
+-- MentionedVars
+class IsVariableSet (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
+
+-- IsExpr
+class (Show e, Eq e) => IsExpr e
+class IsExpr e => IsCommonExpr e
+class IsExpr e => IterativeExpr e
+class IsExpr e => IsAggregativeExpr e
+
+class (Show es, Eq es, HList es) => IsExprSet es
+instance IsExprSet HNil
+instance (IsExpr e, IsExprSet es) => IsExprSet (e :*: es)
+
+class (Show es, Eq es, HList es) => IsCommonExprSet es
+instance IsCommonExprSet HNil
+instance (IsCommonExpr e, IsCommonExprSet es) => IsCommonExprSet (e :*: es)
+
+
+-- Constants and variable names
+data Constant
+ = Const !Double
+ deriving (Show, Eq, Ord)
+instance IsExpr Constant
+instance IsCommonExpr Constant
+instance MentionedVars Constant where
+ type MentionedVarsOf Constant = HNil
+
+class (Show a, Eq a, Ord a) => IsVarName a where
+ varName :: a -> String
+
+data Variable vn
+ = Variable !vn
+ deriving (Show, Eq, Ord)
+
+instance IsVarName vn => IsExpr (Variable vn)
+instance IsVarName vn => IsCommonExpr (Variable vn)
+instance IsVarName vn => MentionedVars (Variable vn) where
+ type MentionedVarsOf (Variable vn) = vn :*: HNil
+
+class HList vs => IsVariableSet vs
+instance IsVariableSet HNil
+instance (IsVarName v, IsVariableSet vs) => IsVariableSet (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 IsExpr a => IsExpr (CommonUnaryOp a)
+instance IsCommonExpr a => IsCommonExpr (CommonUnaryOp a)
+instance IsVariableSet (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 (IsExpr a, IsExpr b) =>
+ IsExpr (CommonBinaryOp a b)
+
+instance (IsCommonExpr a, IsCommonExpr b) =>
+ IsCommonExpr (CommonBinaryOp a b)
+
+instance IsVariableSet (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 (IsExpr a, IsExpr b, IsExpr c)
+ => IsExpr (CommonTrinaryOp a b c)
+
+instance (IsCommonExpr a, IsCommonExpr b, IsCommonExpr c)
+ => IsCommonExpr (CommonTrinaryOp a b c)
+
+instance IsVariableSet (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 IsExprSet es => IsExpr (CommonSetOp es)
+instance (IsExprSet es, IsCommonExprSet es) => IsCommonExpr (CommonSetOp es)
+instance IsVariableSet (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 (IsVarName vn, IsExpr a) => IsExpr (TrendOp vn a)
+instance (IsVarName vn, IsCommonExpr a) => IsCommonExpr (TrendOp vn a)
+instance (IsVarName 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 (IsExprSet ss, IsExpr w, IsVarName vn)
+ => IsExpr (VariableShiftPredictOp ss w vn)
+instance (IsExprSet ss, IsCommonExprSet ss, IsCommonExpr w, IsVarName vn)
+ => IsCommonExpr (VariableShiftPredictOp ss w vn)
+instance ( IsVarName vn
+ , IsVariableSet (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 (IsExpr sm, IsExpr w, IsVarName vn)
+ => IsExpr (FixedShiftPredictOp sm w vn)
+
+instance (IsCommonExpr sm, IsCommonExpr w, IsVarName vn)
+ => IsCommonExpr (FixedShiftPredictOp sm w vn)
+
+instance ( IsVarName vn
+ , IsVariableSet (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 IsExpr CommonValue
+
+instance IsCommonExpr CommonValue
+
+instance MentionedVars CommonValue where
+ type MentionedVarsOf CommonValue = HNil
+
+-- Iterative special values
+data IterativeValue
+ = Previous
+ | Count
+ | TakenTime
+ | TakenLocalTime
+ deriving (Show, Eq, Ord)
+
+instance IsExpr 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 IsVarName vn => IsExpr (IterativeValueOf vn)
+
+instance IsVarName vn => IterativeExpr (IterativeValueOf vn)
+
+instance IsVarName 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 IsVarName vn => IsExpr (AggregativeUnaryOp vn)
+
+instance IsVarName vn => IsAggregativeExpr (AggregativeUnaryOp vn)
+
+instance IsVarName vn => MentionedVars (AggregativeUnaryOp vn) where
+ type MentionedVarsOf (AggregativeUnaryOp vn) = vn :*: HNil
bindings-librrd == 0.1.*,
time == 1.1.*
+ Exposed-Modules:
+ Database.RRDtool
+ Database.RRDtool.Create
+ Database.RRDtool.Expression
+ Data.HList
+
Extensions:
DeriveDataTypeable
EmptyDataDecls
TypeOperators
UndecidableInstances
- Exposed-Modules:
- Database.RRDtool
- Data.HList
-
GHC-Options:
-Wall
\ No newline at end of file