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

620 lines
25 KiB
Haskell
Raw Normal View History

{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
2015-12-27 17:54:29 +01:00
#include "overlapping-compat.h"
module Servant.Server.Internal
( module Servant.Server.Internal
, module Servant.Server.Internal.Router
, module Servant.Server.Internal.RoutingApplication
, module Servant.Server.Internal.ServantErr
) where
2014-12-10 16:10:57 +01:00
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
2015-09-12 14:11:24 +02:00
import Control.Monad.Trans.Except (ExceptT)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Map as M
import Data.Maybe (fromMaybe, mapMaybe)
import Data.String (fromString)
import Data.String.Conversions (ConvertibleStrings, cs, (<>))
import Data.Text (Text)
import Data.Typeable
import GHC.TypeLits (KnownSymbol, symbolVal)
import Network.HTTP.Types hiding (Header, ResponseHeaders)
import Network.Socket (SockAddr)
import Network.Wai (Application, lazyRequestBody,
rawQueryString, requestHeaders,
requestMethod, responseLBS, remoteHost,
isSecure, vault, httpVersion, Response,
Request, pathInfo)
import Servant.API ((:<|>) (..), (:>), Capture,
Delete, Get, Header,
IsSecure(..), Patch, Post, Put,
QueryFlag, QueryParam, QueryParams,
Raw, RemoteHost, ReqBody, Vault)
import Servant.API.ContentTypes (AcceptHeader (..),
AllCTRender (..),
AllCTUnrender (..),
AllMime,
canHandleAcceptH)
import Servant.API.ResponseHeaders (GetHeaders, Headers, getHeaders,
getResponse)
2015-01-13 20:40:41 +01:00
import Servant.Server.Internal.Router
import Servant.Server.Internal.RoutingApplication
2015-05-02 04:38:53 +02:00
import Servant.Server.Internal.ServantErr
import Web.HttpApiData (FromHttpApiData)
import Web.HttpApiData.Internal (parseUrlPieceMaybe, parseHeaderMaybe, parseQueryParamMaybe)
2014-12-10 16:10:57 +01:00
class HasServer layout where
2015-05-03 01:45:17 +02:00
type ServerT layout (m :: * -> *) :: *
2014-12-10 16:10:57 +01:00
route :: Proxy layout -> Delayed (Server layout) -> Router
2014-12-28 23:07:14 +01:00
2015-09-12 14:11:24 +02:00
type Server layout = ServerT layout (ExceptT ServantErr IO)
2014-12-10 16:10:57 +01:00
-- * Instances
2014-12-28 23:07:14 +01:00
-- | A server for @a ':<|>' b@ first tries to match the request against the route
2014-12-10 16:10:57 +01:00
-- represented by @a@ and if it fails tries @b@. You must provide a request
-- handler for each route.
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
-- > :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = listAllBooks :<|> postBook
-- > where listAllBooks = ...
-- > postBook book = ...
instance (HasServer a, HasServer b) => HasServer (a :<|> b) where
2015-05-03 01:45:17 +02:00
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m
route Proxy server = choice (route pa ((\ (a :<|> _) -> a) <$> server))
(route pb ((\ (_ :<|> b) -> b) <$> server))
2014-12-10 16:10:57 +01:00
where pa = Proxy :: Proxy a
pb = Proxy :: Proxy b
captured :: FromHttpApiData a => proxy (Capture sym a) -> Text -> Maybe a
captured _ = parseUrlPieceMaybe
2014-12-10 16:10:57 +01:00
-- | If you use 'Capture' in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of the type specified by the 'Capture'.
-- This lets servant worry about getting it from the URL and turning
-- it into a value of the type you specify.
--
-- You can control how it'll be converted from 'Text' to your type
-- by simply providing an instance of 'FromHttpApiData' for your type.
2014-12-10 16:10:57 +01:00
--
-- Example:
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = getBook
2015-09-12 14:11:24 +02:00
-- > where getBook :: Text -> ExceptT ServantErr IO Book
2014-12-10 16:10:57 +01:00
-- > getBook isbn = ...
instance (KnownSymbol capture, FromHttpApiData a, HasServer sublayout)
2014-12-10 16:10:57 +01:00
=> HasServer (Capture capture a :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (Capture capture a :> sublayout) m =
a -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy d =
DynamicRouter $ \ first ->
route (Proxy :: Proxy sublayout)
(addCapture d $ case captured captureProxy first of
Nothing -> return $ Fail err404
Just v -> return $ Route v
)
where
captureProxy = Proxy :: Proxy (Capture capture a)
2015-01-12 15:08:41 +01:00
allowedMethodHead :: Method -> Request -> Bool
allowedMethodHead method request = method == methodGet && requestMethod request == methodHead
allowedMethod :: Method -> Request -> Bool
allowedMethod method request = allowedMethodHead method request || requestMethod request == method
processMethodRouter :: forall a. ConvertibleStrings a B.ByteString
=> Maybe (a, BL.ByteString) -> Status -> Method
-> Maybe [(HeaderName, B.ByteString)]
-> Request -> RouteResult Response
processMethodRouter handleA status method headers request = case handleA of
Nothing -> FailFatal err406 -- this should not happen (checked before), so we make it fatal if it does
Just (contentT, body) -> Route $ responseLBS status hdrs bdy
where
2015-08-17 23:50:42 +02:00
bdy = if allowedMethodHead method request then "" else body
hdrs = (hContentType, cs contentT) : (fromMaybe [] headers)
2014-12-10 16:10:57 +01:00
methodCheck :: Method -> Request -> IO (RouteResult ())
methodCheck method request
| allowedMethod method request = return $ Route ()
| otherwise = return $ Fail err405
acceptCheck :: (AllMime list) => Proxy list -> B.ByteString -> IO (RouteResult ())
acceptCheck proxy accH
| canHandleAcceptH proxy (AcceptHeader accH) = return $ Route ()
| otherwise = return $ Fail err406
methodRouter :: (AllCTRender ctypes a)
=> Method -> Proxy ctypes -> Status
-> Delayed (ExceptT ServantErr IO a)
-> Router
methodRouter method proxy status action = LeafRouter route'
where
route' request respond
| pathIsEmpty request =
let accH = fromMaybe ct_wildcard $ lookup hAccept $ requestHeaders request
in runAction (action `addMethodCheck` methodCheck method request
`addAcceptCheck` acceptCheck proxy accH
) respond $ \ output -> do
let handleA = handleAcceptH proxy (AcceptHeader accH) output
processMethodRouter handleA status method Nothing request
| otherwise = respond $ Fail err404
methodRouterHeaders :: (GetHeaders (Headers h v), AllCTRender ctypes v)
=> Method -> Proxy ctypes -> Status
-> Delayed (ExceptT ServantErr IO (Headers h v))
-> Router
methodRouterHeaders method proxy status action = LeafRouter route'
where
route' request respond
| pathIsEmpty request =
let accH = fromMaybe ct_wildcard $ lookup hAccept $ requestHeaders request
in runAction (action `addMethodCheck` methodCheck method request
`addAcceptCheck` acceptCheck proxy accH
) respond $ \ output -> do
let headers = getHeaders output
handleA = handleAcceptH proxy (AcceptHeader accH) (getResponse output)
processMethodRouter handleA status method (Just headers) request
| otherwise = respond $ Fail err404
methodRouterEmpty :: Method
-> Delayed (ExceptT ServantErr IO ())
-> Router
methodRouterEmpty method action = LeafRouter route'
where
route' request respond
| pathIsEmpty request = do
runAction (addMethodCheck action (methodCheck method request)) respond $ \ () ->
Route $! responseLBS noContent204 [] ""
| otherwise = respond $ Fail err404
2014-12-10 16:10:57 +01:00
-- | If you have a 'Delete' endpoint in your API,
-- the handler for this endpoint is meant to delete
-- a resource.
--
-- The code of the handler will, just like
-- for 'Servant.API.Get.Get', 'Servant.API.Post.Post' and
2015-09-12 14:11:24 +02:00
-- 'Servant.API.Put.Put', run in @ExceptT ServantErr IO ()@.
2014-12-10 16:10:57 +01:00
-- The 'Int' represents the status code and the 'String' a message
2015-09-12 14:11:24 +02:00
-- to be returned. You can use 'Control.Monad.Trans.Except.throwE' to
2014-12-10 16:10:57 +01:00
-- painlessly error out if the conditions for a successful deletion
-- are not met.
2015-12-27 17:54:29 +01:00
instance OVERLAPPABLE_
( AllCTRender ctypes a
) => HasServer (Delete ctypes a) where
type ServerT (Delete ctypes a) m = m a
route Proxy = methodRouter methodDelete (Proxy :: Proxy ctypes) ok200
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
HasServer (Delete ctypes ()) where
type ServerT (Delete ctypes ()) m = m ()
2014-12-10 16:10:57 +01:00
route Proxy = methodRouterEmpty methodDelete
-- Add response headers
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
( GetHeaders (Headers h v), AllCTRender ctypes v
) => HasServer (Delete ctypes (Headers h v)) where
type ServerT (Delete ctypes (Headers h v)) m = m (Headers h v)
route Proxy = methodRouterHeaders methodDelete (Proxy :: Proxy ctypes) ok200
2014-12-10 16:10:57 +01:00
-- | When implementing the handler for a 'Get' endpoint,
-- just like for 'Servant.API.Delete.Delete', 'Servant.API.Post.Post'
-- and 'Servant.API.Put.Put', the handler code runs in the
2015-09-12 14:11:24 +02:00
-- @ExceptT ServantErr IO@ monad, where the 'Int' represents
2014-12-10 16:10:57 +01:00
-- the status code and the 'String' a message, returned in case of
2015-09-12 14:11:24 +02:00
-- failure. You can quite handily use 'Control.Monad.Trans.Except.throwE'
2014-12-10 16:10:57 +01:00
-- to quickly fail if some conditions are not met.
--
2015-01-13 20:40:41 +01:00
-- If successfully returning a value, we use the type-level list, combined
-- with the request's @Accept@ header, to encode the value for you
-- (returning a status code of 200). If there was no @Accept@ header or it
-- was @*\/\*@, we return encode using the first @Content-Type@ type on the
2015-01-13 20:40:41 +01:00
-- list.
2015-12-27 17:54:29 +01:00
instance OVERLAPPABLE_
2015-04-20 19:52:29 +02:00
( AllCTRender ctypes a ) => HasServer (Get ctypes a) where
2015-05-03 01:45:17 +02:00
type ServerT (Get ctypes a) m = m a
route Proxy = methodRouter methodGet (Proxy :: Proxy ctypes) ok200
2014-12-10 16:10:57 +01:00
-- '()' ==> 204 No Content
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-04-20 19:52:29 +02:00
HasServer (Get ctypes ()) where
2015-05-03 01:45:17 +02:00
type ServerT (Get ctypes ()) m = m ()
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterEmpty methodGet
2014-12-10 16:10:57 +01:00
-- Add response headers
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-05-02 03:21:03 +02:00
( GetHeaders (Headers h v), AllCTRender ctypes v
) => HasServer (Get ctypes (Headers h v)) where
2015-04-20 19:52:29 +02:00
2015-05-03 01:45:17 +02:00
type ServerT (Get ctypes (Headers h v)) m = m (Headers h v)
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterHeaders methodGet (Proxy :: Proxy ctypes) ok200
2014-12-10 16:10:57 +01:00
-- | If you use 'Header' in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of the type specified by 'Header'.
-- This lets servant worry about extracting it from the request and turning
-- it into a value of the type you specify.
--
-- All it asks is for a 'FromHttpApiData' instance.
2014-12-10 16:10:57 +01:00
--
-- Example:
--
-- > newtype Referer = Referer Text
-- > deriving (Eq, Show, FromHttpApiData, ToText)
2014-12-10 16:10:57 +01:00
-- >
-- > -- GET /view-my-referer
2015-01-13 20:40:41 +01:00
-- > type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = viewReferer
2015-09-12 14:11:24 +02:00
-- > where viewReferer :: Referer -> ExceptT ServantErr IO referer
2014-12-10 16:10:57 +01:00
-- > viewReferer referer = return referer
instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout)
2014-12-10 16:10:57 +01:00
=> HasServer (Header sym a :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (Header sym a :> sublayout) m =
Maybe a -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy subserver = WithRequest $ \ request ->
let mheader = parseHeaderMaybe =<< lookup str (requestHeaders request)
in route (Proxy :: Proxy sublayout) (passToServer subserver mheader)
where str = fromString $ symbolVal (Proxy :: Proxy sym)
2014-12-10 16:10:57 +01:00
-- | When implementing the handler for a 'Post' endpoint,
-- just like for 'Servant.API.Delete.Delete', 'Servant.API.Get.Get'
-- and 'Servant.API.Put.Put', the handler code runs in the
2015-09-12 14:11:24 +02:00
-- @ExceptT ServantErr IO@ monad, where the 'Int' represents
2014-12-10 16:10:57 +01:00
-- the status code and the 'String' a message, returned in case of
2015-09-12 14:11:24 +02:00
-- failure. You can quite handily use 'Control.Monad.Trans.Except.throwE'
2014-12-10 16:10:57 +01:00
-- to quickly fail if some conditions are not met.
--
2015-01-13 20:40:41 +01:00
-- If successfully returning a value, we use the type-level list, combined
-- with the request's @Accept@ header, to encode the value for you
-- (returning a status code of 201). If there was no @Accept@ header or it
-- was @*\/\*@, we return encode using the first @Content-Type@ type on the
2015-01-13 20:40:41 +01:00
-- list.
2015-12-27 17:54:29 +01:00
instance OVERLAPPABLE_
2015-04-20 19:52:29 +02:00
( AllCTRender ctypes a
2015-01-13 20:40:41 +01:00
) => HasServer (Post ctypes a) where
2015-05-03 01:45:17 +02:00
type ServerT (Post ctypes a) m = m a
2014-12-10 16:10:57 +01:00
route Proxy = methodRouter methodPost (Proxy :: Proxy ctypes) created201
2014-12-10 16:10:57 +01:00
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-04-20 19:52:29 +02:00
HasServer (Post ctypes ()) where
2015-05-03 01:45:17 +02:00
type ServerT (Post ctypes ()) m = m ()
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterEmpty methodPost
2014-12-10 16:10:57 +01:00
-- Add response headers
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-05-02 03:21:03 +02:00
( GetHeaders (Headers h v), AllCTRender ctypes v
) => HasServer (Post ctypes (Headers h v)) where
2015-04-20 19:52:29 +02:00
2015-05-03 01:45:17 +02:00
type ServerT (Post ctypes (Headers h v)) m = m (Headers h v)
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterHeaders methodPost (Proxy :: Proxy ctypes) created201
2014-12-10 16:10:57 +01:00
-- | When implementing the handler for a 'Put' endpoint,
-- just like for 'Servant.API.Delete.Delete', 'Servant.API.Get.Get'
-- and 'Servant.API.Post.Post', the handler code runs in the
2015-09-12 14:11:24 +02:00
-- @ExceptT ServantErr IO@ monad, where the 'Int' represents
2014-12-10 16:10:57 +01:00
-- the status code and the 'String' a message, returned in case of
2015-09-12 14:11:24 +02:00
-- failure. You can quite handily use 'Control.Monad.Trans.Except.throwE'
2014-12-10 16:10:57 +01:00
-- to quickly fail if some conditions are not met.
--
2015-01-13 20:40:41 +01:00
-- If successfully returning a value, we use the type-level list, combined
-- with the request's @Accept@ header, to encode the value for you
-- (returning a status code of 200). If there was no @Accept@ header or it
-- was @*\/\*@, we return encode using the first @Content-Type@ type on the
2015-01-13 20:40:41 +01:00
-- list.
2015-12-27 17:54:29 +01:00
instance OVERLAPPABLE_
2015-04-20 19:52:29 +02:00
( AllCTRender ctypes a) => HasServer (Put ctypes a) where
2015-05-03 01:45:17 +02:00
type ServerT (Put ctypes a) m = m a
2014-12-10 16:10:57 +01:00
route Proxy = methodRouter methodPut (Proxy :: Proxy ctypes) ok200
2014-12-10 16:10:57 +01:00
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-04-20 19:52:29 +02:00
HasServer (Put ctypes ()) where
2015-05-03 01:45:17 +02:00
type ServerT (Put ctypes ()) m = m ()
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterEmpty methodPut
2014-12-10 16:10:57 +01:00
-- Add response headers
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-05-02 03:21:03 +02:00
( GetHeaders (Headers h v), AllCTRender ctypes v
) => HasServer (Put ctypes (Headers h v)) where
2015-04-20 19:52:29 +02:00
2015-05-03 01:45:17 +02:00
type ServerT (Put ctypes (Headers h v)) m = m (Headers h v)
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterHeaders methodPut (Proxy :: Proxy ctypes) ok200
2014-12-10 16:10:57 +01:00
2015-02-10 01:33:41 +01:00
-- | When implementing the handler for a 'Patch' endpoint,
-- just like for 'Servant.API.Delete.Delete', 'Servant.API.Get.Get'
-- and 'Servant.API.Put.Put', the handler code runs in the
2015-09-12 14:11:24 +02:00
-- @ExceptT ServantErr IO@ monad, where the 'Int' represents
2015-02-10 01:33:41 +01:00
-- the status code and the 'String' a message, returned in case of
2015-09-12 14:11:24 +02:00
-- failure. You can quite handily use 'Control.Monad.Trans.Except.throwE'
2015-02-10 01:33:41 +01:00
-- to quickly fail if some conditions are not met.
--
-- If successfully returning a value, we just require that its type has
-- a 'ToJSON' instance and servant takes care of encoding it for you,
-- yielding status code 200 along the way.
2015-12-27 17:54:29 +01:00
instance OVERLAPPABLE_
2015-04-20 19:52:29 +02:00
( AllCTRender ctypes a) => HasServer (Patch ctypes a) where
2015-05-03 01:45:17 +02:00
type ServerT (Patch ctypes a) m = m a
2015-02-10 01:33:41 +01:00
route Proxy = methodRouter methodPatch (Proxy :: Proxy ctypes) ok200
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-04-20 19:52:29 +02:00
HasServer (Patch ctypes ()) where
2015-05-03 01:45:17 +02:00
type ServerT (Patch ctypes ()) m = m ()
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterEmpty methodPatch
2015-02-10 01:33:41 +01:00
-- Add response headers
2015-12-27 17:54:29 +01:00
instance OVERLAPPING_
2015-05-02 03:21:03 +02:00
( GetHeaders (Headers h v), AllCTRender ctypes v
) => HasServer (Patch ctypes (Headers h v)) where
2015-04-20 19:52:29 +02:00
2015-05-03 01:45:17 +02:00
type ServerT (Patch ctypes (Headers h v)) m = m (Headers h v)
2015-04-20 19:52:29 +02:00
route Proxy = methodRouterHeaders methodPatch (Proxy :: Proxy ctypes) ok200
2015-02-10 01:33:41 +01:00
2014-12-10 16:10:57 +01:00
-- | If you use @'QueryParam' "author" Text@ in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of type @'Maybe' 'Text'@.
--
-- This lets servant worry about looking it up in the query string
-- and turning it into a value of the type you specify, enclosed
-- in 'Maybe', because it may not be there and servant would then
-- hand you 'Nothing'.
--
-- You can control how it'll be converted from 'Text' to your type
-- by simply providing an instance of 'FromHttpApiData' for your type.
2014-12-10 16:10:57 +01:00
--
-- Example:
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = getBooksBy
2015-09-12 14:11:24 +02:00
-- > where getBooksBy :: Maybe Text -> ExceptT ServantErr IO [Book]
2014-12-10 16:10:57 +01:00
-- > getBooksBy Nothing = ...return all books...
-- > getBooksBy (Just author) = ...return books by the given author...
instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout)
2014-12-10 16:10:57 +01:00
=> HasServer (QueryParam sym a :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (QueryParam sym a :> sublayout) m =
Maybe a -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy subserver = WithRequest $ \ request ->
2014-12-10 16:10:57 +01:00
let querytext = parseQueryText $ rawQueryString request
param =
case lookup paramname querytext of
Nothing -> Nothing -- param absent from the query string
Just Nothing -> Nothing -- param present with no value -> Nothing
Just (Just v) -> parseQueryParamMaybe v -- if present, we try to convert to
2014-12-10 16:10:57 +01:00
-- the right type
in route (Proxy :: Proxy sublayout) (passToServer subserver param)
2014-12-10 16:10:57 +01:00
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
-- | If you use @'QueryParams' "authors" Text@ in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of type @['Text']@.
--
-- This lets servant worry about looking up 0 or more values in the query string
-- associated to @authors@ and turning each of them into a value of
-- the type you specify.
--
-- You can control how the individual values are converted from 'Text' to your type
-- by simply providing an instance of 'FromHttpApiData' for your type.
2014-12-10 16:10:57 +01:00
--
-- Example:
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = getBooksBy
2015-09-12 14:11:24 +02:00
-- > where getBooksBy :: [Text] -> ExceptT ServantErr IO [Book]
2014-12-10 16:10:57 +01:00
-- > getBooksBy authors = ...return all books by these authors...
instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout)
2014-12-10 16:10:57 +01:00
=> HasServer (QueryParams sym a :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (QueryParams sym a :> sublayout) m =
[a] -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy subserver = WithRequest $ \ request ->
2014-12-10 16:10:57 +01:00
let querytext = parseQueryText $ rawQueryString request
-- if sym is "foo", we look for query string parameters
-- named "foo" or "foo[]" and call parseQueryParam on the
2014-12-10 16:10:57 +01:00
-- corresponding values
parameters = filter looksLikeParam querytext
2015-08-17 23:50:42 +02:00
values = mapMaybe (convert . snd) parameters
in route (Proxy :: Proxy sublayout) (passToServer subserver values)
2014-12-10 16:10:57 +01:00
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
looksLikeParam (name, _) = name == paramname || name == (paramname <> "[]")
convert Nothing = Nothing
convert (Just v) = parseQueryParamMaybe v
2014-12-10 16:10:57 +01:00
-- | If you use @'QueryFlag' "published"@ in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of type 'Bool'.
--
-- Example:
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = getBooks
2015-09-12 14:11:24 +02:00
-- > where getBooks :: Bool -> ExceptT ServantErr IO [Book]
2014-12-10 16:10:57 +01:00
-- > getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
instance (KnownSymbol sym, HasServer sublayout)
=> HasServer (QueryFlag sym :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (QueryFlag sym :> sublayout) m =
Bool -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy subserver = WithRequest $ \ request ->
2014-12-10 16:10:57 +01:00
let querytext = parseQueryText $ rawQueryString request
param = case lookup paramname querytext of
Just Nothing -> True -- param is there, with no value
Just (Just v) -> examine v -- param with a value
Nothing -> False -- param not in the query string
in route (Proxy :: Proxy sublayout) (passToServer subserver param)
2014-12-10 16:10:57 +01:00
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
examine v | v == "true" || v == "1" || v == "" = True
| otherwise = False
-- | Just pass the request to the underlying application and serve its response.
--
-- Example:
--
-- > type MyApi = "images" :> Raw
-- >
-- > server :: Server MyApi
-- > server = serveDirectory "/var/www/images"
instance HasServer Raw where
2015-05-03 01:45:17 +02:00
type ServerT Raw m = Application
route Proxy rawApplication = LeafRouter $ \ request respond -> do
r <- runDelayed rawApplication
case r of
Route app -> app request (respond . Route)
Fail a -> respond $ Fail a
FailFatal e -> respond $ FailFatal e
2014-12-10 16:10:57 +01:00
-- | If you use 'ReqBody' in one of the endpoints for your API,
-- this automatically requires your server-side handler to be a function
-- that takes an argument of the type specified by 'ReqBody'.
2015-01-13 20:40:41 +01:00
-- The @Content-Type@ header is inspected, and the list provided is used to
-- attempt deserialization. If the request does not have a @Content-Type@
2015-09-15 17:21:41 +02:00
-- header, it is treated as @application/octet-stream@ (as specified in
-- <http://tools.ietf.org/html/rfc7231#section-3.1.1.5 RFC7231>.
2014-12-10 16:10:57 +01:00
-- This lets servant worry about extracting it from the request and turning
-- it into a value of the type you specify.
--
2015-01-13 20:40:41 +01:00
--
2014-12-10 16:10:57 +01:00
-- All it asks is for a 'FromJSON' instance.
--
-- Example:
--
2015-01-13 20:40:41 +01:00
-- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book
2014-12-10 16:10:57 +01:00
-- >
-- > server :: Server MyApi
-- > server = postBook
2015-09-12 14:11:24 +02:00
-- > where postBook :: Book -> ExceptT ServantErr IO Book
2014-12-10 16:10:57 +01:00
-- > postBook book = ...insert into your db...
2015-01-13 20:40:41 +01:00
instance ( AllCTUnrender list a, HasServer sublayout
) => HasServer (ReqBody list a :> sublayout) where
2014-12-10 16:10:57 +01:00
2015-05-03 01:45:17 +02:00
type ServerT (ReqBody list a :> sublayout) m =
a -> ServerT sublayout m
2014-12-10 16:10:57 +01:00
route Proxy subserver = WithRequest $ \ request ->
route (Proxy :: Proxy sublayout) (addBodyCheck subserver (bodyCheck request))
where
bodyCheck request = do
-- See HTTP RFC 2616, section 7.2.1
-- http://www.w3.org/Protocols/rfc2616/rfc2616-sec7.html#sec7.2.1
-- See also "W3C Internet Media Type registration, consistency of use"
-- http://www.w3.org/2001/tag/2002/0129-mime
let contentTypeH = fromMaybe "application/octet-stream"
$ lookup hContentType $ requestHeaders request
mrqbody <- handleCTypeH (Proxy :: Proxy list) (cs contentTypeH)
<$> lazyRequestBody request
case mrqbody of
Nothing -> return $ FailFatal err415
Just (Left e) -> return $ FailFatal err400 { errBody = cs e }
Just (Right v) -> return $ Route v
2014-12-10 16:10:57 +01:00
-- | Make sure the incoming request starts with @"/path"@, strip it and
-- pass the rest of the request path to @sublayout@.
instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where
2015-05-03 01:45:17 +02:00
type ServerT (path :> sublayout) m = ServerT sublayout m
route Proxy subserver = StaticRouter $
M.singleton (cs (symbolVal proxyPath))
(route (Proxy :: Proxy sublayout) subserver)
2014-12-10 16:10:57 +01:00
where proxyPath = Proxy :: Proxy path
instance HasServer api => HasServer (RemoteHost :> api) where
type ServerT (RemoteHost :> api) m = SockAddr -> ServerT api m
route Proxy subserver = WithRequest $ \req ->
route (Proxy :: Proxy api) (passToServer subserver $ remoteHost req)
instance HasServer api => HasServer (IsSecure :> api) where
type ServerT (IsSecure :> api) m = IsSecure -> ServerT api m
route Proxy subserver = WithRequest $ \req ->
route (Proxy :: Proxy api) (passToServer subserver $ secure req)
where secure req = if isSecure req then Secure else NotSecure
instance HasServer api => HasServer (Vault :> api) where
type ServerT (Vault :> api) m = Vault -> ServerT api m
route Proxy subserver = WithRequest $ \req ->
route (Proxy :: Proxy api) (passToServer subserver $ vault req)
instance HasServer api => HasServer (HttpVersion :> api) where
type ServerT (HttpVersion :> api) m = HttpVersion -> ServerT api m
route Proxy subserver = WithRequest $ \req ->
route (Proxy :: Proxy api) (passToServer subserver $ httpVersion req)
pathIsEmpty :: Request -> Bool
pathIsEmpty = go . pathInfo
where go [] = True
go [""] = True
go _ = False
ct_wildcard :: B.ByteString
ct_wildcard = "*" <> "/" <> "*" -- Because CPP