Skip to content

Instantly share code, notes, and snippets.

@evanrinehart
Last active June 3, 2017 01:27
Show Gist options
  • Save evanrinehart/5841875e9de68bdda46900763ffe2c60 to your computer and use it in GitHub Desktop.
Save evanrinehart/5841875e9de68bdda46900763ffe2c60 to your computer and use it in GitHub Desktop.
module Foo where
import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8
import Data.Attoparsec.Combinator
import Control.Applicative
import Data.Time
import Data.ByteString
import qualified Data.ByteString as BS
import Control.Monad
consumer ::
IO ByteString -> -- a source of ByteString input chunks
(UTCTime -> ByteString -> IO ()) -> -- callback to run on each timestamp-body pair, after the first (second) time stamp is found
IO a -- never returns, continues to absorb input until it crashes or is killed
consumer readBytes callback = go0 where
-- initial state, begin parsing
go0 = readBytes >>= go1 . parse chunk
-- keep parsing until you get a timestamp
go1 result = case result of
Done rest (prefix, ts) -> go2 ts (parse chunk rest)
Partial k -> readBytes >>= go1 . k
_ -> error "impossible (go1 failed)"
-- keep parsing until you get a timestamp, then execute
-- callback on old timestamp and everything before next one
-- then repeat
go2 ts result = case result of
Done rest (prefix, ts') -> do
callback ts prefix
go2 ts' (parse chunk rest)
Partial k -> readBytes >>= go2 ts . k
_ -> error "impossible (go2 failed)"
chunk :: Parser (ByteString, UTCTime)
chunk = do
(bs, ts) <- match (skipUntil timestamp)
_ <- timestamp
return (bs,ts)
skipUntil :: Parser a -> Parser a
skipUntil p = (lookAhead p) <|> (anyWord8 >> skipUntil p)
timestamp :: Parser UTCTime
timestamp = do
year <- decimal
char '-'
month <- decimal
char '-'
day <- decimal
case fromGregorianValid year month day of
Nothing -> mzero
Just date -> do
char ' '
hour <- fmap fromInteger decimal
char ':'
minute <- fmap fromInteger decimal
char ':'
seconds <- scientific
let time = 3600 * hour + 60 * minute + seconds
return (UTCTime date (realToFrac time))
{-
munge :: ByteString -> [ByteString]
munge bs = case (BS.take 35 bs, BS.drop 35 bs) of
(x, xs) | BS.null xs -> [x]
| otherwise -> x : munge xs
loadInput :: IO [ByteString]
loadInput = do
input <- BS.readFile "logback.log"
let (x,y) = foldr (\b -> (
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment