rename GetParam to QueryParam everywhere

This commit is contained in:
Alp Mestanogullari 2014-10-28 15:06:47 +01:00
parent 641ee69eba
commit fc67c3b7aa
6 changed files with 53 additions and 47 deletions

View File

@ -37,11 +37,11 @@ instance ToCapture (Capture "name" Text) where
instance ToCapture (Capture "greetid" Text) where
toCapture _ = DocCapture "greetid" "identifier of the greet msg to remove"
instance ToParam (GetParam "capital" Bool) where
instance ToParam (QueryParam "capital" Bool) where
toParam _ =
DocGetParam "capital"
["true", "false"]
"Get the greeting message in uppercase (true) or not (false). Default is false."
DocQueryParam "capital"
["true", "false"]
"Get the greeting message in uppercase (true) or not (false). Default is false."
instance ToSample Greet where
toSample Proxy = Just (encode g)
@ -50,7 +50,7 @@ instance ToSample Greet where
-- API specification
type TestApi =
"hello" :> Capture "name" Text :> GetParam "capital" Bool :> Get Greet
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get Greet
:<|> "greet" :> RQBody Greet :> Post Greet
:<|> "delete" :> Capture "greetid" Text :> Delete

View File

@ -22,9 +22,9 @@ library
Servant.API.Capture
Servant.API.Delete
Servant.API.Get
Servant.API.GetParam
Servant.API.Post
Servant.API.Put
Servant.API.QueryParam
Servant.API.Raw
Servant.API.RQBody
Servant.API.Sub

View File

