]> gitweb @ CieloNegro.org - hs-rrdtool.git/blobdiff - Database/RRDtool/Expression.hs
major rename
[hs-rrdtool.git] / Database / RRDtool / Expression.hs
index f2d2574f93b8a23d70ed0c0e0b05004ffbacd1c5..fa6aa5452cd2137d494ee624bcacfb3e77f89612 100644 (file)
@@ -2,6 +2,7 @@
   EmptyDataDecls,
   FlexibleInstances,
   TypeFamilies,
+  TypeOperators,
   MultiParamTypeClasses,
   UndecidableInstances
   #-}
@@ -14,6 +15,7 @@ module Database.RRDtool.Expression
     , IsIterativeExpr
 
     , IsVarName
+    , hString
 
     , Constant(..)
     , Variable(..)
@@ -32,6 +34,7 @@ module Database.RRDtool.Expression
     where
 
 import Data.HList
+import Data.HList.String
 import Types.Data.Bool
 import Types.Data.Num hiding ((:*:))
 import Types.Data.Ord
@@ -53,16 +56,16 @@ type family IsCommonExpr e
 type family IsIterativeExpr e
 
 type family   IsExprSet es
-type instance IsExprSet HNil         = True
-type instance IsExprSet (HCons e es) = IsExpr e :&&: IsExprSet es
+type instance IsExprSet Nil         = True
+type instance IsExprSet (Cons e es) = IsExpr e :&&: IsExprSet es
 
 type family   IsCommonExprSet es
-type instance IsCommonExprSet HNil         = True
-type instance IsCommonExprSet (HCons e es) = IsCommonExpr e :&&: IsCommonExprSet es
+type instance IsCommonExprSet Nil         = True
+type instance IsCommonExprSet (Cons e es) = IsCommonExpr e :&&: IsCommonExprSet es
 
 type family   IsIterativeExprSet es
-type instance IsIterativeExprSet HNil         = True
-type instance IsIterativeExprSet (HCons e es) = IsIterativeExpr e :&&: IsIterativeExprSet es
+type instance IsIterativeExprSet Nil         = True
+type instance IsIterativeExprSet (Cons e es) = IsIterativeExpr e :&&: IsIterativeExprSet es
 
 -- Constants and variable names
 data Constant
@@ -72,24 +75,26 @@ data Constant
 type instance IsExpr          Constant = True
 type instance IsCommonExpr    Constant = True
 type instance IsIterativeExpr Constant = True
