]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool.hs
major rename of classes
[hs-rrdtool.git] / Database / RRDtool.hs
index 34867d0f19372ac2a80ec50a42feb1ae9944c086..6b5734076a4ab446f02aba82e11438fa648e3dd3 100644 (file)
@@ -2,19 +2,20 @@ module Database.RRDtool
     ( DataSource(..)
 
     , MentionedVars(..)
+    , ApplyMentionedVarsOf(..)
 
-    , Expr
-    , CommonExpr
+    , IsExpr
+    , IsCommonExpr
     , IterativeExpr
-    , AggregativeExpr
+    , IsAggregativeExpr
 
-    , ExprSet
-    , CommonExprSet
+    , IsExprSet
+    , IsCommonExprSet
 
     , Constant(..)
-    , VarName(..)
+    , IsVarName(..)
     , Variable(..)
-    , VariableSet
+    , IsVariableSet
     , CommonUnaryOp(..)
     , CommonBinaryOp(..)
     , CommonTrinaryOp(..)
@@ -139,7 +140,7 @@ data DataSource
     -- referred to as \"virtual\" or \"computed\" columns.
     --
     -- FIXME: doc links
-    | forall a. CommonExpr a => COMPUTE {
+    | 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
@@ -165,49 +166,56 @@ dsTest = COMPUTE {
            , dsExpr = AverageOf (Const 100 .*. Const 200 .*. HNil)
          }
 
-class VariableSet (MentionedVarsOf a) => MentionedVars a where
+-- MentionedVars
+class IsVariableSet (MentionedVarsOf a) => MentionedVars a where
     type MentionedVarsOf a
 
-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
+-- ApplyMentionedVarsOf
+data ApplyMentionedVarsOf = ApplyMentionedVarsOf
 
-class (Show es, Eq es, HList es) => ExprSet es
-instance ExprSet HNil
-instance (Expr e, ExprSet es) => ExprSet (HCons e es)
+instance Applyable ApplyMentionedVarsOf a where
+    type Apply ApplyMentionedVarsOf a = MentionedVarsOf a
+    apply = undefined
 
-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)
+-- 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 Expr Constant
-instance CommonExpr Constant
+instance IsExpr Constant
+instance IsCommonExpr Constant
 instance MentionedVars Constant where
     type MentionedVarsOf Constant = HNil
 
-class (Show a, Eq a, Ord a) => VarName a where
+class (Show a, Eq a, Ord a) => IsVarName 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
+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 => VariableSet vs
-instance VariableSet HNil
-instance (VarName vn, VariableSet vs) => VariableSet (HCons vn vs)
+class HList vs => IsVariableSet vs
+instance IsVariableSet HNil
+instance (IsVarName v, IsVariableSet vs) => IsVariableSet (v :*: vs)
 
 -- Common operators
 data CommonUnaryOp a
@@ -225,9 +233,9 @@ data CommonUnaryOp 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
+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
@@ -248,28 +256,37 @@ data CommonBinaryOp a b
     | AtanXY !a !b
     deriving (Show, Eq, Ord)
 
-instance (Expr a, Expr b) =>
-    Expr (CommonBinaryOp a b)
+instance (IsExpr a, IsExpr b) =>
+    IsExpr (CommonBinaryOp a b)
 
-instance (CommonExpr a, CommonExpr b) =>
-    CommonExpr (CommonBinaryOp a b)
+instance (IsCommonExpr a, IsCommonExpr b) =>
+    IsCommonExpr (CommonBinaryOp a b)
 
-instance (VariableSet (MentionedVarsOf a),
-          VariableSet (MentionedVarsOf b),
-          VariableSet (HAppend (MentionedVarsOf a) (MentionedVarsOf b))) =>
+instance IsVariableSet (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 (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...
@@ -277,33 +294,54 @@ instance (CommonExpr a, CommonExpr b, CommonExpr c)
 data CommonSetOp es
     = AverageOf !es
     deriving (Show, Eq, Ord)
-instance ExprSet es => Expr (CommonSetOp es)
-instance CommonExprSet es => CommonExpr (CommonSetOp es)
+
+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 (VarName vn, Expr a) => Expr (TrendOp vn a)
-instance (VarName vn, CommonExpr a) => CommonExpr (TrendOp vn a)
+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 (ExprSet ss, Expr w, VarName vn)
-    => Expr (VariableShiftPredictOp ss w vn)
-instance (CommonExprSet ss, CommonExpr w, VarName vn)
-    => CommonExpr (VariableShiftPredictOp ss w vn)
-
+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 (Expr sm, Expr w, VarName vn)
-    => Expr (FixedShiftPredictOp sm w vn)
-instance (CommonExpr sm, CommonExpr w, VarName vn)
-    => CommonExpr (FixedShiftPredictOp sm w vn)
+
+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
@@ -312,8 +350,13 @@ data CommonValue
     | NegativeInfinity
     | Now
     deriving (Show, Eq, Ord)
-instance Expr CommonValue
-instance CommonExpr CommonValue
+
+instance IsExpr CommonValue
+
+instance IsCommonExpr CommonValue
+
+instance MentionedVars CommonValue where
+    type MentionedVarsOf CommonValue = HNil
 
 -- Iterative special values
 data IterativeValue
@@ -322,14 +365,25 @@ data IterativeValue
     | TakenTime
     | TakenLocalTime
     deriving (Show, Eq, Ord)
-instance Expr IterativeValue
+
+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 VarName vn => Expr (IterativeValueOf vn)
-instance VarName vn => IterativeExpr (IterativeValueOf vn)
+
+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)
@@ -347,8 +401,13 @@ 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 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