]> gitweb @ CieloNegro.org - hs-rrdtool.git/blob - Database/RRDtool/Expression.hs
669acbca32adffa985f93c652b4e60cc5823f39e
[hs-rrdtool.git] / Database / RRDtool / Expression.hs
1 module Database.RRDtool.Expression
2     ( MentionedVars(..)
3     , ApplyMentionedVarsOf(..)
4
5     , IsExpr
6     , IsCommonExpr
7     , IterativeExpr
8     , IsAggregativeExpr
9
10     , IsExprSet
11     , IsCommonExprSet
12
13     , Constant(..)
14     , IsVarName(..)
15     , Variable(..)
16     , IsVariableSet
17     , CommonUnaryOp(..)
18     , CommonBinaryOp(..)
19     , CommonTrinaryOp(..)
20     , CommonSetOp(..)
21     , TrendOp(..)
22     , VariableShiftPredictOp(..)
23     , FixedShiftPredictOp(..)
24     , CommonValue(..)
25     , IterativeValue(..)
26     , IterativeValueOf(..)
27     , AggregativeUnaryOp(..)
28     )
29     where
30
31 import Data.HList
32
33
34 -- MentionedVars
35 class IsVariableSet (MentionedVarsOf a) => MentionedVars a where
36     type MentionedVarsOf a
37
38 -- ApplyMentionedVarsOf
39 data ApplyMentionedVarsOf = ApplyMentionedVarsOf
40
41 instance Applyable ApplyMentionedVarsOf a where
42     type Apply ApplyMentionedVarsOf a = MentionedVarsOf a
43     apply = undefined
44
45 -- IsExpr
46 class (Show e, Eq e) => IsExpr e
47 class IsExpr e => IsCommonExpr e
48 class IsExpr e => IterativeExpr e
49 class IsExpr e => IsAggregativeExpr e
50
51 class (Show es, Eq es, HList es) => IsExprSet es
52 instance IsExprSet HNil
53 instance (IsExpr e, IsExprSet es) => IsExprSet (HCons e es)
54
55 class (Show es, Eq es, HList es) => IsCommonExprSet es
56 instance IsCommonExprSet HNil
57 instance (IsCommonExpr e, IsCommonExprSet es) => IsCommonExprSet (HCons e es)
58
59
60 -- Constants and variable names
61 data Constant
62     = Const !Double
63     deriving (Show, Eq, Ord)
64 instance IsExpr Constant
65 instance IsCommonExpr Constant
66 instance MentionedVars Constant where
67     type MentionedVarsOf Constant = HNil
68
69 class (Show a, Eq a, Ord a) => IsVarName a where
70     varName :: a -> String
71
72 data Variable vn
73     = Variable !vn
74     deriving (Show, Eq, Ord)
75
76 instance IsVarName vn => IsExpr (Variable vn)
77 instance IsVarName vn => IsCommonExpr (Variable vn)
78 instance IsVarName vn => MentionedVars (Variable vn) where
79     type MentionedVarsOf (Variable vn) = vn :*: HNil
80
81 class HList vs => IsVariableSet vs
82 instance IsVariableSet HNil
83 instance (IsVarName v, IsVariableSet vs) => IsVariableSet (HCons v vs)
84
85 -- Common operators
86 data CommonUnaryOp a
87     = IsUnknown  !a
88     | IsInfinity !a
89     | Sin        !a
90     | Cos        !a
91     | Log        !a
92     | Exp        !a
93     | Sqrt       !a
94     | Atan       !a
95     | Floor      !a
96     | Ceil       !a
97     | Deg2Rad    !a
98     | Rad2Deg    !a
99     | Abs        !a
100     deriving (Show, Eq, Ord)
101 instance IsExpr a => IsExpr (CommonUnaryOp a)
102 instance IsCommonExpr a => IsCommonExpr (CommonUnaryOp a)
103 instance IsVariableSet (MentionedVarsOf a) => MentionedVars (CommonUnaryOp a) where
104     type MentionedVarsOf (CommonUnaryOp a) = MentionedVarsOf a
105
106 data CommonBinaryOp a b
107     = !a :<:  !b
108     | !a :<=: !b
109     | !a :>:  !b
110     | !a :>=: !b
111     | !a :==: !b
112     | !a :/=: !b
113     | Min !a !b
114     | Max !a !b
115     | !a :+: !b
116     | !a :-: !b
117     | !a :*: !b
118     | !a :/: !b
119     | !a :%: !b
120     | AddNaN !a !b
121     | AtanXY !a !b
122     deriving (Show, Eq, Ord)
123
124 instance (IsExpr a, IsExpr b) =>
125     IsExpr (CommonBinaryOp a b)
126
127 instance (IsCommonExpr a, IsCommonExpr b) =>
128     IsCommonExpr (CommonBinaryOp a b)
129
130 instance IsVariableSet (MentionedVarsOf a :++: MentionedVarsOf b) =>
131     MentionedVars (CommonBinaryOp a b) where
132         type MentionedVarsOf (CommonBinaryOp a b)
133             = MentionedVarsOf a :++: MentionedVarsOf b
134         
135
136 data CommonTrinaryOp a b c
137     = If !a !b !c
138     | Limit !a !b !c
139     deriving (Show, Eq, Ord)
140
141 instance (IsExpr a, IsExpr b, IsExpr c)
142     => IsExpr (CommonTrinaryOp a b c)
143
144 instance (IsCommonExpr a, IsCommonExpr b, IsCommonExpr c)
145     => IsCommonExpr (CommonTrinaryOp a b c)
146
147 instance IsVariableSet (MentionedVarsOf a :++:
148                         MentionedVarsOf b :++:
149                         MentionedVarsOf c) =>
150     MentionedVars (CommonTrinaryOp a b c) where
151         type MentionedVarsOf (CommonTrinaryOp a b c)
152             = MentionedVarsOf a :++:
153               MentionedVarsOf b :++:
154               MentionedVarsOf c
155
156 -- SORT and REV can't be expressed in this way as they pushes possibly
157 -- multiple values onto the stack...
158
159 data CommonSetOp es
160     = AverageOf !es
161     deriving (Show, Eq, Ord)
162
163 instance IsExprSet es => IsExpr (CommonSetOp es)
164 instance (IsExprSet es, IsCommonExprSet es) => IsCommonExpr (CommonSetOp es)
165 instance IsVariableSet (HConcat (HMap ApplyMentionedVarsOf es)) =>
166     MentionedVars (CommonSetOp es) where
167         type MentionedVarsOf (CommonSetOp es)
168             = HConcat (HMap ApplyMentionedVarsOf es)
169
170 data TrendOp vn a
171     = Trend      !(Variable vn) !a
172     | TrendNan   !(Variable vn) !a
173     deriving (Show, Eq, Ord)
174 instance (IsVarName vn, IsExpr a) => IsExpr (TrendOp vn a)
175 instance (IsVarName vn, IsCommonExpr a) => IsCommonExpr (TrendOp vn a)
176
177 instance ( IsVariableSet (vn :*: MentionedVarsOf a)
178          ) => MentionedVars (TrendOp vn a) where
179     type MentionedVarsOf (TrendOp vn a) = vn :*: MentionedVarsOf a
180
181 data VariableShiftPredictOp ss w vn
182     = VariableShiftPredictAverage !ss !w !(Variable vn)
183     | VariableShiftPredictSigma   !ss !w !(Variable vn)
184     deriving (Show, Eq, Ord)
185 instance (IsExprSet ss, IsExpr w, IsVarName vn)
186     => IsExpr (VariableShiftPredictOp ss w vn)
187 instance (IsExprSet ss, IsCommonExprSet ss, IsCommonExpr w, IsVarName vn)
188     => IsCommonExpr (VariableShiftPredictOp ss w vn)
189 instance ( IsVariableSet (vn :*: (MentionedVarsOf ss :++: MentionedVarsOf w))
190          ) => MentionedVars (VariableShiftPredictOp ss w vn) where
191     type MentionedVarsOf (VariableShiftPredictOp ss w vn)
192         = vn :*: (MentionedVarsOf ss :++: MentionedVarsOf w)
193
194 -- FixedShiftPredictOp
195 data FixedShiftPredictOp sm w vn
196     = FixedShiftPredictAverage !sm !w !(Variable vn)
197     | FixedShiftPredictSigma   !sm !w !(Variable vn)
198     deriving (Show, Eq, Ord)
199
200 instance (IsExpr sm, IsExpr w, IsVarName vn)
201     => IsExpr (FixedShiftPredictOp sm w vn)
202
203 instance (IsCommonExpr sm, IsCommonExpr w, IsVarName vn)
204     => IsCommonExpr (FixedShiftPredictOp sm w vn)
205
206 instance ( IsVariableSet (vn :*: (MentionedVarsOf sm :++: MentionedVarsOf w))
207          ) => MentionedVars (FixedShiftPredictOp sm w vn) where
208     type MentionedVarsOf (FixedShiftPredictOp sm w vn)
209         = vn :*: (MentionedVarsOf sm :++: MentionedVarsOf w)
210
211 -- Common special values
212 data CommonValue
213     = Unknown
214     | Infinity
215     | NegativeInfinity
216     | Now
217     deriving (Show, Eq, Ord)
218
219 instance IsExpr CommonValue
220
221 instance IsCommonExpr CommonValue
222
223 instance MentionedVars CommonValue where
224     type MentionedVarsOf CommonValue = HNil
225
226 -- Iterative special values
227 data IterativeValue
228     = Previous
229     | Count
230     | TakenTime
231     | TakenLocalTime
232     deriving (Show, Eq, Ord)
233
234 instance IsExpr IterativeValue
235
236 instance IterativeExpr IterativeValue
237
238 instance MentionedVars IterativeValue where
239     type MentionedVarsOf IterativeValue = HNil
240
241 -- Iterative special values of something
242 data IterativeValueOf vn
243     = PreviousOf !(Variable vn)
244     deriving (Show, Eq, Ord)
245
246 instance IsVarName vn => IsExpr (IterativeValueOf vn)
247
248 instance IsVarName vn => IterativeExpr (IterativeValueOf vn)
249
250 instance IsVarName vn => MentionedVars (IterativeValueOf vn) where
251     type MentionedVarsOf (IterativeValueOf vn) = vn :*: HNil
252
253 -- Aggregative operators (fairly restricted due to rrdtool's
254 -- restriction)
255 data AggregativeUnaryOp vn
256     = Maximum    !(Variable vn)
257     | Minimum    !(Variable vn)
258     | Average    !(Variable vn)
259     | StandardDeviation !(Variable vn)
260     | First      !(Variable vn)
261     | Last       !(Variable vn)
262     | Total      !(Variable vn)
263     | Percent    !(Variable vn) !Constant
264     | PercentNan !(Variable vn) !Constant
265     | LSLSlope   !(Variable vn)
266     | LSLInt     !(Variable vn)
267     | LSLCorrel  !(Variable vn)
268     deriving (Show, Eq, Ord)
269
270 instance IsVarName vn => IsExpr (AggregativeUnaryOp vn)
271
272 instance IsVarName vn => IsAggregativeExpr (AggregativeUnaryOp vn)
273
274 instance IsVarName vn => MentionedVars (AggregativeUnaryOp vn) where
275     type MentionedVarsOf (AggregativeUnaryOp vn) = vn :*: HNil