]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool/Create.hs
DSList
[hs-rrdtool.git] / Database / RRDtool / Create.hs
index a6a67fca729a31f3a5eefa750c0cc79fff45776f..2adeb2475a7abe86f3766eb4fff4cf5d58ed0d34 100644 (file)
@@ -1,7 +1,12 @@
 {-# LANGUAGE
+  FlexibleContexts,
+  FlexibleInstances,
+  GADTs,
+  OverlappingInstances,
   TypeFamilies,
   UndecidableInstances
   #-}
+{-# LANGUAGE QuasiQuotes #-} -- DELETE THIS
 module Database.RRDtool.Create
     ( DataSource
     , ExternalDSType(..)
@@ -10,7 +15,7 @@ module Database.RRDtool.Create
     , createRRD
 
     -- Data.HList
-    , (.*.)    
+    , (.&.)
     , HNil(..)
 
     -- Database.RRDtool.Expression
@@ -91,14 +96,12 @@ data ExternalDSType
                -- number of messages since the last update.
     deriving (Show, Eq, Ord)
 
-instance DataSource ExternalDSType
-
-data ExternalDataSource
+data ExternalDataSource vn
     = ExternalDataSource {
         -- |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_]@.
-        edsName :: !String
+        edsName :: !vn
         -- |The type of this data source.
       , edsType :: !ExternalDSType
         -- |Defines the maximum number of seconds that may pass
@@ -124,6 +127,10 @@ data ExternalDataSource
       }
     deriving (Show, Eq, Ord)
 
+instance ( IsVarName vn ~ True
+         )
+    => DataSource (ExternalDataSource vn)
+
 
 -- |ComputedDataSource is for storing the result of a formula applied
 -- to other data sources in the RRD. This data source is not supplied
@@ -136,10 +143,10 @@ data ExternalDataSource
 -- \"computed\" columns.
 --
 -- FIXME: doc links
-data ComputedDataSource e
+data ComputedDataSource vn e
     = ComputedDataSource {
         -- |See 'edsName'
-        cdsName :: !String
+        cdsName :: !vn
         -- |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
@@ -157,33 +164,76 @@ data ComputedDataSource e
     }
     deriving (Show, Eq, Ord)
 
-instance (IsCommonExpr e ~ True) =>
-    DataSource (ComputedDataSource e)
-
+instance ( IsVarName vn ~ True
+         , IsCommonExpr e ~ True
+         )
+    => DataSource (ComputedDataSource vn e)
 
+{-
 dsTest = ComputedDataSource {
            cdsName = "foo"
 --         , cdsExpr = Previous :<: Const 100
 --         , cdsExpr = Var "foo" :<: Const 100
          , cdsExpr = AverageOf (Const 100 .*. Const 200 .*. HNil)
          }
+-}
+
+-- |The name of the RRD you want to create. RRD files should end with
+-- the extension @.rrd@. However, RRDtool will accept any filename.
+newtype RRDPath = RRDPath FilePath
+
+-- |Do not clobber an existing file of the same name.
+data KeepOldRRD = KeepOldRRD
+
+-- |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@)
+newtype RRDStartTime = RRDStartTime POSIXTime
+
+-- |Specifies the base interval in seconds with which data will be fed
+-- into the RRD. (default: 300 sec)
+newtype RRDInterval = RRDInterval NominalDiffTime
+
+class RRDSpec s
+instance ( HOccurs    RRDPath       s
+         , HOccursOpt KeepOldRRD    s
+         , HOccursOpt RRDStartTime  s
+         , HOccursOpt RRDInterval   s
+         )
+    => RRDSpec s
+
+class NonEmptyDSList l
+instance ( DSList l
+         , DataSource ds
+         )
+    => NonEmptyDSList (HCons ds l)
+
+class DSList l
+instance DSList HNil
+instance ( DSList l
+         , DataSource ds
+         )
+    => DSList (HCons ds l)
+
+-- DataList would be a graph...
 
 -- |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 :: ( RRDSpec s
+             , NonEmptyDSList l
+             )
+            => s -> l -> IO ()
 createRRD = error "FIXME"
+
+testMain :: IO ()
+testMain = let s = RRDPath "test.rrd" .&.
+                   KeepOldRRD         .&.
+                   HNil
+               x = ComputedDataSource {
+                     cdsName = [$hString|foo|]
+                   , cdsExpr = Const 100
+                   }
+               d = x .&. HNil
+           in
+             createRRD s d