summaryrefslogtreecommitdiff
path: root/src/Logstat/Main.hs
blob: 96c69bae1066d114d3cfbb4315123b15a90222bd (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
{-# LANGUAGE OverloadedStrings #-}
module Logstat.Main (main) where

import Control.Exception (catchJust)
import Control.Monad (filterM,foldM)
import System.Directory (doesFileExist,getHomeDirectory)
import System.Exit
import System.FilePath ((</>))
import System.IO (hPutStrLn,stderr)
import System.IO.Error (isEOFError)
import Options.Applicative
import Data.Semigroup ((<>))
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C
import qualified Data.Map.Strict as Map

import Logstat.Types
import Logstat.Parse
import Logstat.Value
import Logstat.Eval


-- Extract the final 'show' statement or provide a default expression to display.
-- Returns an error if there is a non-last 'show' statement.
extractShow :: [Stmt] -> Either String ([Expr], [Stmt])
extractShow proc = f [] ["msg"] proc
  where
  f l v [] = Right (map (\v' -> Loc Nothing (EField v')) v, reverse l)
  f l _ ((Loc _ (SShow e)):[]) = Right (e, reverse l)
  f _ _ ((Loc pos (SShow _)):_) = Left $ "Error: show at " ++ show pos ++ " must not be followed by other statements"
  f l _ (x@(Loc _ (SGroup v)):xs) = f (x:l) v xs
  f l v (x:xs) = f (x:l) v xs



run :: [State] -> [Event -> Either EvalError Val] -> Step -> ([State] -> [Either EvalError Event]) -> IO ()
run st sh stp fnl = loop st
  where
  loop state = do
    r <- catchJust
      (\e -> if isEOFError e then Just () else Nothing)
      (Just <$> line state)
      (const (Nothing <$ finalize state))
    case r of
      Nothing -> return ()
      Just state' -> loop state'

  eval ev =
    case mapM (\f -> f ev) sh of
      Left e -> hPutStrLn stderr $ show e
      Right v -> C.putStrLn $ B.intercalate ", " $ map asBS v

  line state = do
    l <- B.getLine
    let event       = Map.fromList [("msg", bs l)]
        (state', r) = stp state event
    case r of
      Left (Loc _ Filtered) -> return ()
      Left e -> hPutStrLn stderr $ show e ++ " with input: " ++ show l
      Right v -> eval v
    return state'

  finalize state = mapM_
    (\r ->
      case r of
        Left e -> hPutStrLn stderr $ show e
        Right l -> eval l)
    (fnl state)



data Options = Options
  { optConfig :: [String]
  , optEval   :: [String]
  , optNoRC   :: Bool
  } deriving(Show)


main :: IO ()
main = do
  o <- execParser opts

  home <- getHomeDirectory
  c <- loadCfg
    (if optNoRC o then [] else ["/etc/logstat.conf", home </> ".logstat.conf", "logstat.conf"])
    (optConfig o)

  stmts' <- concat <$> mapM (parseStmtsIO c "-e") (optEval o)
  (sh, stmts) <- case extractShow stmts' of
    Left e -> hPutStrLn stderr e >> exitFailure
    Right r -> return r

  run (newState stmts) (map evalExpr sh) (stepL stmts) (finalL stmts)

  where
  opts = info (optparse <**> helper) fullDesc
  optparse = Options
    <$> many (strOption (long "config" <> short 'c' <> metavar "FILE" <> help "Config file"))
    <*> some (strOption (long "eval"   <> short 'e' <> metavar "CODE" <> help "Code to evaluate"))
    <*> switch          (long "norc"   <> short 'X'                   <> help "Don't load default config files")

  loadCfg :: [String] -> [String] -> IO Config
  loadCfg def conf = do
    def' <- filterM doesFileExist def
    foldM
      parseFileIO
      (Config mempty mempty [])
      (def' ++ conf)