Skip to content

Instantly share code, notes, and snippets.

@MgaMPKAy
Created August 24, 2014 04:02
Show Gist options
  • Save MgaMPKAy/e0145b103a5a76428efa to your computer and use it in GitHub Desktop.
Save MgaMPKAy/e0145b103a5a76428efa to your computer and use it in GitHub Desktop.
Dump command history into InfluxDB (rember to `iconv -t utf8 -c ~/.bash_history > history`)
{-# LANGUAGE OverloadedStrings #-}
import Parser
import Types
import Network.HTTP.Client
import Control.Applicative
import Control.Monad.Trans (liftIO)
import Database.InfluxDB
main = do
config <- Config <$> pure rootCreds
<*> newServerPool localServer []
<*> newManager defaultManagerSettings
content <- readFile "history"
let cmds = parse content
post config "cmds" $ mapM_ (\c -> writeSeries "commands" c) cmds
return ()
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Parser where
import Types
import Data.Generics
import Data.List.Split (splitOn)
import Control.Applicative ((<$>), (<*>))
import Data.Time hiding (parseTime)
import qualified Data.Text as T
import System.FilePath (takeFileName)
-- A customised version of language-sh is needed
import qualified Language.Sh.Parser as P
import qualified Language.Sh.Syntax as P
import qualified Language.Sh.Pretty as P
parseTime :: String -> Int
parseTime = (* 1000) . read
parseCommand :: String -> Maybe [T.Text]
parseCommand str =
case P.parse [] str of
Left _ -> Nothing
Right r -> notEmpty $ removeSpecial $ collectCommand r
where
removeSpecial = filter (`notElem` ["[", "[["])
notEmpty [] = Nothing
notEmpty x = Just x
collectCommand = everything (++) ([] `mkQ` getCommand)
getCommand :: P.Statement -> [T.Text]
getCommand (P.Statement (x:_) _ _) = [T.pack $ takeFileName $ P.pretty x]
getCommand _ = []
parse :: String -> [CommandEntry]
parse str = concatMap parseEntry $ tail $ splitOn "#" str
where
parseEntry str =
let (tstr, cmdstr') = break (=='\n') str
cmdstr = drop 1 cmdstr'
time = parseTime tstr
cmds = parseCommand cmdstr
in case cmds of
Nothing -> []
Just cs -> map (CommandEntry time) cs
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Types where
import Data.Text(Text)
import qualified Data.Vector as V
import Database.InfluxDB
data CommandEntry = CommandEntry {
time :: !Int
, cmd :: !Text
}
instance ToSeriesData CommandEntry where
toSeriesColumns _ = V.fromList ["time", "command"]
toSeriesPoints (CommandEntry time cmd) = V.fromList [toValue time, toValue cmd]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment