Skip to content

Commit 6801446

Browse files
committed
Rewrite client concatQueryString for client requests and pull extraneous data type for spec
Remove symbol from QueryParamForm type args Remove the data instance for QueryParamForm in HasDocs
1 parent cffa511 commit 6801446

File tree

12 files changed

+82
-81
lines changed

12 files changed

+82
-81
lines changed

servant-client-core/src/Servant/Client/Core/HasClient.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -557,7 +557,7 @@ instance (KnownSymbol sym, HasClient m api)
557557
-- > } deriving (Eq, Show, Generic)
558558
-- > instance ToForm BookSearchParams
559559
--
560-
-- > type MyApi = "books" :> QueryParamForm "searchQ" BookSearchParams :> Get '[JSON] [Book]
560+
-- > type MyApi = "books" :> QueryParamForm BookSearchParams :> Get '[JSON] [Book]
561561
-- >
562562
-- > myApi :: Proxy MyApi
563563
-- > myApi = Proxy
@@ -567,10 +567,10 @@ instance (KnownSymbol sym, HasClient m api)
567567
-- > -- then you can just use "getBooks" to query that endpoint.
568568
-- > -- 'getBooksBy Nothing' for all books
569569
-- > -- 'getBooksBy (Just $ BookSearchParams "white noise" ["DeLillo"] Nothing)'
570-
instance (KnownSymbol sym, ToForm a, HasClient m api, SBoolI (FoldRequired mods))
571-
=> HasClient m (QueryParamForm' mods sym a :> api) where
570+
instance (ToForm a, HasClient m api, SBoolI (FoldRequired mods))
571+
=> HasClient m (QueryParamForm' mods a :> api) where
572572

573-
type Client m (QueryParamForm' mods sym a :> api) =
573+
type Client m (QueryParamForm' mods a :> api) =
574574
RequiredArgument mods a -> Client m api
575575

576576
-- if mparam = Nothing, we don't add it to the query string

servant-client-core/src/Servant/Client/Core/Request.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -51,11 +51,11 @@ import Network.HTTP.Media
5151
(MediaType)
5252
import Network.HTTP.Types
5353
(Header, HeaderName, HttpVersion (..), Method, QueryItem,
54-
http11, methodGet, parseQuery)
54+
http11, methodGet)
5555
import Servant.API
5656
(ToHttpApiData, toEncodedUrlPiece, toHeader, SourceIO)
5757
import Web.FormUrlEncoded
58-
(ToForm (..), urlEncodeAsForm)
58+
(ToForm (..), toListStable)
5959

6060
import Servant.Client.Core.Internal (mediaTypeRnf)
6161

@@ -143,14 +143,16 @@ concatQueryString :: ToForm a
143143
-> Request
144144
-> Request
145145
concatQueryString form req
146-
= let querySeq = Seq.fromList . parseQuery . LBS.toStrict . urlEncodeAsForm $ form
146+
= let
147+
queryEncoder = map (bimap encodeUtf8 (Just . encodeUtf8))
148+
querySeq = Seq.fromList . queryEncoder . toListStable . toForm $ form
147149
in req { requestQueryString = requestQueryString req Seq.>< querySeq }
148150

151+
149152
-- | Set body and media type of the request being constructed.
150153
--
151154
-- The body is set to the given bytestring using the 'RequestBodyLBS'
152155
-- constructor.
153-
--
154156
-- @since 0.12
155157
--
156158
setRequestBodyLBS :: LBS.ByteString -> MediaType -> Request -> Request

servant-docs/src/Servant/Docs/Internal.hs

Lines changed: 9 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -32,8 +32,6 @@ import qualified Data.ByteString.Lazy.Char8 as LBSC
3232
import Data.ByteString.Lazy.Char8
3333
(ByteString)
3434
import qualified Data.CaseInsensitive as CI
35-
import Data.Data
36-
(Data, toConstr, constrFields)
3735
import Data.Foldable
3836
(toList)
3937
import Data.Foldable
@@ -955,25 +953,23 @@ instance (KnownSymbol sym, ToParam (QueryFlag sym), HasDocs api)
955953
paramP = Proxy :: Proxy (QueryFlag sym)
956954
action' = over params (|> toParam paramP) action
957955

958-
-- | The docs for a @'QueryParamForm' sym a'@
959-
-- require the following instances for the `a`:
960-
-- 'Data', 'ToSample'
961-
instance (KnownSymbol sym, Data a, ToForm a, ToSample a, HasDocs api)
962-
=> HasDocs (QueryParamForm' mods sym a :> api) where
963-
956+
-- | The docs for a @'QueryParamForm' a'@
957+
-- require a 'ToSample a' instance
958+
instance (ToForm a, ToSample a, HasDocs api)
959+
=> HasDocs (QueryParamForm' mods a :> api) where
960+
964961
docsFor Proxy (endpoint, action) =
965962
docsFor subApiP (endpoint, action')
966963

967964
where subApiP = Proxy :: Proxy api
968965
action' =
969966
let (Just sampleForm) = toSample (Proxy :: Proxy a)
970-
paramNames = constrFields (toConstr sampleForm)
971967
sampleEncoding = LBSC.unpack . urlEncodeAsForm . toForm $ sampleForm
972-
in action & params <>~ (fmap (qParamMaker sampleEncoding) paramNames)
973-
qParamMaker formEncodedSample pName = DocQueryParam {
974-
_paramName = pName
968+
in action & params <>~ [qParamMaker sampleEncoding]
969+
qParamMaker formEncodedSample = DocQueryParam {
970+
_paramName = "Collection of Parameters"
975971
, _paramValues = [formEncodedSample]
976-
, _paramDesc = "Query parameter"
972+
, _paramDesc = "Query parameters"
977973
, _paramKind = Normal
978974
}
979975

servant-docs/test/Servant/DocsSpec.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ instance ToParam (QueryParam' mods "bar" Int) where
5858
instance ToParam (QueryParams "foo" Int) where
5959
toParam _ = DocQueryParam "foo" ["1","2","3"] "QueryParams Int" List
6060
instance ToParam (QueryParam "query" String) where
61-
toParam _ = DocQueryParam "query" ["a","b","c"] "QueryParams String" Normal
61+
toParam _ = DocQueryParam "query" ["a","b","c"] "QueryParams String" Normal
6262
instance ToParam (QueryFlag "foo") where
6363
toParam _ = DocQueryParam "foo" [] "QueryFlag" Flag
6464
instance ToCapture (Capture "foo" Int) where
@@ -143,10 +143,7 @@ spec = describe "Servant.Docs" $ do
143143
it "mentions optional query-param" $ do
144144
md `shouldContain` "### GET Parameters:"
145145
md `shouldContain` "- query"
146-
it "mentions optional query-param-form params from QueryParamForm" $ do
147-
md `shouldContain` "- dt1field1"
148-
md `shouldContain` "- dt1field2"
149-
-- contains sample url-encoded form
146+
it "mentions optional query-param-form params from QueryParamForm" $
150147
md `shouldContain` "- **Values**: *dt1field1=field%201&dt1field2=13*"
151148

152149
it "does not generate any docs mentioning the 'empty-api' path" $
@@ -177,7 +174,7 @@ instance MimeRender PlainText Int where
177174
type TestApi1 = Get '[JSON, PlainText] (Headers '[Header "Location" String] Int)
178175
:<|> "postJson" :> ReqBody '[JSON] String :> Post '[JSON] Datatype1
179176
:<|> "qparam" :> QueryParam "query" String :> Get '[JSON] Datatype1
180-
:<|> "qparamform" :> QueryParamForm "form" Datatype1 :> Get '[JSON] Datatype1
177+
:<|> "qparamform" :> QueryParamForm Datatype1 :> Get '[JSON] Datatype1
181178
:<|> "header" :> Header "X-Test" Int :> Put '[JSON] Int
182179
:<|> "empty-api" :> EmptyAPI
183180

servant-foreign/src/Servant/Foreign/Internal.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -325,9 +325,9 @@ instance
325325
{ _argName = PathSegment str
326326
, _argType = typeFor lang ftype (Proxy :: Proxy Bool) }
327327

328-
instance (KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api)
329-
=> HasForeign lang ftype (QueryParamForm' mods sym a :> api) where
330-
type Foreign ftype (QueryParamForm' mods sym a :> api) = Foreign ftype api
328+
instance (HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api)
329+
=> HasForeign lang ftype (QueryParamForm' mods a :> api) where
330+
type Foreign ftype (QueryParamForm' mods a :> api) = Foreign ftype api
331331

332332
foreignFor lang Proxy Proxy req =
333333
foreignFor lang (Proxy :: Proxy ftype) (Proxy :: Proxy api) $
@@ -336,7 +336,7 @@ instance (KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a),
336336
arg = Arg
337337
{ _argName = PathSegment ""
338338
, _argType = typeFor lang (Proxy :: Proxy ftype) (Proxy :: Proxy (RequiredArgument mods a)) }
339-
339+
340340

341341
instance HasForeign lang ftype Raw where
342342
type Foreign ftype Raw = HTTP.Method -> Req ftype

servant-foreign/test/Servant/ForeignSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ instance HasForeignType LangX String ContactForm where
8282
type TestApi
8383
= "test" :> Header "header" [String] :> QueryFlag "flag" :> Get '[JSON] Int
8484
:<|> "test" :> QueryParam "param" Int :> ReqBody '[JSON] [String] :> Post '[JSON] NoContent
85-
:<|> "test" :> QueryParamForm "contact" ContactForm :> Post '[JSON] NoContent
85+
:<|> "test" :> QueryParamForm ContactForm :> Post '[JSON] NoContent
8686
:<|> "test" :> QueryParams "params" Int :> ReqBody '[JSON] String :> Put '[JSON] NoContent
8787
:<|> "test" :> Capture "id" Int :> Delete '[JSON] NoContent
8888
:<|> "test" :> CaptureAll "ids" Int :> Get '[JSON] [Int]

servant-http-streams/test/Servant/ClientSpec.hs

Lines changed: 5 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -111,14 +111,6 @@ alice = Person "Alice" 42
111111
carol :: Person
112112
carol = Person "Carol" 17
113113

114-
data PersonSearch = PersonSearch
115-
{ nameStartsWith :: String
116-
, ageGreaterThan :: Integer
117-
} deriving (Eq, Show, Generic)
118-
119-
instance ToForm PersonSearch
120-
instance FromForm PersonSearch
121-
122114
type TestHeaders = '[Header "X-Example1" Int, Header "X-Example2" String]
123115

124116
type Api =
@@ -130,7 +122,7 @@ type Api =
130122
:<|> "body" :> ReqBody '[FormUrlEncoded,JSON] Person :> Post '[JSON] Person
131123
:<|> "param" :> QueryParam "name" String :> Get '[FormUrlEncoded,JSON] Person
132124
:<|> "params" :> QueryParams "names" String :> Get '[JSON] [Person]
133-
:<|> "paramform" :> QueryParamForm "names" PersonSearch :> Get '[JSON] [Person]
125+
:<|> "paramform" :> QueryParamForm Person :> Get '[JSON] [Person]
134126
:<|> "flag" :> QueryFlag "flag" :> Get '[JSON] Bool
135127
:<|> "rawSuccess" :> Raw
136128
:<|> "rawFailure" :> Raw
@@ -156,7 +148,7 @@ getCaptureAll :: [String] -> ClientM [Person]
156148
getBody :: Person -> ClientM Person
157149
getQueryParam :: Maybe String -> ClientM Person
158150
getQueryParams :: [String] -> ClientM [Person]
159-
getQueryParamForm :: Maybe PersonSearch -> ClientM [Person]
151+
getQueryParamForm :: Maybe Person -> ClientM [Person]
160152
getQueryFlag :: Bool -> ClientM Bool
161153
getRawSuccess :: HTTP.Method -> ClientM Response
162154
getRawFailure :: HTTP.Method -> ClientM Response
@@ -198,8 +190,8 @@ server = serve api (
198190
Nothing -> throwError $ ServerError 400 "missing parameter" "" [])
199191
:<|> (\ names -> return (zipWith Person names [0..]))
200192
:<|> (\ psearch -> case psearch of
201-
Just (Right psearch) -> return [alice, carol]
202-
Just (Left err) -> throwError $ ServerError 400 "failed to decode form" "" []
193+
Just (Right _) -> return [alice, carol]
194+
Just (Left _) -> throwError $ ServerError 400 "failed to decode form" "" []
203195
Nothing -> return [])
204196
:<|> return
205197
:<|> (Tagged $ \ _request respond -> respond $ Wai.responseLBS HTTP.ok200 [] "rawSuccess")
@@ -323,7 +315,7 @@ sucessSpec = beforeAll (startWaiApp server) $ afterAll endWaiApp $ do
323315

324316
it "Servant.API.QueryParam.QueryParamForm" $ \(_, baseUrl) -> do
325317
left show <$> runClient (getQueryParamForm Nothing) baseUrl `shouldReturn` Right []
326-
left show <$> runClient (getQueryParamForm (Just $ PersonSearch "a" 10)) baseUrl
318+
left show <$> runClient (getQueryParamForm (Just $ Person "a" 10)) baseUrl
327319
`shouldReturn` Right [alice, carol]
328320

329321
context "Servant.API.QueryParam.QueryFlag" $

servant-server/src/Servant/Server/Internal.hs

Lines changed: 12 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -558,9 +558,9 @@ instance (KnownSymbol sym, HasServer api context)
558558
examine v | v == "true" || v == "1" || v == "" = True
559559
| otherwise = False
560560

561-
-- | If you define a custom record type, for example @BookSearchParams@, then you can use
562-
-- @'QueryParamForm' "formName" BookSearchParams@ in one of the endpoints for your API
563-
-- to translate a collection of query-string parameters into a value of your record type.
561+
-- | If you define a custom record type, for example @BookSearchParams@, then you can use
562+
-- @'QueryParamForm' BookSearchParams@ in one of the endpoints for your API
563+
-- to translate a collection of query-string parameters into a value of your record type.
564564
--
565565
-- Your server-side handler must be a function that takes an argument of type
566566
-- @'Maybe' ('Either' BookSearchParams)@.
@@ -582,26 +582,24 @@ instance (KnownSymbol sym, HasServer api context)
582582
-- > , page :: Maybe Int
583583
-- > } deriving (Eq, Show, Generic)
584584
-- > instance FromForm BookSearchParams
585-
-- > type MyApi = "books" :> QueryParamForm "searchQ" BookSearchParams :> Get '[JSON] [Book]
586-
--
585+
-- > type MyApi = "books" :> QueryParamForm BookSearchParams :> Get '[JSON] [Book]
586+
--
587587
-- Example Handler Signature:
588588
-- Maybe (Either Text BookSearchParams) -> Handler [Book]
589589
instance
590-
( KnownSymbol sym, FromForm a, HasServer api context
590+
(FromForm a, HasServer api context
591591
, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)
592592
)
593-
=> HasServer (QueryParamForm' mods sym a :> api) context where
593+
=> HasServer (QueryParamForm' mods a :> api) context where
594594
------
595-
type ServerT (QueryParamForm' mods sym a :> api) m =
595+
type ServerT (QueryParamForm' mods a :> api) m =
596596
RequestArgument mods a -> ServerT api m
597597

598598
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt . s
599599

600-
route Proxy context subserver =
601-
602-
let formName = cs $ symbolVal (Proxy :: Proxy sym)
600+
route Proxy context subserver =
603601

604-
parseParamForm req =
602+
let parseParamForm req =
605603
unfoldRequestArgument (Proxy :: Proxy mods) errReq errSt mev
606604
where
607605
rawQS = rawQueryString req
@@ -612,12 +610,11 @@ instance
612610
_ -> Just $ urlDecodeAsForm (BL.drop 1 . BL.fromStrict $ rawQS)
613611

614612
errReq = delayedFailFatal err400
615-
{ errBody = cs $ "Query parameter form " <> formName <> " is required"
613+
{ errBody = "Query parameter form is required"
616614
}
617615

618616
errSt e = delayedFailFatal err400
619-
{ errBody = cs $ "Error parsing query parameter form "
620-
<> formName <> " failed: " <> e
617+
{ errBody = cs $ "Error: parsing query parameter form failed. " <> e
621618
}
622619

623620
delayed = addParameterCheck subserver . withRequest $ \req ->

servant-server/test/Servant/ServerSpec.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -466,14 +466,14 @@ data AnimalSearch = AnimalSearch {
466466
instance FromForm AnimalSearch
467467

468468
type QueryParamFormApi =
469-
QueryParamForm "octopus" AnimalSearch :> Get '[JSON] Animal
469+
QueryParamForm AnimalSearch :> Get '[JSON] Animal
470470
:<|> "before-param"
471471
:> QueryParam "before" Bool
472-
:> QueryParamForm "before" AnimalSearch
472+
:> QueryParamForm AnimalSearch
473473
:> Get '[JSON] Animal
474474
:<|> "mixed-param"
475475
:> QueryParam "before" Bool
476-
:> QueryParamForm "multiple" AnimalSearch
476+
:> QueryParamForm AnimalSearch
477477
:> QueryParam "after" Bool
478478
:> Get '[JSON] Animal
479479

servant/src/Servant/API/QueryParam.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ data QueryParams (sym :: Symbol) (a :: *)
5050
-- of type (Maybe (Either Text a)). This also means that in a server implementation
5151
-- if there as a query string of any length (even just a "?"), we'll try to parse
5252
-- the 'QueryParamForm' into the custom type specified.
53-
--
53+
--
5454
-- Example:
5555
--
5656
-- > data BookSearchParams = BookSearchParams
@@ -59,15 +59,15 @@ data QueryParams (sym :: Symbol) (a :: *)
5959
-- > , page :: Maybe Int
6060
-- > } deriving (Eq, Show, Generic)
6161
-- > instance FromForm BookSearchParams
62-
-- > type MyApi = "books" :> QueryParamForm "searchQ" BookSearchParams :> Get '[JSON] [Book]
63-
--
62+
-- > type MyApi = "books" :> QueryParamForm BookSearchParams :> Get '[JSON] [Book]
63+
--
6464
-- Example Handler Signature:
6565
-- Maybe (Either Text BookSearchParams) -> Handler [Book]
6666

6767
type QueryParamForm = QueryParamForm' '[Optional, Lenient]
6868

6969
-- | 'QueryParamForm' which can be 'Required', 'Lenient', or modified otherwise.
70-
data QueryParamForm' (mods :: [*]) (sym :: Symbol) (a :: *)
70+
data QueryParamForm' (mods :: [*]) (a :: *)
7171
deriving Typeable
7272

7373

0 commit comments

Comments
 (0)