]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool.hs
major refactoring
[hs-rrdtool.git] / Database / RRDtool.hs
index 6e7b3321503ed72491397bed7b7df21ae75a1e9d..df0fc4863efc084a34695bf3c8e10d44926a1eeb 100644 (file)
@@ -1,6 +1,9 @@
 module Database.RRDtool
     ( DataSource(..)
 
+    , MentionedVars(..)
+    , ApplyMentionedVarsOf(..)
+
     , Expr
     , CommonExpr
     , IterativeExpr
@@ -10,14 +13,19 @@ module Database.RRDtool
     , CommonExprSet
 
     , Constant(..)
+    , VarName(..)
     , Variable(..)
+    , VariableSet
     , CommonUnaryOp(..)
     , CommonBinaryOp(..)
     , CommonTrinaryOp(..)
     , CommonSetOp(..)
+    , TrendOp(..)
     , VariableShiftPredictOp(..)
     , FixedShiftPredictOp(..)
+    , CommonValue(..)
     , IterativeValue(..)
+    , IterativeValueOf(..)
     , AggregativeUnaryOp(..)
 
     , createRRD
@@ -155,24 +163,35 @@ dsTest = COMPUTE {
            dsName = "foo"
 --         , dsExpr = Previous :<: Const 100
 --         , dsExpr = Var "foo" :<: Const 100
-           , dsExpr = Average (Const 100 .*. Const 200 .*. HNil)
+           , 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
-instance CommonExpr e => AggregativeExpr e
 
 class (Show es, Eq es, HList es) => ExprSet es
 instance ExprSet HNil
-instance (Expr e, ExprSet es) => ExprSet (HCons e es)
+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 (HCons e es)
+instance (CommonExpr e, CommonExprSet es) => CommonExprSet (e :*: es)
 
 
 -- Constants and variable names
@@ -181,12 +200,24 @@ data Constant
     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
-    = Var !String
+data Variable vn
+    = Variable !vn
     deriving (Show, Eq, Ord)
-instance Expr Variable
-instance CommonExpr Variable
+
+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
@@ -203,11 +234,11 @@ data CommonUnaryOp a
     | Deg2Rad    !a
     | Rad2Deg    !a
     | Abs        !a
-    | Trend      !Variable !a
-    | TrendNan   !Variable !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
@@ -226,60 +257,159 @@ data CommonBinaryOp 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 (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
-    = Average !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)
 
-data VariableShiftPredictOp ss w
-    = VariableShiftPredictAverage !ss !w !Variable
-    | VariableShiftPredictSigma   !ss !w !Variable
+-- FixedShiftPredictOp
+data FixedShiftPredictOp sm w vn
+    = FixedShiftPredictAverage !sm !w !(Variable vn)
+    | FixedShiftPredictSigma   !sm !w !(Variable vn)
     deriving (Show, Eq, Ord)
-instance (ExprSet ss, Expr w)
-    => Expr (VariableShiftPredictOp ss w)
-instance (CommonExprSet ss, CommonExpr w)
-    => CommonExpr (VariableShiftPredictOp ss w)
-
-data FixedShiftPredictOp sm w
-    = FixedShiftPredictAverage !sm !w !Variable
-    | FixedShiftPredictSigma   !sm !w !Variable
+
+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 sm, Expr w)
-    => Expr (FixedShiftPredictOp sm w)
-instance (CommonExpr sm, CommonExpr w)
-    => CommonExpr (FixedShiftPredictOp sm w)
+
+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
 
--- Aggregative operators
-data AggregativeUnaryOp a
-    = Maximum !a
+instance MentionedVars IterativeValue where
+    type MentionedVarsOf IterativeValue = HNil
+
+-- Iterative special values of something
+data IterativeValueOf vn
+    = PreviousOf !(Variable vn)
     deriving (Show, Eq, Ord)
-instance Expr a => Expr (AggregativeUnaryOp a)
-instance AggregativeExpr a => AggregativeExpr (AggregativeUnaryOp a)
+
+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