1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 06:41:45 +03:00
semantic/src/GitmonClient.hs

125 lines
4.2 KiB
Haskell
Raw Normal View History

{-# LANGUAGE RecordWildCards, BangPatterns, DeriveGeneric #-}
2017-02-15 04:42:35 +03:00
module GitmonClient where
import Data.Aeson
import Data.Aeson.Types
2017-02-24 01:03:26 +03:00
import Data.ByteString.Lazy (toStrict)
2017-03-01 02:27:33 +03:00
import Data.Text (pack, unpack, toLower)
import qualified Data.Yaml as Y
2017-02-24 01:03:26 +03:00
import GHC.Generics
2017-02-22 22:15:58 +03:00
import Git.Libgit2
import Network.Socket
import Network.Socket.ByteString (sendAll)
2017-02-24 01:03:26 +03:00
import Prelude
import Prologue hiding (toStrict)
import System.Clock
2017-03-01 02:27:33 +03:00
import System.Directory (getCurrentDirectory)
import System.Environment
import System.IO
2017-02-15 04:42:35 +03:00
data ProcIO = ProcIO {
read_bytes :: Integer
, write_bytes :: Integer
} deriving (Show, Generic)
instance FromJSON ProcIO
2017-02-23 00:34:28 +03:00
data ProcessStats =
ProcessBeforeStats { gitDir :: String
, program :: String
, realIP :: Maybe String
, repoID :: Maybe String
, repoName :: Maybe String
, userID :: Maybe String
, via :: String }
2017-02-23 00:34:28 +03:00
| ProcessAfterStats { cpu :: Integer
, diskReadBytes :: Integer
, diskWriteBytes :: Integer
, resultCode :: Integer } deriving (Generic, Show)
instance ToJSON ProcessStats where
2017-02-15 04:42:35 +03:00
toJSON = genericToJSON defaultOptions { fieldLabelModifier = camelTo2 '_' }
2017-02-24 01:04:24 +03:00
2017-02-25 04:37:09 +03:00
2017-02-15 04:42:35 +03:00
data GitmonCommand = Update
| Finish
| Schedule deriving (Generic, Show)
2017-02-15 04:42:35 +03:00
instance ToJSON GitmonCommand where
toJSON command = String $ case command of
Update -> "update"
Finish -> "finish"
Schedule -> "schedule"
2017-02-24 01:04:24 +03:00
2017-02-23 00:34:28 +03:00
data GitmonMsg = GitmonMsg { command :: GitmonCommand, stats :: ProcessStats } deriving (Show)
2017-02-15 04:42:35 +03:00
instance ToJSON GitmonMsg where
toJSON GitmonMsg{..} = object [
"command" .= command,
"data" .= stats
]
2017-02-24 03:42:07 +03:00
gitmonSocketAddr :: String
gitmonSocketAddr = "/tmp/gitstats.sock"
2017-02-24 03:53:55 +03:00
procFileAddr :: String
procFileAddr = "/proc/self/io"
clock :: Clock
clock = Realtime
2017-02-23 00:35:05 +03:00
processJSON :: GitmonCommand -> ProcessStats -> ByteString
processJSON command stats = toStrict . encode $ GitmonMsg command stats
2017-02-24 03:53:55 +03:00
type ProcInfo = Either Y.ParseException (Maybe ProcIO)
reportGitmon :: String -> Arguments -> ReaderT LgRepo IO a -> ReaderT LgRepo IO a
reportGitmon program Arguments{..} gitCommand = do
2017-02-22 22:15:58 +03:00
soc <- liftIO $ socket AF_UNIX Stream defaultProtocol
2017-02-24 03:42:07 +03:00
safeIO $ connect soc (SockAddrUnix gitmonSocketAddr)
2017-02-15 04:42:35 +03:00
safeIO $ sendAll soc (processJSON Update ProcessBeforeStats { gitDir = gitDir, via = "semantic-diff", program = program, realIP = realIP, repoID = repoID, repoName = repoName, userID = userID })
2017-02-15 04:42:35 +03:00
(startTime, beforeProcIOContents) <- liftIO collectStats
2017-02-23 01:29:50 +03:00
!result <- gitCommand
2017-02-15 04:42:35 +03:00
(afterTime, afterProcIOContents) <- liftIO collectStats
let (cpuTime, diskReadBytes', diskWriteBytes', resultCode') = procStats startTime afterTime beforeProcIOContents afterProcIOContents
safeIO $ sendAll soc (processJSON Finish ProcessAfterStats { cpu = cpuTime, diskReadBytes = diskReadBytes', diskWriteBytes = diskWriteBytes', resultCode = resultCode' })
2017-02-15 04:42:35 +03:00
2017-02-23 00:35:05 +03:00
safeIO $ close soc
2017-02-15 04:42:35 +03:00
2017-02-22 23:54:43 +03:00
return result
where safeIO :: MonadIO m => IO () -> m ()
safeIO command = liftIO $ command `catch` noop
2017-02-23 00:35:05 +03:00
2017-02-22 23:54:43 +03:00
noop :: IOException -> IO ()
noop _ = return ()
2017-02-24 03:56:02 +03:00
collectStats :: IO (TimeSpec, ProcInfo)
collectStats = do
time <- getTime clock
procIOContents <- Y.decodeFileEither procFileAddr :: IO ProcInfo
return (time, procIOContents)
procStats :: TimeSpec -> TimeSpec -> ProcInfo -> ProcInfo -> ( Integer, Integer, Integer, Integer )
procStats beforeTime afterTime beforeProcIOContents afterProcIOContents = ( cpuTime, diskReadBytes, diskWriteBytes, resultCode )
2017-02-24 03:56:02 +03:00
where
cpuTime = toNanoSecs afterTime - toNanoSecs beforeTime
2017-02-24 03:56:02 +03:00
beforeDiskReadBytes = either (const 0) (maybe 0 read_bytes) beforeProcIOContents
afterDiskReadBytes = either (const 0) (maybe 0 read_bytes) afterProcIOContents
beforeDiskWriteBytes = either (const 0) (maybe 0 write_bytes) beforeProcIOContents
afterDiskWriteBytes = either (const 0) (maybe 0 write_bytes) afterProcIOContents
diskReadBytes = afterDiskReadBytes - beforeDiskReadBytes
diskWriteBytes = afterDiskWriteBytes - beforeDiskWriteBytes
resultCode = 0