Add QueryParamForm to API
This commit is contained in:
parent
86ad89b15c
commit
0897ae55ff
3 changed files with 17 additions and 3 deletions
|
@ -71,7 +71,7 @@ import Servant.API.Header (Header (..))
|
|||
import Servant.API.HttpVersion (HttpVersion (..))
|
||||
import Servant.API.IsSecure (IsSecure (..))
|
||||
import Servant.API.QueryParam (QueryFlag, QueryParam,
|
||||
QueryParams)
|
||||
QueryParams, QueryParamForm)
|
||||
import Servant.API.Raw (Raw)
|
||||
import Servant.API.RemoteHost (RemoteHost)
|
||||
import Servant.API.ReqBody (ReqBody)
|
||||
|
|
|
@ -3,7 +3,7 @@
|
|||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# OPTIONS_HADDOCK not-home #-}
|
||||
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams) where
|
||||
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams, QueryParamForm) where
|
||||
|
||||
import Data.Typeable (Typeable)
|
||||
import GHC.TypeLits (Symbol)
|
||||
|
@ -42,9 +42,21 @@ data QueryParams (sym :: Symbol) a
|
|||
-- >>> type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
|
||||
data QueryFlag (sym :: Symbol)
|
||||
|
||||
-- | Lookup the values associated to the query string parameter
|
||||
-- and try to extract it as a value of type @a@.
|
||||
--
|
||||
-- Example:
|
||||
--
|
||||
-- >>> -- /books?title=<title>&authors[]=<author1>&authors[]=<author2>&...
|
||||
-- >>> type MyApi = "books" :> QueryParamForm BookSearchParams :> Get '[JSON] [Book]
|
||||
data QueryParamForm a
|
||||
deriving Typeable
|
||||
|
||||
-- $setup
|
||||
-- >>> import Servant.API
|
||||
-- >>> import Data.Aeson
|
||||
-- >>> import Data.Text
|
||||
-- >>> import Web.FormUrlEncoded (FromForm)
|
||||
-- >>> data Book
|
||||
-- >>> instance ToJSON Book where { toJSON = undefined }
|
||||
-- >>> data BookSearchParams
|
||||
|
|
|
@ -51,7 +51,8 @@ import GHC.Exts (Constraint)
|
|||
import Servant.API.Alternative (type (:<|>))
|
||||
import Servant.API.Capture (Capture, CaptureAll)
|
||||
import Servant.API.Header (Header)
|
||||
import Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams)
|
||||
import Servant.API.QueryParam (QueryFlag, QueryParam,
|
||||
QueryParams, QueryParamForm)
|
||||
import Servant.API.ReqBody (ReqBody)
|
||||
import Servant.API.Sub (type (:>))
|
||||
import Servant.API.Verbs (Verb)
|
||||
|
@ -123,6 +124,7 @@ type family IsElem endpoint api :: Constraint where
|
|||
= IsElem sa sb
|
||||
IsElem sa (QueryParam x y :> sb) = IsElem sa sb
|
||||
IsElem sa (QueryParams x y :> sb) = IsElem sa sb
|
||||
IsElem sa (QueryParamForm x :> sb) = IsElem sa sb
|
||||
IsElem sa (QueryFlag x :> sb) = IsElem sa sb
|
||||
IsElem (Verb m s ct typ) (Verb m s ct' typ)
|
||||
= IsSubList ct ct'
|
||||
|
|
Loading…
Reference in a new issue