rename RQBody to JsonBody everywhere

This commit is contained in:
Alp Mestanogullari 2014-10-28 15:29:07 +01:00
parent fc67c3b7aa
commit 9b375b137f
5 changed files with 16 additions and 16 deletions

View file

@ -51,7 +51,7 @@ instance ToSample Greet where
-- API specification
type TestApi =
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get Greet
:<|> "greet" :> RQBody Greet :> Post Greet
:<|> "greet" :> JsonBody Greet :> Post Greet
:<|> "delete" :> Capture "greetid" Text :> Delete
testApi :: Proxy TestApi

View file

@ -22,11 +22,11 @@ library
Servant.API.Capture
Servant.API.Delete
Servant.API.Get
Servant.API.JsonBody
Servant.API.Post
Servant.API.Put
Servant.API.QueryParam
Servant.API.Raw
Servant.API.RQBody
Servant.API.Sub
Servant.API.Union
Servant.Utils.Text

View file

@ -9,10 +9,10 @@ module Servant.API (
-- * Accessing information from the request
-- | Capturing parts of the url path as parsed values: @'Capture'@
module Servant.API.Capture,
-- | Retrieving parameters from the query part of the 'URI': @'QueryParam'@
-- | Accessing the request body as a JSON-encoded type: @'JsonBody'@
module Servant.API.JsonBody,
-- | Retrieving parameters from the query string of the 'URI': @'QueryParam'@
module Servant.API.QueryParam,
-- | Accessing the request's body: @'RQBody'@
module Servant.API.RQBody,
-- * Actual endpoints, distinguished by HTTP method
-- | GET requests
@ -28,9 +28,9 @@ module Servant.API (
import Servant.API.Capture
import Servant.API.Delete
import Servant.API.Get
import Servant.API.JsonBody
import Servant.API.Post
import Servant.API.Put
import Servant.API.QueryParam
import Servant.API.RQBody
import Servant.API.Sub
import Servant.API.Union

View file

@ -3,7 +3,7 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Servant.API.RQBody where
module Servant.API.JsonBody where
import Control.Applicative
import Data.Aeson
@ -15,12 +15,12 @@ import Servant.Docs
import Servant.Server
-- * Request Body support
data RQBody a
data JsonBody a
instance (FromJSON a, HasServer sublayout)
=> HasServer (RQBody a :> sublayout) where
=> HasServer (JsonBody a :> sublayout) where
type Server (RQBody a :> sublayout) =
type Server (JsonBody a :> sublayout) =
a -> Server sublayout
route Proxy subserver request respond = do
@ -30,9 +30,9 @@ instance (FromJSON a, HasServer sublayout)
Just v -> route (Proxy :: Proxy sublayout) (subserver v) request respond
instance (ToJSON a, HasClient sublayout)
=> HasClient (RQBody a :> sublayout) where
=> HasClient (JsonBody a :> sublayout) where
type Client (RQBody a :> sublayout) =
type Client (JsonBody a :> sublayout) =
a -> Client sublayout
clientWithRoute Proxy req body =
@ -40,7 +40,7 @@ instance (ToJSON a, HasClient sublayout)
setRQBody (encode body) req
instance (ToSample a, HasDocs sublayout)
=> HasDocs (RQBody a :> sublayout) where
=> HasDocs (JsonBody a :> sublayout) where
docsFor Proxy (endpoint, action) =
docsFor sublayoutP (endpoint, action')

View file

@ -22,10 +22,10 @@ import Test.Hspec.Wai
import Servant.API.Capture
import Servant.API.Get
import Servant.API.JsonBody
import Servant.API.Post
import Servant.API.QueryParam
import Servant.API.Raw
import Servant.API.RQBody
import Servant.API.Sub
import Servant.API.Union
import Servant.Server
@ -141,13 +141,13 @@ queryParamSpec = do
}
type PostApi = RQBody Person :> (Post Integer)
type PostApi = JsonBody Person :> Post Integer
postApi :: Proxy PostApi
postApi = Proxy
postSpec :: Spec
postSpec = do
describe "Servant.API.Post and .RQBody" $ do
describe "Servant.API.Post and .JsonBody" $ do
with (return (serve postApi (return . age))) $ do
it "allows to POST a Person" $ do
post "/" (encode alice) `shouldRespondWith` "42"{