1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 18:23:44 +03:00
semantic/test/GitmonClientSpec.hs

112 lines
4.7 KiB
Haskell
Raw Normal View History

2017-03-02 01:06:58 +03:00
module GitmonClientSpec where
import Data.Aeson
import Data.Aeson.Types
import Data.ByteString.Char8 (split, ByteString)
import Data.Foldable
2017-03-02 01:06:58 +03:00
import Data.Maybe (fromJust)
import Data.Text hiding (split, take)
import Git.Libgit2
import Git.Repository
import Git.Types hiding (Object)
import GitmonClient
import Network.Socket hiding (recv)
import Network.Socket.ByteString
2017-03-02 01:48:39 +03:00
import Prelude hiding (lookup)
2017-03-03 00:16:38 +03:00
import Prologue (liftIO, runReaderT)
2017-03-02 01:48:39 +03:00
import System.Environment (setEnv)
2017-03-03 00:16:38 +03:00
import Test.Hspec hiding (shouldBe, shouldSatisfy, shouldThrow, anyErrorCall)
2017-03-02 01:06:58 +03:00
import Test.Hspec.Expectations.Pretty
import Control.Exception
2017-03-02 01:06:58 +03:00
spec :: Spec
2017-03-03 01:19:29 +03:00
spec = parallel $ do
2017-03-02 01:06:58 +03:00
describe "gitmon" $ do
let wd = "test/fixtures/git/examples/all-languages.git"
it "receives commands in order" . withSocketPair $ \(_, server, socketFactory) ->
withRepository lgFactory wd $ do
2017-03-03 00:16:38 +03:00
liftIO $ sendAll server "continue"
2017-03-02 01:06:58 +03:00
object <- parseObjOid (pack "dfac8fd681b0749af137aebf3203e77a06fbafc2")
commit <- reportGitmon' socketFactory "cat-file" $ lookupCommit object
2017-03-02 01:06:58 +03:00
info <- liftIO $ recv server 1024
let [update, schedule, finish] = infoToCommands info
liftIO $ shouldBe (commitOid commit) object
liftIO $ shouldBe update (Just "update")
liftIO $ shouldBe schedule (Just "schedule")
liftIO $ shouldBe finish (Just "finish")
it "receives update command with correct data" . withSocketPair $ \(_, server, socketFactory) ->
2017-03-02 01:48:39 +03:00
withRepository lgFactory wd $ do
liftIO $ setEnv "GIT_DIR" wd
liftIO $ setEnv "GIT_SOCKSTAT_VAR_real_ip" "127.0.0.1"
liftIO $ setEnv "GIT_SOCKSTAT_VAR_repo_name" "examples/all-languages"
2017-03-03 00:16:38 +03:00
liftIO $ sendAll server "continue"
2017-03-02 01:48:39 +03:00
object <- parseObjOid (pack "dfac8fd681b0749af137aebf3203e77a06fbafc2")
commit <- reportGitmon' socketFactory "cat-file" $ lookupCommit object
2017-03-02 01:48:39 +03:00
info <- liftIO $ recv server 1024
let [updateData, _, finishData] = infoToData info
2017-03-02 01:48:39 +03:00
liftIO $ shouldBe (commitOid commit) object
liftIO $ shouldBe (either id gitDir updateData) wd
liftIO $ shouldBe (either id program updateData) "cat-file"
liftIO $ shouldBe (either Just realIP updateData) (Just "127.0.0.1")
liftIO $ shouldBe (either Just repoName updateData) (Just "examples/all-languages")
liftIO $ shouldBe (either id via updateData) "semantic-diff"
liftIO $ shouldSatisfy (either (const (-1)) cpu finishData) (>= 0)
liftIO $ shouldSatisfy (either (const (-1)) diskReadBytes finishData) (>= 0)
liftIO $ shouldSatisfy (either (const (-1)) diskWriteBytes finishData) (>= 0)
liftIO $ shouldSatisfy (either (const (-1)) resultCode finishData) (>= 0)
2017-03-02 01:48:39 +03:00
it "returns the correct git result if the socket is unavailable" . withSocketPair $ \(client, server, socketFactory) ->
withRepository lgFactory wd $ do
liftIO $ close client
object <- parseObjOid (pack "dfac8fd681b0749af137aebf3203e77a06fbafc2")
commit <- reportGitmon' socketFactory "cat-file" $ lookupCommit object
info <- liftIO $ recv server 1024
liftIO $ shouldBe (commitOid commit) object
liftIO $ shouldBe "" info
it "throws if schedule response is fail" . withSocketPair $ \(_, server, socketFactory) ->
2017-03-03 00:16:38 +03:00
withRepository lgFactory wd $ do
repo <- getRepository
liftIO $ sendAll server "fail too busy"
object <- parseObjOid (pack "dfac8fd681b0749af137aebf3203e77a06fbafc2")
liftIO $ shouldThrow (runReaderT (reportGitmon' socketFactory "cat-file" (lookupCommit object)) repo) anyErrorCall
2017-03-03 00:16:38 +03:00
withSocketPair :: ((Socket, Socket, SocketFactory) -> IO c) -> IO c
withSocketPair = bracket create release
where
create = do
(client, server) <- socketPair AF_UNIX Stream defaultProtocol
pure (client, server, SocketFactory (\f -> f client))
release (client, server, _) = do
close client
close server
2017-03-02 01:06:58 +03:00
infoToCommands :: ByteString -> [Maybe Text]
infoToCommands input = command' . toObject <$> Prelude.take 3 (split '\n' input)
where
command' :: Object -> Maybe Text
command' = parseMaybe (.: "command")
infoToData :: ByteString -> [Either String ProcessData]
2017-03-02 01:48:39 +03:00
infoToData input = data' . toObject <$> Prelude.take 3 (split '\n' input)
where data' = parseEither parser
parser o = do
dataO <- o .: "data"
2017-03-07 21:33:18 +03:00
asum [ ProcessUpdateData <$> (dataO .: "git_dir") <*> (dataO .: "program") <*> (dataO .:? "real_ip") <*> (dataO .:? "repo_name") <*> (dataO .: "via")
, ProcessFinishData <$> (dataO .: "cpu") <*> (dataO .: "disk_read_bytes") <*> (dataO .: "disk_write_bytes") <*> (dataO .: "result_code")
, pure ProcessScheduleData
]
2017-03-02 01:06:58 +03:00
2017-03-02 01:48:39 +03:00
toObject :: ByteString -> Object
toObject = fromJust . decodeStrict