module HEyefi.AppSpec where import Control.Concurrent.STM import Data.ByteString.Lazy (toStrict) import Data.CaseInsensitive as CI import Data.Text (Text, isInfixOf) import Data.Text.Encoding (decodeUtf8) import HEyefi.App import HEyefi.Config import HEyefi.SpecPrelude import Network.HTTP.Types.Method import Network.Wai (Application) import Network.Wai.Test (SResponse (simpleBody)) import Test.Hspec.Wai import Test.Hspec.Wai.Internal spec :: Spec spec = do describe "StartSession" ( it "should return expected body" ( do a <- app' action <- runWaiSession sampleStartSessionRequest a responseBodyContains action sampleStartSessionResponse1 `shouldBe` True responseBodyContains action sampleStartSessionResponse2 `shouldBe` True)) with app' ( do describe "MarkLastPhotoInRoll" ( it "should respond with status 200" ( sampleMarkLastPhotoRequest `shouldRespondWith` sampleMarkLastPhotoInRollResponse {matchStatus = 200})) describe "StartSession" ( it "should respond with status 200" ( sampleStartSessionRequest `shouldRespondWith` 200)) describe "GetPhotoStatus" ( it "should respond with status 200" ( sampleStartSessionRequest `shouldRespondWith` 200))) responseBodyContains :: SResponse -> Text -> Bool responseBodyContains r t = t `isInfixOf` (decodeUtf8 . toStrict) (simpleBody r) app' :: IO Application app' = do sharedConfig <- atomically (newTVar (insertCard "0018562de4ce" "36d61e4e7403a0586702c9159892a062" emptyConfig)) return (app sharedConfig) sampleMarkLastPhotoRequest :: WaiSession SResponse sampleMarkLastPhotoRequest = request methodPost "/" [(CI.mk "SoapAction", "\"urn:MarkLastPhotoInRoll\"")] "0018564177290" sampleMarkLastPhotoInRollResponse :: ResponseMatcher sampleMarkLastPhotoInRollResponse = "" sampleStartSessionRequest :: WaiSession SResponse sampleStartSessionRequest = request methodPost "/" [(CI.mk "SoapAction", "\"urn:StartSession\"")] "0018562de4ce6eb0444343c1953e47fb28181bb4e47f341356903384" sampleStartSessionResponse1 :: Text sampleStartSessionResponse1 = "f9d03ddcce53582ff10075577e522373" sampleStartSessionResponse2 :: Text sampleStartSessionResponse2 = "341356903384true" sampleGetPhotoRequest :: WaiSession SResponse sampleGetPhotoRequest = request methodPost "/" [(CI.mk "SoapAction", "\"urn:GetPhotoRequest\"")] "7daa9ecf3a9f135f5bb30541ed84fcfb0018562de4ceIMG_2195.JPG.tar125952736ffb7fa20f1708fd300c58c0aabb614"