This commit is contained in:
Chris Allen 2014-04-06 18:29:46 -05:00
parent 1ed7096774
commit 886ef3ffdd
4 changed files with 68 additions and 5 deletions

View File

@ -8,6 +8,9 @@ module Database.Bloodhound.Client
, Server(..)
, defaultIndexSettings
, indexDocument
, getDocument
, documentExists
, deleteDocument
)
where

12
Makefile Normal file
View File

@ -0,0 +1,12 @@
test:
cabal install --enable-tests
build:
cabal build
test-repl:
cabal repl tests
repl:
cabal repl

View File

@ -43,7 +43,14 @@ test-suite tests
hs-source-dirs: tests
build-depends: base,
bloodhound,
hspec >= 1.9,
http-conduit,
http-types
http-types,
hspec >= 1.9,
QuickCheck >= 2.5,
derive >= 2.5,
text >= 0.11,
time >= 1.4,
aeson >= 0.7,
random >= 1.0,
quickcheck-instances >= 0.3
default-language: Haskell2010

View File

@ -1,20 +1,61 @@
{-# LANGUAGE DeriveGeneric, TemplateHaskell #-}
module Main where
import Database.Bloodhound.Client
import Data.Aeson
import Data.DeriveTH
import Data.Maybe (fromJust)
import Data.Time.Clock (UTCTime)
import Data.Text (Text)
import GHC.Generics (Generic)
import Network.HTTP.Conduit
import qualified Network.HTTP.Types.Status as NHTS
import System.Random
import Test.Hspec
import Test.QuickCheck
import Test.QuickCheck.Gen
import Test.QuickCheck.Instances
testServer = Server "http://localhost:9200"
testIndex = "twitter"
validateStatus resp expected = (NHTS.statusCode $ responseStatus resp) `shouldBe` (expected :: Int)
createExampleIndex = createIndex testServer defaultIndexSettings testIndex
deleteExampleIndex = deleteIndex testServer testIndex
data Tweet = Tweet { user :: Text
, postDate :: UTCTime
, message :: Text }
deriving (Eq, Generic, Show)
instance ToJSON Tweet
instance FromJSON Tweet
$(derive makeArbitrary ''Tweet)
newTweet :: IO Tweet
newTweet = do
g <- newStdGen
let seed = head (take 1 $ randoms g)
return (unGen arbitrary (mkStdGen seed) 100)
main :: IO ()
main = hspec $ do
describe "index API" $ do
describe "index create/delete API" $ do
it "creates and then deletes the requested index" $ do
resp <- createIndex testServer defaultIndexSettings testIndex
deleteResp <- deleteIndex testServer testIndex
-- priming state.
_ <- deleteExampleIndex
resp <- createExampleIndex
deleteResp <- deleteExampleIndex
validateStatus resp 200
validateStatus deleteResp 200
describe "document API" $ do
it "indexes, gets, and then deletes the generated document" $ do
tweet <- newTweet
let encoded = encode tweet
created <- createExampleIndex
docCreated <- indexDocument (Server "http://localhost:9200") "twitter" "tweet" tweet "1"
docInserted <- getDocument (Server "http://localhost:9200") "twitter" "tweet" "1"
let newTweet = decode (responseBody docInserted) :: Maybe Tweet
deleted <- deleteExampleIndex
(Just tweet) `shouldBe` newTweet