]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool.hs
major refactoring
[hs-rrdtool.git] / Database / RRDtool.hs
index 34867d0f19372ac2a80ec50a42feb1ae9944c086..df0fc4863efc084a34695bf3c8e10d44926a1eeb 100644 (file)
@@ -2,6 +2,7 @@ module Database.RRDtool
     ( DataSource(..)
 
     , MentionedVars(..)
+    , ApplyMentionedVarsOf(..)
 
     , Expr
     , CommonExpr
@@ -165,9 +166,18 @@ dsTest = COMPUTE {
            , 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
@@ -176,12 +186,12 @@ instance CommonExpr e => IterativeExpr 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
@@ -207,7 +217,7 @@ instance VarName vn => MentionedVars (Variable vn) where
 
 class HList vs => VariableSet vs
 instance VariableSet HNil
-instance (VarName vn, VariableSet vs) => VariableSet (HCons vn vs)
+instance (VarName v, VariableSet vs) => VariableSet (v :*: vs)
 
 -- Common operators
 data CommonUnaryOp a
@@ -254,31 +264,45 @@ instance (Expr a, Expr b) =>
 instance (CommonExpr a, CommonExpr b) =>
     CommonExpr (CommonBinaryOp a b)
 
-instance (VariableSet (MentionedVarsOf a),
-          VariableSet (MentionedVarsOf b),
-          VariableSet (HAppend (MentionedVarsOf a) (MentionedVarsOf b))) =>
+instance VariableSet (MentionedVarsOf a :++: MentionedVarsOf b) =>
     MentionedVars (CommonBinaryOp a b) where
         type MentionedVarsOf (CommonBinaryOp a b)
-            = HAppend (MentionedVarsOf a) (MentionedVarsOf 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
@@ -286,6 +310,8 @@ data TrendOp 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)
@@ -295,16 +321,30 @@ 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
@@ -312,9 +352,14 @@ data CommonValue
     | 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
@@ -322,15 +367,26 @@ data IterativeValue
     | 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
@@ -347,9 +403,14 @@ data AggregativeUnaryOp 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.