Skip to content

Commit 0897ae5

Browse files
committed
Add QueryParamForm to API
1 parent 86ad89b commit 0897ae5

File tree

3 files changed

+17
-3
lines changed

3 files changed

+17
-3
lines changed

servant/src/Servant/API.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ import Servant.API.Header (Header (..))
7171
import Servant.API.HttpVersion (HttpVersion (..))
7272
import Servant.API.IsSecure (IsSecure (..))
7373
import Servant.API.QueryParam (QueryFlag, QueryParam,
74-
QueryParams)
74+
QueryParams, QueryParamForm)
7575
import Servant.API.Raw (Raw)
7676
import Servant.API.RemoteHost (RemoteHost)
7777
import Servant.API.ReqBody (ReqBody)

servant/src/Servant/API/QueryParam.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
{-# LANGUAGE TypeOperators #-}
44
{-# LANGUAGE PolyKinds #-}
55
{-# OPTIONS_HADDOCK not-home #-}
6-
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams) where
6+
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams, QueryParamForm) where
77

88
import Data.Typeable (Typeable)
99
import GHC.TypeLits (Symbol)
@@ -42,9 +42,21 @@ data QueryParams (sym :: Symbol) a
4242
-- >>> type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
4343
data QueryFlag (sym :: Symbol)
4444

45+
-- | Lookup the values associated to the query string parameter
46+
-- and try to extract it as a value of type @a@.
47+
--
48+
-- Example:
49+
--
50+
-- >>> -- /books?title=<title>&authors[]=<author1>&authors[]=<author2>&...
51+
-- >>> type MyApi = "books" :> QueryParamForm BookSearchParams :> Get '[JSON] [Book]
52+
data QueryParamForm a
53+
deriving Typeable
54+
4555
-- $setup
4656
-- >>> import Servant.API
4757
-- >>> import Data.Aeson
4858
-- >>> import Data.Text
59+
-- >>> import Web.FormUrlEncoded (FromForm)
4960
-- >>> data Book
5061
-- >>> instance ToJSON Book where { toJSON = undefined }
62+
-- >>> data BookSearchParams

servant/src/Servant/API/TypeLevel.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,8 @@ import GHC.Exts (Constraint)
5151
import Servant.API.Alternative (type (:<|>))
5252
import Servant.API.Capture (Capture, CaptureAll)
5353
import Servant.API.Header (Header)
54-
import Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams)
54+
import Servant.API.QueryParam (QueryFlag, QueryParam,
55+
QueryParams, QueryParamForm)
5556
import Servant.API.ReqBody (ReqBody)
5657
import Servant.API.Sub (type (:>))
5758
import Servant.API.Verbs (Verb)
@@ -123,6 +124,7 @@ type family IsElem endpoint api :: Constraint where
123124
= IsElem sa sb
124125
IsElem sa (QueryParam x y :> sb) = IsElem sa sb
125126
IsElem sa (QueryParams x y :> sb) = IsElem sa sb
127+
IsElem sa (QueryParamForm x :> sb) = IsElem sa sb
126128
IsElem sa (QueryFlag x :> sb) = IsElem sa sb
127129
IsElem (Verb m s ct typ) (Verb m s ct' typ)
128130
= IsSubList ct ct'

0 commit comments

Comments
 (0)