2017-02-24 01:03:01 +03:00
|
|
|
{-# 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
|
2017-02-22 22:15:32 +03:00
|
|
|
import Network.Socket
|
|
|
|
import Network.Socket.ByteString (sendAll)
|
2017-02-24 01:03:26 +03:00
|
|
|
import Prelude
|
|
|
|
import Prologue hiding (toStrict)
|
2017-02-24 01:01:53 +03:00
|
|
|
import System.Clock
|
2017-03-01 02:27:33 +03:00
|
|
|
import System.Directory (getCurrentDirectory)
|
|
|
|
import System.Environment
|
2017-02-15 04:42:35 +03:00
|
|
|
|
2017-02-24 01:03:01 +03:00
|
|
|
data ProcIO = ProcIO {
|
|
|
|
read_bytes :: Integer
|
|
|
|
, write_bytes :: Integer
|
|
|
|
} deriving (Show, Generic)
|
|
|
|
|
|
|
|
instance FromJSON ProcIO
|
|
|
|
|
|
|
|
|
2017-03-01 02:46:29 +03:00
|
|
|
data ProcessData =
|
|
|
|
ProcessUpdateData { gitDir :: String
|
|
|
|
, program :: String
|
|
|
|
, realIP :: Maybe String
|
|
|
|
, repoID :: Maybe String
|
|
|
|
, repoName :: Maybe String
|
|
|
|
, userID :: Maybe String
|
|
|
|
, via :: String }
|
|
|
|
| ProcessScheduleData
|
|
|
|
| ProcessFinishData { cpu :: Integer
|
2017-02-23 00:34:28 +03:00
|
|
|
, diskReadBytes :: Integer
|
|
|
|
, diskWriteBytes :: Integer
|
|
|
|
, resultCode :: Integer } deriving (Generic, Show)
|
|
|
|
|
2017-03-01 02:46:29 +03:00
|
|
|
instance ToJSON ProcessData 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
|
2017-03-01 02:28:05 +03:00
|
|
|
| Schedule deriving (Generic, Show)
|
2017-02-15 04:42:35 +03:00
|
|
|
|
|
|
|
instance ToJSON GitmonCommand where
|
2017-03-01 02:28:20 +03:00
|
|
|
toJSON = genericToJSON defaultOptions { constructorTagModifier = unpack . toLower . pack }
|
2017-02-15 04:42:35 +03:00
|
|
|
|
2017-02-24 01:04:24 +03:00
|
|
|
|
2017-03-01 02:46:29 +03:00
|
|
|
data GitmonMsg = GitmonMsg { command :: GitmonCommand, processData :: ProcessData } deriving (Show)
|
2017-02-15 04:42:35 +03:00
|
|
|
|
|
|
|
instance ToJSON GitmonMsg where
|
2017-03-02 21:22:02 +03:00
|
|
|
toJSON GitmonMsg{..} = object ["command" .= command, "data" .= processData]
|
2017-02-24 01:01:53 +03:00
|
|
|
|
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"
|
|
|
|
|
2017-02-24 01:01:53 +03:00
|
|
|
clock :: Clock
|
|
|
|
clock = Realtime
|
|
|
|
|
2017-03-01 02:46:29 +03:00
|
|
|
processJSON :: GitmonCommand -> ProcessData -> ByteString
|
2017-03-02 01:06:58 +03:00
|
|
|
processJSON command processData = (toStrict . encode $ GitmonMsg command processData) <> "\n"
|
2017-02-23 00:35:05 +03:00
|
|
|
|
2017-02-24 03:53:55 +03:00
|
|
|
type ProcInfo = Either Y.ParseException (Maybe ProcIO)
|
|
|
|
|
2017-03-02 01:06:58 +03:00
|
|
|
safeIO :: MonadIO m => IO () -> m ()
|
|
|
|
safeIO command = liftIO $ command `catch` noop
|
|
|
|
|
2017-03-02 21:22:02 +03:00
|
|
|
safeIOValue :: MonadIO m => IO a -> m (Maybe a)
|
|
|
|
safeIOValue command = liftIO $ (Just <$> command) `catch` noopValue
|
|
|
|
|
2017-03-02 01:06:58 +03:00
|
|
|
noop :: IOException -> IO ()
|
2017-03-02 21:22:02 +03:00
|
|
|
noop _ = pure ()
|
|
|
|
|
|
|
|
noopValue :: IOException -> IO (Maybe a)
|
|
|
|
noopValue _ = pure Nothing
|
2017-03-02 01:06:58 +03:00
|
|
|
|
2017-03-01 02:31:19 +03:00
|
|
|
reportGitmon :: String -> ReaderT LgRepo IO a -> ReaderT LgRepo IO a
|
|
|
|
reportGitmon program gitCommand = do
|
2017-03-02 21:22:02 +03:00
|
|
|
maybeSoc <- safeIOValue $ socket AF_UNIX Stream defaultProtocol
|
|
|
|
case maybeSoc of
|
|
|
|
Nothing -> gitCommand
|
|
|
|
Just soc -> do
|
|
|
|
safeIO $ connect soc (SockAddrUnix gitmonSocketAddr)
|
|
|
|
result <- reportGitmon' soc program gitCommand
|
|
|
|
safeIO $ close soc
|
|
|
|
pure result
|
2017-03-02 01:06:58 +03:00
|
|
|
|
|
|
|
reportGitmon' :: Socket -> String -> ReaderT LgRepo IO a -> ReaderT LgRepo IO a
|
|
|
|
reportGitmon' soc program gitCommand = do
|
2017-03-02 21:22:02 +03:00
|
|
|
(gitDir, realIP, repoID, repoName, userID) <- liftIO loadEnvVars
|
2017-03-01 02:46:29 +03:00
|
|
|
safeIO $ sendAll soc (processJSON Update (ProcessUpdateData gitDir program realIP repoID repoName userID "semantic-diff"))
|
|
|
|
safeIO $ sendAll soc (processJSON Schedule ProcessScheduleData)
|
2017-02-24 04:08:01 +03:00
|
|
|
(startTime, beforeProcIOContents) <- liftIO collectStats
|
2017-02-23 01:29:50 +03:00
|
|
|
!result <- gitCommand
|
2017-02-24 04:08:01 +03:00
|
|
|
(afterTime, afterProcIOContents) <- liftIO collectStats
|
|
|
|
let (cpuTime, diskReadBytes', diskWriteBytes', resultCode') = procStats startTime afterTime beforeProcIOContents afterProcIOContents
|
2017-03-01 02:46:29 +03:00
|
|
|
safeIO $ sendAll soc (processJSON Finish ProcessFinishData { cpu = cpuTime, diskReadBytes = diskReadBytes', diskWriteBytes = diskWriteBytes', resultCode = resultCode' })
|
2017-03-02 21:22:02 +03:00
|
|
|
pure result
|
2017-02-22 23:54:43 +03:00
|
|
|
|
2017-03-02 01:06:58 +03:00
|
|
|
where collectStats :: IO (TimeSpec, ProcInfo)
|
2017-02-24 04:08:01 +03:00
|
|
|
collectStats = do
|
|
|
|
time <- getTime clock
|
|
|
|
procIOContents <- Y.decodeFileEither procFileAddr :: IO ProcInfo
|
2017-03-02 21:22:02 +03:00
|
|
|
pure (time, procIOContents)
|
2017-02-24 04:08:01 +03:00
|
|
|
|
|
|
|
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
|
2017-02-24 04:08:01 +03:00
|
|
|
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
|
|
|
|
|
2017-03-01 02:30:42 +03:00
|
|
|
loadEnvVars :: IO (String, Maybe String, Maybe String, Maybe String, Maybe String)
|
|
|
|
loadEnvVars = do
|
|
|
|
pwd <- getCurrentDirectory
|
|
|
|
gitDir <- fromMaybe pwd <$> lookupEnv "GIT_DIR"
|
|
|
|
realIP <- lookupEnv "GIT_SOCKSTAT_VAR_real_ip"
|
|
|
|
repoID <- lookupEnv "GIT_SOCKSTAT_VAR_repo_id"
|
|
|
|
repoName <- lookupEnv "GIT_SOCKSTAT_VAR_repo_name"
|
|
|
|
userID <- lookupEnv "GIT_SOCKSTAT_VAR_user_id"
|
2017-03-02 21:22:02 +03:00
|
|
|
pure (gitDir, realIP, repoID, repoName, userID)
|