summaryrefslogtreecommitdiff
path: root/src/Logstat/Eval.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Logstat/Eval.hs')
-rw-r--r--src/Logstat/Eval.hs32
1 files changed, 19 insertions, 13 deletions
diff --git a/src/Logstat/Eval.hs b/src/Logstat/Eval.hs
index 8e29818..d497cbf 100644
--- a/src/Logstat/Eval.hs
+++ b/src/Logstat/Eval.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings, FlexibleContexts, FlexibleInstances #-}
module Logstat.Eval where
+import Text.Megaparsec (SourcePos)
import Data.Fixed (mod')
import Data.Foldable (foldl',toList)
import qualified Data.ByteString as B
@@ -38,7 +39,7 @@ instance Ord a => Ord (SortItem a) where (SortItem a _) <= (SortItem b _) = a <=
newState :: [Stmt] -> [State]
newState = map st
where
- st s = case s of
+ st (Loc _ s) = case s of
SSort _ _ SortAscNum -> StSortAscNum mempty
SSort _ _ SortAscBS -> StSortAscBS mempty
SSort _ _ SortDescNum -> StSortDescNum mempty
@@ -48,11 +49,16 @@ newState = map st
getField :: Event -> Field -> Either EvalError Val
-getField st n = maybe (Left (UnknownField n)) return $ Map.lookup n st
+getField st n = maybe (Left (Loc Nothing $ UnknownField n)) return $ Map.lookup n st
+
+
+setLoc :: Maybe SourcePos -> Either EvalError a -> Either EvalError a
+setLoc pos (Left (Loc Nothing r)) = Left $ Loc pos r
+setLoc _ r = r
evalExpr :: Expr -> Event -> Either EvalError Val
-evalExpr expr ev = case expr of
+evalExpr (Loc pos expr) ev = setLoc pos $ case expr of
ELit e -> Right e
EField f -> getField ev f
ENot e -> bool . not . asBool <$> evalExpr e ev
@@ -68,7 +74,7 @@ evalExpr expr ev = case expr of
EExtract e r -> do
v <- asBS <$> evalExpr e ev
- ma <- maybe (Left (NoExtract v)) return $ match r v
+ ma <- maybe (Left (Loc pos $ NoExtract v)) return $ match r v
return $ bs $ ma !! 1
EReplace e r n ->
@@ -110,7 +116,7 @@ evalExpr expr ev = case expr of
-- Division with zero-check
idiv f = withab asNum $ \a b ->
if b == 0
- then Left DivByZero
+ then Left $ Loc pos DivByZero
else return $ num $ f a b
@@ -135,14 +141,14 @@ evalExpr expr ev = case expr of
-- the final step.
step :: Stmt -> State -> Event -> (State, Either EvalError Event)
-step stmt st ev = case stmt of
+step (Loc pos stmt) st ev = setLoc pos <$> case stmt of
SShow _ -> undefined -- Should be handled by extractShow
SSet f e -> (,) st $ evalExpr e ev >>= \v -> return $ Map.insert f v ev
- SFilter e -> (,) st $ evalExpr e ev >>= \v -> if asBool v then return ev else Left Filtered
+ SFilter e -> (,) st $ evalExpr e ev >>= \v -> if asBool v then return ev else Left $ Loc pos Filtered
SRegex f r p -> (,) st $ do
val <- asBS <$> getField ev f
- ma <- maybe (Left (NoMatch f val)) return $ match r val
+ ma <- maybe (Left (Loc pos $ NoMatch f val)) return $ match r val
return $ foldl' ins ev $ zip ma p
where
ins s (_, Nothing) = s
@@ -159,7 +165,7 @@ step stmt st ev = case stmt of
run wrap hp f =
case evalExpr e ev >>= f of
Left err -> (st, Left err)
- Right val -> (wrap (ins hp val), Left Filtered)
+ Right val -> (wrap (ins hp val), Left $ Loc pos Filtered)
ins hp val =
let si = SortItem val ev in
if Heap.size hp < n
@@ -174,11 +180,11 @@ step stmt st ev = case stmt of
Left err -> (st, Left err)
Right v ->
let m' = Map.insert v () m
- in m' `seq` (StGroup m', Left Filtered)
+ in m' `seq` (StGroup m', Left $ Loc pos Filtered)
final :: Stmt -> State -> [Event]
-final stmt st = case stmt of
+final (Loc _ stmt) st = case stmt of
SSort _ _ _ ->
case st of
StSortAscNum hp -> f hp
@@ -221,5 +227,5 @@ finalL = loop
let (st', r) = f st ev
(st'', evs') = steps f st' evs
in (,) st'' $ case r of
- Left Filtered -> evs'
- _ -> r : evs'
+ Left (Loc _ Filtered) -> evs'
+ _ -> r : evs'