servant/servant-server/test/Servant/Server/CombinatorUtilsSpec.hs

118 lines
3.5 KiB
Haskell
Raw Normal View History

2016-10-23 19:36:45 +02:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Server.CombinatorUtilsSpec where
import Control.Concurrent
2016-10-23 20:00:52 +02:00
import Data.ByteString.Builder
2016-10-23 19:36:45 +02:00
import Data.ByteString.Lazy
import Data.Monoid
import Data.Proxy
import Data.String.Conversions
2016-10-23 20:00:52 +02:00
import Data.Text
2016-10-23 19:36:45 +02:00
import Network.HTTP.Types
import Network.Wai
import Network.Wai.Internal
import Test.Hspec
import Servant.API
import Servant.Server
import Servant.Server.CombinatorUtils
runApp :: Application -> Request -> IO Response
runApp app req = do
mvar <- newMVar Nothing
app req $ \ response -> do
modifyMVar mvar $ \ Nothing ->
return $ (Just response, ResponseReceived)
modifyMVar mvar $ \mResponse -> do
case mResponse of
Nothing -> error "shouldn't happen"
Just response -> return (Just response, response)
responseBodyLbs :: Response -> IO ByteString
responseBodyLbs response = do
let (_, _, action) = responseToStream response
action $ \ streamingBody -> do
mvar <- newMVar ""
streamingBody
(\ builder -> modifyMVar_ mvar $ \ acc ->
return $ acc <> toLazyByteString builder)
(return ())
readMVar mvar
spec :: Spec
spec = do
it "allows to write a combinator by providing a function (Request -> a)" $ do
let server = return
2016-10-23 20:00:52 +02:00
app = serve (Proxy :: Proxy (FooHeader :> Get' String)) server
2016-10-23 19:36:45 +02:00
request = defaultRequest{
requestHeaders =
2016-10-23 20:00:52 +02:00
("FooHeader", "foo") :
2016-10-23 19:36:45 +02:00
requestHeaders defaultRequest
}
response <- runApp app request
responseBodyLbs response `shouldReturn` "\"foo\""
it "allows to write a combinator the errors out" $ do
let server = return
2016-10-23 20:00:52 +02:00
app = serve (Proxy :: Proxy (FooHeader :> Get' String)) server
2016-10-23 19:36:45 +02:00
request = defaultRequest
response <- runApp app request
responseStatus response `shouldBe` status400
2016-10-23 20:00:52 +02:00
it "allows to write capture combinators" $ do
let server = return
app = serve (Proxy :: Proxy (StringCapture :> Get' String)) server
request = defaultRequest{
rawPathInfo = "/foo",
pathInfo = ["foo"]
}
response <- runApp app request
responseBodyLbs response `shouldReturn` "\"foo\""
it "allows to pick the request check phase" $ do
pending
it "allows to write streaming combinators for request bodies" $ do
pending
it "disallows to access the request body unless in the checkBody phase" $ do
pending
it "allows to access the context" $ do
pending
it "allows to write combinators without args" $ do
pending
it "allows to implement combinators based in terms of existing combinators" $ do
2016-10-23 19:36:45 +02:00
pending
type Get' = Get '[JSON]
2016-10-23 20:00:52 +02:00
data FooHeader
2016-10-23 19:36:45 +02:00
2016-10-23 20:00:52 +02:00
instance HasServer api context => HasServer (FooHeader :> api) context where
type ServerT (FooHeader :> api) m = String -> ServerT api m
2016-10-23 19:36:45 +02:00
route = argumentCombinator getCustom
getCustom :: Request -> RouteResult String
2016-10-23 20:00:52 +02:00
getCustom request = case lookup "FooHeader" (requestHeaders request) of
2016-10-23 19:36:45 +02:00
Nothing -> FailFatal err400
Just l -> Route $ cs l
2016-10-23 20:00:52 +02:00
data StringCapture
instance HasServer api context => HasServer (StringCapture :> api) context where
type ServerT (StringCapture :> api) m = String -> ServerT api m
route = captureCombinator getCapture
getCapture :: Text -> RouteResult String
getCapture = Route . cs