#include "overlapping-compat.h"
module Servant.Server.Internal
( module Servant.Server.Internal
, module Servant.Server.Internal.BasicAuth
, module Servant.Server.Internal.Context
, module Servant.Server.Internal.Handler
, module Servant.Server.Internal.Router
, module Servant.Server.Internal.RoutingApplication
, module Servant.Server.Internal.ServantErr
) where
import Control.Monad.Trans (liftIO)
import Control.Monad.Trans.Resource (runResourceT)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC8
import qualified Data.ByteString.Lazy as BL
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Either (partitionEithers)
import Data.String (fromString)
import Data.String.Conversions (cs, (<>))
import Data.Tagged (Tagged(..), untag)
import qualified Data.Text as T
import Data.Typeable
import GHC.TypeLits (KnownNat, KnownSymbol, natVal,
symbolVal)
import Network.HTTP.Types hiding (Header, ResponseHeaders)
import Network.Socket (SockAddr)
import Network.Wai (Application, Request, Response,
httpVersion, isSecure,
lazyRequestBody,
rawQueryString, remoteHost,
requestHeaders, requestMethod,
responseLBS, vault)
import Prelude ()
import Prelude.Compat
import Web.HttpApiData (FromHttpApiData, parseHeader,
parseQueryParam,
parseUrlPieceMaybe,
parseUrlPieces)
import Servant.API ((:<|>) (..), (:>), BasicAuth, Capture,
CaptureAll, Verb, EmptyAPI,
ReflectMethod(reflectMethod),
IsSecure(..), Header, QueryFlag,
QueryParam, QueryParams, Raw,
RemoteHost, ReqBody, Vault,
WithNamedContext)
import Servant.API.ContentTypes (AcceptHeader (..),
AllCTRender (..),
AllCTUnrender (..),
AllMime,
canHandleAcceptH)
import Servant.API.ResponseHeaders (GetHeaders, Headers, getHeaders,
getResponse)
import Servant.Server.Internal.Context
import Servant.Server.Internal.BasicAuth
import Servant.Server.Internal.Handler
import Servant.Server.Internal.Router
import Servant.Server.Internal.RoutingApplication
import Servant.Server.Internal.ServantErr
class HasServer api context where
type ServerT api (m :: * -> *) :: *
route ::
Proxy api
-> Context context
-> Delayed env (Server api)
-> Router env
type Server api = ServerT api Handler
instance (HasServer a context, HasServer b context) => HasServer (a :<|> b) context where
type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m
route Proxy context server = choice (route pa context ((\ (a :<|> _) -> a) <$> server))
(route pb context ((\ (_ :<|> b) -> b) <$> server))
where pa = Proxy :: Proxy a
pb = Proxy :: Proxy b
instance (KnownSymbol capture, FromHttpApiData a, HasServer api context)
=> HasServer (Capture capture a :> api) context where
type ServerT (Capture capture a :> api) m =
a -> ServerT api m
route Proxy context d =
CaptureRouter $
route (Proxy :: Proxy api)
context
(addCapture d $ \ txt -> case parseUrlPieceMaybe txt of
Nothing -> delayedFail err400
Just v -> return v
)
instance (KnownSymbol capture, FromHttpApiData a, HasServer sublayout context)
=> HasServer (CaptureAll capture a :> sublayout) context where
type ServerT (CaptureAll capture a :> sublayout) m =
[a] -> ServerT sublayout m
route Proxy context d =
CaptureAllRouter $
route (Proxy :: Proxy sublayout)
context
(addCapture d $ \ txts -> case parseUrlPieces txts of
Left _ -> delayedFail err400
Right v -> return v
)
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 :: Maybe (BL.ByteString, BL.ByteString) -> Status -> Method
-> Maybe [(HeaderName, B.ByteString)]
-> Request -> RouteResult Response
processMethodRouter handleA status method headers request = case handleA of
Nothing -> FailFatal err406
Just (contentT, body) -> Route $ responseLBS status hdrs bdy
where
bdy = if allowedMethodHead method request then "" else body
hdrs = (hContentType, cs contentT) : (fromMaybe [] headers)
methodCheck :: Method -> Request -> DelayedIO ()
methodCheck method request
| allowedMethod method request = return ()
| otherwise = delayedFail err405
acceptCheck :: (AllMime list) => Proxy list -> B.ByteString -> DelayedIO ()
acceptCheck proxy accH
| canHandleAcceptH proxy (AcceptHeader accH) = return ()
| otherwise = delayedFail err406
methodRouter :: (AllCTRender ctypes a)
=> Method -> Proxy ctypes -> Status
-> Delayed env (Handler a)
-> Router env
methodRouter method proxy status action = leafRouter route'
where
route' env request respond =
let accH = fromMaybe ct_wildcard $ lookup hAccept $ requestHeaders request
in runAction (action `addMethodCheck` methodCheck method request
`addAcceptCheck` acceptCheck proxy accH
) env request respond $ \ output -> do
let handleA = handleAcceptH proxy (AcceptHeader accH) output
processMethodRouter handleA status method Nothing request
methodRouterHeaders :: (GetHeaders (Headers h v), AllCTRender ctypes v)
=> Method -> Proxy ctypes -> Status
-> Delayed env (Handler (Headers h v))
-> Router env
methodRouterHeaders method proxy status action = leafRouter route'
where
route' env request respond =
let accH = fromMaybe ct_wildcard $ lookup hAccept $ requestHeaders request
in runAction (action `addMethodCheck` methodCheck method request
`addAcceptCheck` acceptCheck proxy accH
) env request respond $ \ output -> do
let headers = getHeaders output
handleA = handleAcceptH proxy (AcceptHeader accH) (getResponse output)
processMethodRouter handleA status method (Just headers) request
instance OVERLAPPABLE_
( AllCTRender ctypes a, ReflectMethod method, KnownNat status
) => HasServer (Verb method status ctypes a) context where
type ServerT (Verb method status ctypes a) m = m a
route Proxy _ = methodRouter method (Proxy :: Proxy ctypes) status
where method = reflectMethod (Proxy :: Proxy method)
status = toEnum . fromInteger $ natVal (Proxy :: Proxy status)
instance OVERLAPPING_
( AllCTRender ctypes a, ReflectMethod method, KnownNat status
, GetHeaders (Headers h a)
) => HasServer (Verb method status ctypes (Headers h a)) context where
type ServerT (Verb method status ctypes (Headers h a)) m = m (Headers h a)
route Proxy _ = methodRouterHeaders method (Proxy :: Proxy ctypes) status
where method = reflectMethod (Proxy :: Proxy method)
status = toEnum . fromInteger $ natVal (Proxy :: Proxy status)
instance (KnownSymbol sym, FromHttpApiData a, HasServer api context)
=> HasServer (Header sym a :> api) context where
type ServerT (Header sym a :> api) m =
Maybe a -> ServerT api m
route Proxy context subserver = route (Proxy :: Proxy api) context $
subserver `addHeaderCheck` withRequest headerCheck
where
headerName = symbolVal (Proxy :: Proxy sym)
headerCheck req =
case lookup (fromString headerName) (requestHeaders req) of
Nothing -> return Nothing
Just txt ->
case parseHeader txt of
Left e -> delayedFailFatal err400
{ errBody = cs $ "Error parsing header "
<> fromString headerName
<> " failed: " <> e
}
Right header -> return $ Just header
instance (KnownSymbol sym, FromHttpApiData a, HasServer api context)
=> HasServer (QueryParam sym a :> api) context where
type ServerT (QueryParam sym a :> api) m =
Maybe a -> ServerT api m
route Proxy context subserver =
let querytext req = parseQueryText $ rawQueryString req
parseParam req =
case lookup paramname (querytext req) of
Nothing -> return Nothing
Just Nothing -> return Nothing
Just (Just v) ->
case parseQueryParam v of
Left e -> delayedFailFatal err400
{ errBody = cs $ "Error parsing query parameter "
<> paramname <> " failed: " <> e
}
Right param -> return $ Just param
delayed = addParameterCheck subserver . withRequest $ \req ->
parseParam req
in route (Proxy :: Proxy api) context delayed
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, FromHttpApiData a, HasServer api context)
=> HasServer (QueryParams sym a :> api) context where
type ServerT (QueryParams sym a :> api) m =
[a] -> ServerT api m
route Proxy context subserver = route (Proxy :: Proxy api) context $
subserver `addParameterCheck` withRequest paramsCheck
where
paramname = cs $ symbolVal (Proxy :: Proxy sym)
paramsCheck req =
case partitionEithers $ fmap parseQueryParam params of
([], parsed) -> return parsed
(errs, _) -> delayedFailFatal err400
{ errBody = cs $ "Error parsing query parameter(s) "
<> paramname <> " failed: "
<> T.intercalate ", " errs
}
where
params :: [T.Text]
params = mapMaybe snd
. filter (looksLikeParam . fst)
. parseQueryText
. rawQueryString
$ req
looksLikeParam name = name == paramname || name == (paramname <> "[]")
instance (KnownSymbol sym, HasServer api context)
=> HasServer (QueryFlag sym :> api) context where
type ServerT (QueryFlag sym :> api) m =
Bool -> ServerT api m
route Proxy context subserver =
let querytext r = parseQueryText $ rawQueryString r
param r = case lookup paramname (querytext r) of
Just Nothing -> True
Just (Just v) -> examine v
Nothing -> False
in route (Proxy :: Proxy api) context (passToServer subserver param)
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
examine v | v == "true" || v == "1" || v == "" = True
| otherwise = False
instance HasServer Raw context where
type ServerT Raw m = Tagged m Application
route Proxy _ rawApplication = RawRouter $ \ env request respond -> runResourceT $ do
r <- runDelayed rawApplication env request
liftIO $ go r request respond
where go r request respond = case r of
Route app -> untag app request (respond . Route)
Fail a -> respond $ Fail a
FailFatal e -> respond $ FailFatal e
instance ( AllCTUnrender list a, HasServer api context
) => HasServer (ReqBody list a :> api) context where
type ServerT (ReqBody list a :> api) m =
a -> ServerT api m
route Proxy context subserver
= route (Proxy :: Proxy api) context $
addBodyCheck subserver ctCheck bodyCheck
where
ctCheck = withRequest $ \ request -> do
let contentTypeH = fromMaybe "application/octet-stream"
$ lookup hContentType $ requestHeaders request
case canHandleCTypeH (Proxy :: Proxy list) (cs contentTypeH) :: Maybe (BL.ByteString -> Either String a) of
Nothing -> delayedFailFatal err415
Just f -> return f
bodyCheck f = withRequest $ \ request -> do
mrqbody <- f <$> liftIO (lazyRequestBody request)
case mrqbody of
Left e -> delayedFailFatal err400 { errBody = cs e }
Right v -> return v
instance (KnownSymbol path, HasServer api context) => HasServer (path :> api) context where
type ServerT (path :> api) m = ServerT api m
route Proxy context subserver =
pathRouter
(cs (symbolVal proxyPath))
(route (Proxy :: Proxy api) context subserver)
where proxyPath = Proxy :: Proxy path
instance HasServer api context => HasServer (RemoteHost :> api) context where
type ServerT (RemoteHost :> api) m = SockAddr -> ServerT api m
route Proxy context subserver =
route (Proxy :: Proxy api) context (passToServer subserver remoteHost)
instance HasServer api context => HasServer (IsSecure :> api) context where
type ServerT (IsSecure :> api) m = IsSecure -> ServerT api m
route Proxy context subserver =
route (Proxy :: Proxy api) context (passToServer subserver secure)
where secure req = if isSecure req then Secure else NotSecure
instance HasServer api context => HasServer (Vault :> api) context where
type ServerT (Vault :> api) m = Vault -> ServerT api m
route Proxy context subserver =
route (Proxy :: Proxy api) context (passToServer subserver vault)
instance HasServer api context => HasServer (HttpVersion :> api) context where
type ServerT (HttpVersion :> api) m = HttpVersion -> ServerT api m
route Proxy context subserver =
route (Proxy :: Proxy api) context (passToServer subserver httpVersion)
data EmptyServer = EmptyServer deriving (Typeable, Eq, Show, Bounded, Enum)
emptyServer :: ServerT EmptyAPI m
emptyServer = Tagged EmptyServer
instance HasServer EmptyAPI context where
type ServerT EmptyAPI m = Tagged m EmptyServer
route Proxy _ _ = StaticRouter mempty mempty
instance ( KnownSymbol realm
, HasServer api context
, HasContextEntry context (BasicAuthCheck usr)
)
=> HasServer (BasicAuth realm usr :> api) context where
type ServerT (BasicAuth realm usr :> api) m = usr -> ServerT api m
route Proxy context subserver =
route (Proxy :: Proxy api) context (subserver `addAuthCheck` authCheck)
where
realm = BC8.pack $ symbolVal (Proxy :: Proxy realm)
basicAuthContext = getContextEntry context
authCheck = withRequest $ \ req -> runBasicAuth req realm basicAuthContext
ct_wildcard :: B.ByteString
ct_wildcard = "*" <> "/" <> "*"
instance (HasContextEntry context (NamedContext name subContext), HasServer subApi subContext)
=> HasServer (WithNamedContext name subContext subApi) context where
type ServerT (WithNamedContext name subContext subApi) m =
ServerT subApi m
route Proxy context delayed =
route subProxy subContext delayed
where
subProxy :: Proxy subApi
subProxy = Proxy
subContext :: Context subContext
subContext = descendIntoNamedContext (Proxy :: Proxy name) context