@ -9,8 +9,8 @@ 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': @'GetParam'@
module Servant.API.GetParam,
-- | Retrieving parameters from the query part of the 'URI': @'QueryParam'@
module Servant.API.QueryParam,
-- | Accessing the request's body: @'RQBody'@
module Servant.API.RQBody,
@ -28,9 +28,9 @@ module Servant.API (
import Servant.API.Capture
import Servant.API.Delete
import Servant.API.Get
import Servant.API.GetParam
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

@ -4,7 +4,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Servant.API.GetParam where
module Servant.API.QueryParam where
import Data.Proxy
import Data.String.Conversions
@ -18,13 +18,19 @@ import Servant.Docs
import Servant.Server
import Servant.Utils.Text
-- * GET params support (i.e query string arguments)
data GetParam sym a
-- * Query String parameter lookup
-- | Your must implement:
--
-- - a @'FromText' a@ instance for serving
-- - a @'ToText' a@ instance for (client-side) querying
-- - a @'ToParam' ('QueryParam' sym a)@ instance for automatic documentation generation
data QueryParam sym a
instance (KnownSymbol sym, FromText a, HasServer sublayout)
=> HasServer (GetParam sym a :> sublayout) where
=> HasServer (QueryParam sym a :> sublayout) where
type Server (GetParam sym a :> sublayout) =
type Server (QueryParam sym a :> sublayout) =
Maybe a -> Server sublayout
route Proxy subserver request respond = do
@ -41,9 +47,9 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout)
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, ToText a, HasClient sublayout)
=> HasClient (GetParam sym a :> sublayout) where
=> HasClient (QueryParam sym a :> sublayout) where
type Client (GetParam sym a :> sublayout) =
type Client (QueryParam sym a :> sublayout) =
Maybe a -> Client sublayout
-- if mparam = Nothing, we don't add it to the query string
@ -55,12 +61,12 @@ instance (KnownSymbol sym, ToText a, HasClient sublayout)
pname' = symbolVal (Proxy :: Proxy sym)
mparamText = fmap toText mparam
instance (KnownSymbol sym, ToParam (GetParam sym a), HasDocs sublayout)
=> HasDocs (GetParam sym a :> sublayout) where
instance (KnownSymbol sym, ToParam (QueryParam sym a), HasDocs sublayout)
=> HasDocs (QueryParam sym a :> sublayout) where
docsFor Proxy (endpoint, action) =
docsFor sublayoutP (endpoint, action')
where sublayoutP = Proxy :: Proxy sublayout
paramP = Proxy :: Proxy (GetParam sym a)
paramP = Proxy :: Proxy (QueryParam sym a)
action' = over params (|> toParam paramP) action

View File

@ -56,11 +56,11 @@
-- >
-- > where g = Greet "Hello, haskeller!"
-- >
-- > instance ToParam (GetParam "capital" Bool) where
-- > instance ToParam (QueryParam "capital" Bool) where
-- > toParam _ =
-- > DocGetParam "capital"
-- > ["true", "false"]
-- > "Get the greeting message in uppercase (true) or not (false). Default is false."
-- > DocQueryParam "capital"
-- > ["true", "false"]
-- > "Get the greeting message in uppercase (true) or not (false). Default is false."
-- >
-- > instance ToCapture (Capture "name" Text) where
-- > toCapture _ = DocCapture "name" "name of the person to greet"
@ -70,7 +70,7 @@
-- >
-- > -- API specification
-- > type TestApi =
-- > "hello" :> Capture "name" Text :> GetParam "capital" Bool :> Get Greet
-- > "hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get Greet
-- > :<|> "greet" :> RQBody Greet :> Post Greet
-- > :<|> "delete" :> Capture "greetid" Text :> Delete
-- >
@ -95,7 +95,7 @@ module Servant.Docs
, Endpoint, path, method, defEndpoint
, API, emptyAPI
, DocCapture(..), capSymbol, capDesc
, DocGetParam(..), paramName, paramValues, paramDesc
, DocQueryParam(..), paramName, paramValues, paramDesc
, Response, respStatus, respBody, defResponse
, Action, captures, params, rqbody, response, defAction
, single
@ -190,12 +190,12 @@ data DocCapture = DocCapture
, _capDesc :: String -- user supplied
} deriving (Eq, Show)
-- | A type to represent /GET/ parameters. Holds its name,
-- | A type to represent a /GET/ parameter from the Query String. Holds its name,
-- the possible values (leave empty if there isn't a finite number of them),
-- and a description of how it influences the output or behavior.
--
-- Write a 'ToParam' instance for your GET parameter types
data DocGetParam = DocGetParam
data DocQueryParam = DocQueryParam
{ _paramName :: String -- type supplied
, _paramValues :: [String] -- user supplied
, _paramDesc :: String -- user supplied
@ -243,7 +243,7 @@ defResponse = Response 200 Nothing
-- to transform an action and add some information to it.
data Action = Action
{ _captures :: [DocCapture] -- type collected + user supplied info
, _params :: [DocGetParam] -- type collected + user supplied info
, _params :: [DocQueryParam] -- type collected + user supplied info
, _rqbody :: Maybe ByteString -- user supplied
, _response :: Response -- user supplied
} deriving (Eq, Show)
@ -273,7 +273,7 @@ single = HM.singleton
-- gimme some lenses
makeLenses ''Endpoint
makeLenses ''DocCapture
makeLenses ''DocGetParam
makeLenses ''DocQueryParam
makeLenses ''Response
makeLenses ''Action
@ -319,13 +319,13 @@ class ToJSON a => ToSample a where
--
-- Example of an instance:
--
-- > instance ToParam (GetParam "capital" Bool) where
-- > instance ToParam (QueryParam "capital" Bool) where
-- > toParam _ =
-- > DocGetParam "capital"
-- > ["true", "false"]
-- > "Get the greeting message in uppercase (true) or not (false). Default is false."
-- > DocQueryParam "capital"
-- > ["true", "false"]
-- > "Get the greeting message in uppercase (true) or not (false). Default is false."
class ToParam t where
toParam :: Proxy t -> DocGetParam
toParam :: Proxy t -> DocQueryParam
-- | The class that helps us automatically get documentation
-- for URL captures.
@ -364,7 +364,7 @@ printMarkdown = imapM_ printEndpoint
captureStr cap =
putStrLn $ "- *" ++ (cap ^. capSymbol) ++ "*: " ++ (cap ^. capDesc)
paramsStr :: [DocGetParam] -> IO ()
paramsStr :: [DocQueryParam] -> IO ()
paramsStr [] = return ()
paramsStr l = do
putStrLn "**GET Parameters**: "

View File

@ -22,8 +22,8 @@ import Test.Hspec.Wai
import Servant.API.Capture
import Servant.API.Get
import Servant.API.GetParam
import Servant.API.Post
import Servant.API.QueryParam
import Servant.API.Raw
import Servant.API.RQBody
import Servant.API.Sub
@ -67,7 +67,7 @@ spec :: Spec
spec = do
captureSpec
getSpec
getParamSpec
queryParamSpec
postSpec
rawSpec
unionSpec
@ -117,19 +117,19 @@ getSpec = do
post "/" "" `shouldRespondWith` 405
type GetParamApi = GetParam "name" String :> Get Person
getParamApi :: Proxy GetParamApi
getParamApi = Proxy
type QueryParamApi = QueryParam "name" String :> Get Person
queryParamApi :: Proxy QueryParamApi
queryParamApi = Proxy
getParamServer :: Server GetParamApi
getParamServer (Just name) = return alice{name = name}
getParamServer Nothing = return alice
queryParamServer :: Server QueryParamApi
queryParamServer (Just name) = return alice{name = name}
queryParamServer Nothing = return alice
getParamSpec :: Spec
getParamSpec = do
describe "Servant.API.GetParam" $ do
queryParamSpec :: Spec
queryParamSpec = do
describe "Servant.API.QueryParam" $ do
it "allows to retrieve GET parameters" $ do
(flip runSession) (serve getParamApi getParamServer) $ do
(flip runSession) (serve queryParamApi queryParamServer) $ do
let params = "?name=bob"
response <- Network.Wai.Test.request defaultRequest{
rawQueryString = params,