]> gitweb @ CieloNegro.org - hs-rrdtool.git/commitdiff
wip
authorPHO <pho@cielonegro.org>
Thu, 22 Apr 2010 09:22:32 +0000 (18:22 +0900)
committerPHO <pho@cielonegro.org>
Thu, 22 Apr 2010 09:22:32 +0000 (18:22 +0900)
Database/RRDtool.hs
rrdtool.cabal

index ca842a42b96f474ca3ed7849a2edcaf4e5fe19e2..7d4fda9167bc050e80d2657a7c48ba8ba7ddcde8 100644 (file)
@@ -1,10 +1,27 @@
 module Database.RRDtool
     ( DataSource(..)
-    , Expr(..)
+
+    , Expr
+    , CommonExpr
+    , IterativeExpr
+    , AggregativeExpr
+
+    , ExprSet
+    , CommonExprSet
+
+    , Constant(..)
+    , CommonUnaryOp(..)
+    , CommonBinaryOp(..)
+    , CommonTrinaryOp(..)
+    , CommonSetOp(..)
+    , IterativeValue(..)
+    , AggregativeUnaryOp(..)
+
     , createRRD
     )
     where
 
+import Data.HList
 import Data.Time.Clock
 import Data.Time.Clock.POSIX
 
@@ -33,10 +50,10 @@ import Data.Time.Clock.POSIX
 -- 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 where
-    -- |GAUGE is for things like temperatures or number of people in a
-    -- room or the value of a RedHat share.
-    GAUGE :: {
+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_]@.
@@ -61,7 +78,7 @@ data DataSource where
       , dsMin :: !(Maybe Double)
         -- |See 'dsMin'.
       , dsMax :: !(Maybe Double)
-    } -> 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
@@ -70,12 +87,12 @@ data DataSource where
     -- 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 :: {
+    | COUNTER {
         dsName      :: !String
       , dsHeartbeat :: !NominalDiffTime
       , dsMin       :: !(Maybe Double)
       , dsMax       :: !(Maybe Double)
-    } -> 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
@@ -83,24 +100,24 @@ data DataSource where
     -- 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 :: {
+    | DERIVE {
         dsName      :: !String
       , dsHeartbeat :: !NominalDiffTime
       , dsMin       :: !(Maybe Double)
       , dsMax       :: !(Maybe Double)
-    } -> 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 :: {
+    | ABSOLUTE {
         dsName      :: !String
       , dsHeartbeat :: !NominalDiffTime
       , dsMin       :: !(Maybe Double)
       , dsMax       :: !(Maybe Double)
-    } -> 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)
@@ -112,7 +129,7 @@ data DataSource where
     -- referred to as \"virtual\" or \"computed\" columns.
     --
     -- FIXME: doc links
-    COMPUTE :: CommonExpr a => {
+    | forall a. CommonExpr a => COMPUTE {
         dsName :: !String
         -- |rpn-expression defines the formula used to compute the
         -- PDPs of a COMPUTE data source from other data sources in
@@ -128,60 +145,111 @@ data DataSource where
         -- 
         -- FIXME: doc links
       , dsExpr :: !a
-    } -> DataSource
+    }
 
 dsTest :: DataSource
 dsTest = COMPUTE {
            dsName = "foo"
-         , dsExpr = Var "foo" :<: Const 100
---         , dsExpr = Previous
+--         , dsExpr = Previous :<: Const 100
+--         , dsExpr = Var "foo" :<: Const 100
+           , dsExpr = Average (Const 100 .*. Const 200 .*. HNil)
          }
 
-{-
-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
+class Show 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, HList es) => ExprSet es
+instance ExprSet HNil
+instance (Expr e, ExprSet es) => ExprSet (HCons e es)
+
+class (Show es, HList es) => CommonExprSet es
+instance CommonExprSet es => ExprSet es
+instance CommonExprSet HNil
+instance (CommonExpr e, CommonExprSet es) => CommonExprSet (HCons e es)
+
 
 -- Constants and variable names
-data Constant where
-    Const :: !Double -> Constant
-    Var   :: !String -> Constant
+data Constant
+    = Const !Double
+    | Var   !String
+    deriving (Show, Eq, Ord)
 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)
+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 Expr a => Expr (CommonUnaryOp a)
+instance CommonExpr a => CommonExpr (CommonUnaryOp 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 (Expr a, Expr b)
+    => Expr (CommonBinaryOp a b)
+instance (CommonExpr a, CommonExpr b)
+    => CommonExpr (CommonBinaryOp a 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)
+
+-- SORT and REV can't be expressed in this way as they pushes possibly
+-- multiple values onto the stack...
+
+data CommonSetOp es
+    = Average !es
+    deriving (Show, Eq, Ord)
+instance ExprSet es => Expr (CommonSetOp es)
+instance CommonExprSet es => CommonExpr (CommonSetOp es)
 
 -- Iterative special values
-data IterativeValue where
-    Previous :: IterativeValue
+data IterativeValue
+    = Previous
+    deriving (Show, Eq, Ord)
 instance Expr IterativeValue
 instance IterativeExpr IterativeValue
 
 -- Aggregative operators
-data AggregativeUnaryOp a where
-    Maximum :: !a -> AggregativeUnaryOp a
+data AggregativeUnaryOp a
+    = Maximum !a
+    deriving (Show, Eq, Ord)
 instance Expr a => Expr (AggregativeUnaryOp a)
 instance AggregativeExpr a => AggregativeExpr (AggregativeUnaryOp a)
 
index 900e4c2fbd46c2718e593038d2f71745536ff78e..6dbb994ab584235ff55257ad588d982d12b5be92 100644 (file)
@@ -23,17 +23,22 @@ Source-Repository head
 
 Library
     Build-Depends:
+        HList           == 0.2.*,
         base            == 4.2.*,
         bindings-librrd == 0.1.*,
         time            == 1.1.*
 
     Extensions:
         EmptyDataDecls
+        ExistentialQuantification
         FlexibleInstances
-        GADTs
+        IncoherentInstances
         TypeOperators
         TypeSynonymInstances
         UndecidableInstances
 
     Exposed-Modules:
         Database.RRDtool
+
+    GHC-Options:
+        -Wall
\ No newline at end of file