Skip to content

Instantly share code, notes, and snippets.

@fusion5
Created November 25, 2011 18:52
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save fusion5/1394192 to your computer and use it in GitHub Desktop.
Save fusion5/1394192 to your computer and use it in GitHub Desktop.
module Enumerator where
import Prelude hiding (init, unwords, words)
import Data.Enumerator hiding (map)
import qualified Data.Enumerator.Text as ET
import qualified Data.Enumerator.List as EL
import Data.Text hiding (reverse, take, map)
import Data.List (sort)
import qualified Data.Map as Map
data Entry = Entry {
date :: Text
, host :: Text
, program :: Text
, message :: Text
} deriving Show
parseEntry :: Text
-> Entry
parseEntry t = Entry d h p m
where
d1:d2:d3:h:p':ms = words t
d = unwords [d1,d2,d3]
p = init p'
m = unwords ms
-- Build a Text Enumerator from file lines:
logFileEnum :: Enumerator Text IO b
logFileEnum = ET.enumFile "/var/log/syslog"
-- Enumeratee to convert Text lines to Entry values:
convertToEntry :: Enumeratee Text Entry IO b
convertToEntry = EL.map parseEntry
-- The same idea of using a Map to count program occurences seen in the Automata module.
-- Iteratee for list of entries:
countProgramOcc :: Iteratee Entry IO (Map.Map Text Int)
countProgramOcc = EL.fold f Map.empty
where f m entry = Map.insertWith' (+) (program entry) 1 m
-- Iteratee that counts the number of list elements:
countLines :: Iteratee a IO Integer
countLines = EL.fold f 0
where f = flip $ const $ (+) 1
-- Iteratee that converts lines to entries using `convertToEntry' and applies the two
-- other Iteratees, `countProgramOcc' and `countLines':
logFileIteratee :: Iteratee Entry IO (Map.Map Text Int, Integer)
logFileIteratee = (logFileEnum $= convertToEntry) $$ EL.zip countProgramOcc countLines
top :: Int -> (Map.Map Text Int) -> [(Int, Text)]
top n = take n . reverse . sort . map swap . Map.toList
swap (x,y) = (y, x)
main :: IO ()
main = do
(entries, c) <- run_ logFileIteratee
putStrLn "Top program name occurences: "
Prelude.mapM print (top 10 entries)
putStrLn "Total log file entries: "
print c
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment