Skip to content

Instantly share code, notes, and snippets.

@cppxor2arr
Last active June 29, 2018 15:55
Show Gist options
  • Save cppxor2arr/a93ae09e631cee864ee494a6921e94b7 to your computer and use it in GitHub Desktop.
Save cppxor2arr/a93ae09e631cee864ee494a6921e94b7 to your computer and use it in GitHub Desktop.
weechat log get sent msg count for each nick
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
module Main where
import Data.Map (fromListWith, toList)
main :: IO ()
main = do
let log = "date time Zerock henlo\n\
\date time uptime i'm up\n\
\date time cppxor2arr mwaaa\n\
\date time -- nick change\n\
\date time --> join info\n\
\date time <-- quit info\n\
\date time letty mwaa everyone\n\
\date time @llama mwaaa\n\
\date time * chainsol is morky\n\
\date time @llama bye mwaaa\n\
\date time * cppxor2arr wants to be bogs\n"
print $ nickMsgCnt log
{-
output:
Zerock: 1
chainsol: 1
cppxor2arr: 2
letty: 1
llama: 2
uptime: 1
-}
nickMsgCnt :: String -> [(String,Int)]
nickMsgCnt = frequency . delPrefixes . nicks . msgs . slice . filterInvalid . parse
where parse = map words . lines
filterInvalid = filter ((>= 3) . length)
slice = map (\x -> (x !! 2, x !! 3))
msgs = filter condition
where condition x = not . or $ map' x [join,quit,nickChange]
where map' x = map (\y -> y x)
join (x,_) = x == "-->"
quit (x,_) = x == "<--"
nickChange (x,_) = x == "--"
nicks = map nick
where nick (x,y) = if x == "*" then y else x
delPrefixes = map delPrefix
where delPrefix all@(x:xs) = if x `elem` prefixes then xs else all
where prefixes = "+@"
frequency = toList . fromListWith (+) . assocList
where assocList = map (\x -> (x,1))
instance Show [(String,Int)] where
show = unlines . map format
where format (x,y) = x ++ ": " ++ show y
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment