servant/servant/src/Servant/API/QueryParam.hs
Oleg Grenrus bc3f61d615 Add Servant.API.Modifiers to servant
Changes Header, ReqBody and QueryParam to take a modifier list.

Resolves https://github.com/haskell-servant/servant/issues/856

ResponseHeader story turns to be somewhat ugly, but it can be made
elegant when https://github.com/haskell-servant/servant/issues/841 is
implemnted, then we can omit HList aka Header Heterogenous List
implementation.

- servant-server changes:

  Writing server side intepretations is quite simple using
  `unfoldRequestArgument`, which makes Header and QueryParam look quite
  the same.

  `ReqBody` cannot be easily made optional with current design (what that
  would mean: No Content-Type Header?), so that dimensions isn't used
  there.

- Add HasLink for all the rest ComprehensiveAPI combinators
- Add 'tricky' Header', QueryParam' endpoints to ComprehensiveAPI
- servant-docs: Quick'n'dirty implementation. Don't use modifiers information (yet).
2018-01-25 09:10:11 +02:00

56 lines
2.0 KiB
Haskell

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParam', QueryParams) where
import Data.Typeable (Typeable)
import GHC.TypeLits (Symbol)
import Servant.API.Modifiers
-- | Lookup the value associated to the @sym@ query string parameter
-- and try to extract it as a value of type @a@.
--
-- Example:
--
-- >>> -- /books?author=<author name>
-- >>> type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]
type QueryParam = QueryParam' '[Optional, Strict]
-- | 'QueryParam' which can be 'Required', 'Lenient', or modified otherwise.
data QueryParam' (mods :: [*]) (sym :: Symbol) (a :: *)
deriving Typeable
-- | Lookup the values associated to the @sym@ query string parameter
-- and try to extract it as a value of type @[a]@. This is typically
-- meant to support query string parameters of the form
-- @param[]=val1&param[]=val2@ and so on. Note that servant doesn't actually
-- require the @[]@s and will fetch the values just fine with
-- @param=val1&param=val2@, too.
--
-- Example:
--
-- >>> -- /books?authors[]=<author1>&authors[]=<author2>&...
-- >>> type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
data QueryParams (sym :: Symbol) (a :: *)
deriving Typeable
-- | Lookup a potentially value-less query string parameter
-- with boolean semantics. If the param @sym@ is there without any value,
-- or if it's there with value "true" or "1", it's interpreted as 'True'.
-- Otherwise, it's interpreted as 'False'.
--
-- Example:
--
-- >>> -- /books?published
-- >>> type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
data QueryFlag (sym :: Symbol)
-- $setup
-- >>> import Servant.API
-- >>> import Data.Aeson
-- >>> import Data.Text
-- >>> data Book
-- >>> instance ToJSON Book where { toJSON = undefined }