-type instance MentionedVars   Constant = HNil
+type instance MentionedVars   Constant = Nil
 
 {- This is what we want to do but GHC can't handle this for now. 
-class ( (HLengthOf str :<=: D255) ~ True
+class ( (Length str :<=: D19) ~ True
       , HString str
       )
     => IsVarName str
 -}
 type family   IsVarName str
-type instance IsVarName str = ( (HLength str :<=: D255)
+type instance IsVarName str = ( (Length str :>: D0)
                                 :&&:
-                                (HAll IsGoodLetterForVarNameA str)
+                                (Length str :<=: D19)
+                                :&&:
+                                (All IsGoodLetterForVarNameA str)
                               )
 
 type family   IsGoodLetterForVarName c
 type instance IsGoodLetterForVarName c = ( ((c :>=: D65) :&&: (c :<=:  D90)) -- A-Z
                                            :||:
-                                           ((c :>=: D99) :&&: (c :<=: D122)) -- a-z
+                                           ((c :>=: D97) :&&: (c :<=: D122)) -- a-z
                                            :||:
                                            (c :==: D45) -- '-'
                                            :||:
@@ -101,18 +106,17 @@ instance ApplyT IsGoodLetterForVarNameA c where
     type Apply IsGoodLetterForVarNameA c = IsGoodLetterForVarName c
 
 -- Variable
-data Variable vn
-    = Variable !vn
-    deriving (Show, Eq, Ord)
+data Variable vn = Var !vn
+                   deriving (Show, Eq, Ord)
 
 type instance IsExpr          (Variable vn) = True
 type instance IsCommonExpr    (Variable vn) = True
 type instance IsIterativeExpr (Variable vn) = True
-type instance MentionedVars   (Variable vn) = vn :*: HNil
+type instance MentionedVars   (Variable vn) = vn :&: Nil
 
 type family   IsVariableSet vs
-type instance IsVariableSet HNil         = True
-type instance IsVariableSet (HCons v vs) = IsVarName v :&&: IsVariableSet vs
+type instance IsVariableSet Nil         = True
+type instance IsVariableSet (Cons v vs) = IsVarName v :&&: IsVariableSet vs
 
 -- Common operators
 data CommonUnaryOp a
@@ -196,7 +200,7 @@ data CommonSetOp es
 type instance IsExpr          (CommonSetOp es) = IsExprSet          es
 type instance IsCommonExpr    (CommonSetOp es) = IsCommonExprSet    es
 type instance IsIterativeExpr (CommonSetOp es) = IsIterativeExprSet es
-type instance MentionedVars   (CommonSetOp es) = HConcat (HMap MentionedVarsA es)
+type instance MentionedVars   (CommonSetOp es) = Concat (Map MentionedVarsA es)
 
 -- TrendOp
 data TrendOp vn e
@@ -207,7 +211,7 @@ data TrendOp vn e
 type instance IsExpr          (TrendOp vn e) = IsVarName vn :&&: IsExpr e
 type instance IsCommonExpr    (TrendOp vn e) = IsVarName vn :&&: IsCommonExpr e
 type instance IsIterativeExpr (TrendOp vn e) = IsVarName vn :&&: IsIterativeExpr e
-type instance MentionedVars   (TrendOp vn e) = vn :*: MentionedVars e
+type instance MentionedVars   (TrendOp vn e) = vn :&: MentionedVars e
 
 -- VariableShiftPredictOp
 data VariableShiftPredictOp ss w vn
@@ -225,7 +229,7 @@ type instance IsIterativeExpr (VariableShiftPredictOp ss w vn)
     = IsIterativeExprSet ss :&&: IsIterativeExpr w :&&: IsVarName vn
 
 type instance MentionedVars (VariableShiftPredictOp ss w vn)
-    = vn :*: (MentionedVars ss :++: MentionedVars w)
+    = vn :&: (MentionedVars ss :++: MentionedVars w)
 
 -- FixedShiftPredictOp
 data FixedShiftPredictOp sm w vn
@@ -243,7 +247,7 @@ type instance IsIterativeExpr (FixedShiftPredictOp sm w vn)
     = IsIterativeExpr sm :&&: IsIterativeExpr w :&&: IsVarName vn
 
 type instance MentionedVars (FixedShiftPredictOp sm w vn)
-    = vn :*: (MentionedVars sm :++: MentionedVars w)
+    = vn :&: (MentionedVars sm :++: MentionedVars w)
 
 -- Common special values
 data CommonValue
@@ -256,7 +260,7 @@ data CommonValue
 type instance IsExpr          CommonValue = True
 type instance IsCommonExpr    CommonValue = True
 type instance IsIterativeExpr CommonValue = True
-type instance MentionedVars   CommonValue = HNil
+type instance MentionedVars   CommonValue = Nil
 
 -- Iterative special values
 data IterativeValue
@@ -269,7 +273,7 @@ data IterativeValue
 type instance IsExpr          IterativeValue = True
 type instance IsCommonExpr    IterativeValue = False
 type instance IsIterativeExpr IterativeValue = True
-type instance MentionedVars   IterativeValue = HNil
+type instance MentionedVars   IterativeValue = Nil
 
 -- Iterative special values of something
 data IterativeValueOf vn
@@ -279,7 +283,7 @@ data IterativeValueOf vn
 type instance IsExpr          (IterativeValueOf vn) = IsVarName vn
 type instance IsCommonExpr    (IterativeValueOf vn) = False
 type instance IsIterativeExpr (IterativeValueOf vn) = IsVarName vn
-type instance MentionedVars   (IterativeValueOf vn) = vn :*: HNil
+type instance MentionedVars   (IterativeValueOf vn) = vn :&: Nil
 
 -- Aggregative operators (fairly restricted due to rrdtool's
 -- restriction)
@@ -298,4 +302,4 @@ data AggregativeUnaryOp vn
     | LSLCorrel  !(Variable vn)
     deriving (Show, Eq, Ord)
 
-type instance MentionedVars (AggregativeUnaryOp vn) = vn :*: HNil
+type instance MentionedVars (AggregativeUnaryOp vn) = vn :&: Nil