Skip to content

Commit

Permalink
+vdef render
Browse files Browse the repository at this point in the history
  • Loading branch information
zong-sharo committed Jan 17, 2011
1 parent d302bee commit 86f1f92
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 7 deletions.
6 changes: 3 additions & 3 deletions RRD/RPN/Prim.hs
Expand Up @@ -6,7 +6,7 @@ module RRD.RPN.Prim
, UnaryOperator(..)
, BinaryOperator(..)
, Symbol(..)
, Aggretate(..)
, Aggregate(..)
, AggregateFunction(..)
, RpnValue(..)
, PrimExprEq
Expand All @@ -19,7 +19,7 @@ import RRD.Util (showF)
data Reference
= DataSource String FilePath String
| Expr String (RpnExpr Double)
| AggregateExpr String Aggretate
| AggregateExpr String Aggregate

refName :: Reference -> String
refName (DataSource a _ _) = a
Expand Down Expand Up @@ -128,7 +128,7 @@ data Symbol
| Now
| RecordTime TimeFormat

data Aggretate = Aggregate Reference AggregateFunction
data Aggregate = Aggregate Reference AggregateFunction

data AggregateFunction
= Maximum
Expand Down
27 changes: 23 additions & 4 deletions RRD/RPN/Render.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE GADTs, PackageImports #-}
module RRD.RPN.Render where
import RRD.RPN.Prim
import "monads-tf" Control.Monad.Writer
import "monads-tf" Control.Monad.Writer (Writer, runWriter, tell)
import System.FilePath (takeBaseName)


Expand All @@ -25,16 +25,16 @@ renderRpn (UOp op a) = renderRpn a >> mapM_ push (reprUOp op)
renderRpn (BOp op a b) = renderRpn a >> renderRpn b >> mapM_ push (reprBOp op)
renderRpn (If pred a b) = renderRpn a >> renderRpn b >> renderRpn pred >> push "IF"
renderRpn (Limit a lower upper) = renderRpn a >> renderRpn lower >> renderRpn upper
renderRpn (Sym s) = push (renderSymbol s)
renderRpn (Sym s) = push (reprSymbol s)
renderRpn (Foldr op seed xs)
| length' xs == 0 = renderRpn seed
| otherwise = do
renderRpn xs
renderRpn seed
mapM_ push $ concat $ replicate (length' xs) $ reprBOp op

renderSymbol :: Symbol -> String
renderSymbol sym =
reprSymbol :: Symbol -> String
reprSymbol sym =
case sym of
Unknown -> "UNKN"
Infinity -> "INF"
Expand Down Expand Up @@ -88,3 +88,22 @@ reprBOp op =
Atan2 -> ["ATAN2"]
Cons -> []
Flip op -> ["EXC"] ++ reprBOp op

renderAggregate :: Aggregate -> Render ()
renderAggregate (Aggregate ref f) = push (refName ref) >> mapM_ push (reprAggregateFunction f)

reprAggregateFunction :: AggregateFunction -> [String]
reprAggregateFunction f =
case f of
Maximum -> ["MAXIMUM"]
Minimum -> ["MINIMUM"]
AverageValue -> ["AVERAGE"]
StandardDeviation -> ["STDEV"]
Last -> ["LAST"]
First -> ["FIRST"]
Total -> ["TOTAL"]
Percent n -> [renderValue n, "PERCENT"]
PercentNan n -> [renderValue n, "PERCENTNAN"]
LeastSquareLineSlope -> ["LSLSLOPE"]
LeastSquareLineInt -> ["LSLINT"]
LeastSquareLineCorrelationCoefficient -> ["LSLCORREL"]

0 comments on commit 86f1f92

Please sign in to comment.