Skip to content
This repository has been archived by the owner on Feb 9, 2020. It is now read-only.

Commit

Permalink
Support injecting custom parsers when used as a library.
Browse files Browse the repository at this point in the history
  • Loading branch information
pbogdan committed Apr 20, 2017
1 parent 8165bf0 commit bed9498
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 15 deletions.
7 changes: 1 addition & 6 deletions ngx-top/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,4 @@ import Protolude
import NgxTop

main :: IO ()
main = do
args <- getArgs
case args of
[] -> putText "Usage: ngx-top logfile"
[x] -> run x
_ -> putText "Usage: ngx-top logfile"
main = defaultMain defaultSettings
39 changes: 30 additions & 9 deletions ngx-top/src/NgxTop.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,17 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

module NgxTop
( run
( Settings(..)
, defaultSettings
, defaultMain
, run
) where

import Protolude hiding ((&), try)

import Brick.BChan
import Brick.Main
import qualified Brick.Main
import Control.Concurrent.STM.TVar
import Control.Exception.Safe
import qualified Control.Foldl as Fold
Expand All @@ -17,6 +21,8 @@ import Data.GeoIP2
import qualified Data.HashMap.Strict as HashMap
import Data.IP
import qualified Data.IntMap.Strict as IntMap
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import GeoIP
import Graphics.Vty
import Log.Nginx.Combined
Expand All @@ -32,17 +38,32 @@ import System.IO.TailFile.Pipes
import Types
import URI.ByteString

run :: FilePath -> IO ()
run path = do
{-# ANN Settings ("HLint: Use newtype instead of data" :: Text) #-}
data Settings = Settings
{ parsers :: NonEmpty (ByteString -> Either Text AccessLogEntry)
}

defaultSettings :: Settings
defaultSettings = Settings {parsers = NE.fromList [parseGateway, parseCombined]}

defaultMain :: Settings -> IO ()
defaultMain settings = do
args <- getArgs
case args of
[] -> putText "Usage: ngx-top logfile"
[x] -> run settings x
_ -> putText "Usage: ngx-top logfile"

run :: Settings -> FilePath -> IO ()
run Settings {..} path = do
line <-
try
(evaluate =<<
(do h <- openFile path ReadMode
Bytes.hGetLine h))
let parsers = [parseGateway, parseCombined]
parser =
case detect parsers <$> line of
Left (_ :: SomeException) -> parseGateway
let parser =
case detect (NE.toList parsers) <$> line of
Left (_ :: SomeException) -> NE.head parsers
Right (Just x) -> x
_ -> parseGateway
db <- openGeoDBBS geoIPDB
Expand All @@ -68,7 +89,7 @@ run path = do
async $
void $ do
_ <-
customMain
Brick.Main.customMain
(mkVty defaultConfig {termName = Nothing})
(Just eventChan)
(app path)
Expand Down

0 comments on commit bed9498

Please sign in to comment.