#if __GLASGOW_HASKELL__ < 710
#endif
module Servant.Server.Internal
( module Servant.Server.Internal
, module Servant.Server.Internal.PathInfo
, module Servant.Server.Internal.Router
, module Servant.Server.Internal.RoutingApplication
, module Servant.Server.Internal.ServantErr
) where
import Control.Applicative ((<$>))
import Control.Monad.Trans.Class (lift)
import Data.Bool (bool)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as BL
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Proxy
import Data.String (fromString)
import Data.String.Conversions (cs, (<>))
import Data.Text (Text)
import GHC.Generics
import GHC.TypeLits (KnownNat, KnownSymbol, natVal,
symbolVal)
import Network.HTTP.Types (HeaderName, Method,
Status(..), parseQueryText,
methodGet, methodHead,
hContentType, hAccept)
import Web.HttpApiData (FromHttpApiData,
parseHeaderMaybe,
parseQueryParamMaybe,
parseUrlPieceMaybe,
parseUrlPieces)
import Snap.Core hiding (Headers, Method,
getResponse, route,
method, withRequest)
import Servant.API ((:<|>) (..), (:>), BasicAuth,
Capture,
CaptureAll, Header,
IsSecure(..), QueryFlag,
QueryParam, QueryParams, Raw,
RemoteHost, ReqBody,
ReflectMethod(..), Verb)
import Servant.API.ContentTypes (AcceptHeader (..),
AllCTRender (..),
AllCTUnrender (..), AllMime(..), canHandleAcceptH)
import Servant.API.ResponseHeaders (Headers, getResponse, GetHeaders,
getHeaders)
import Servant.Server.Internal.BasicAuth
import Servant.Server.Internal.Context
import Servant.Server.Internal.PathInfo
import Servant.Server.Internal.Router
import Servant.Server.Internal.RoutingApplication
import Servant.Server.Internal.ServantErr
import Servant.Server.Internal.SnapShims
class HasServer api context (m :: * -> *) where
type ServerT api context m :: *
route :: MonadSnap m
=> Proxy api
-> Context context
-> Delayed m env (Server api context m)
-> Router m env
type Server api context m = ServerT api context m
instance (HasServer a ctx m, HasServer b ctx m) => HasServer (a :<|> b) ctx m where
type ServerT (a :<|> b) ctx m = ServerT a ctx m :<|> ServerT b ctx m
route Proxy ctx server = choice (route pa ctx ((\ (a :<|> _) -> a) <$> server))
(route pb ctx ((\ (_ :<|> b) -> b) <$> server))
where pa = Proxy :: Proxy a
pb = Proxy :: Proxy b
captured :: FromHttpApiData a => proxy (Capture sym a) -> Text -> Maybe a
captured _ = parseUrlPieceMaybe
instance (FromHttpApiData a, HasServer sublayout context m)
=> HasServer (Capture capture a :> sublayout) context m where
type ServerT (Capture capture a :> sublayout) context m =
a -> ServerT sublayout context m
route Proxy ctx d =
CaptureRouter $
route (Proxy :: Proxy sublayout) ctx
(addCapture d $ \ txt -> case parseUrlPieceMaybe txt of
Nothing -> delayedFail err400
Just v -> return v
)
instance (FromHttpApiData a, HasServer sublayout context m)
=> HasServer (CaptureAll capture a :> sublayout) context m where
type ServerT (CaptureAll capture a :> sublayout) context m =
[a] -> ServerT sublayout context m
route Proxy ctx d =
CaptureAllRouter $
route (Proxy :: Proxy sublayout) ctx
(addCapture d $ \ txts -> case parseUrlPieces txts of
Left _ -> delayedFail err400
Right v -> return v
)
allowedMethodHead :: Method -> Request -> Bool
allowedMethodHead method request =
method == methodGet && unSnapMethod (rqMethod request) == methodHead
allowedMethod :: Method -> Request -> Bool
allowedMethod method request =
allowedMethodHead method request || unSnapMethod (rqMethod request) == method
processMethodRouter :: Maybe (BL.ByteString, BL.ByteString) -> Status -> Method
-> Maybe [(HeaderName, B.ByteString)]
-> Request -> RouteResult Response
processMethodRouter handleA status method rHeaders 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 [] rHeaders
methodCheck :: MonadSnap m => Method -> Request -> DelayedM m ()
methodCheck method request
| allowedMethod method request = return ()
| otherwise = delayedFail err405
acceptCheck :: (AllMime list, MonadSnap m) => Proxy list -> B.ByteString -> DelayedM m ()
acceptCheck proxy accH
| canHandleAcceptH proxy (AcceptHeader accH) = return ()
| otherwise = delayedFail err406
methodRouter :: (AllCTRender ctypes a, MonadSnap m)
=> Method -> Proxy ctypes -> Status
-> Delayed m env (m a)
-> Router m env
methodRouter method proxy status action = leafRouter route'
where
route' env request respond =
let accH = fromMaybe ct_wildcard $ getHeader hAccept 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, MonadSnap m)
=> Method -> Proxy ctypes -> Status
-> Delayed m env (m (Headers h v))
-> Router m env
methodRouterHeaders method proxy status action = leafRouter route'
where
route' env request respond =
let accH = fromMaybe ct_wildcard $ getHeader hAccept request
in runAction (action `addMethodCheck` methodCheck method request
`addAcceptCheck` acceptCheck proxy accH
) env request respond $ \ output -> do
let hdrs = getHeaders output
handleA = handleAcceptH proxy (AcceptHeader accH) (getResponse output)
processMethodRouter handleA status method (Just hdrs) request
instance (AllCTRender ctypes a,
ReflectMethod method,
KnownNat status)
=> HasServer (Verb method status ctypes a) context m where
type ServerT (Verb method status ctypes a) context 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 (AllCTRender ctypes a,
ReflectMethod method,
KnownNat status,
GetHeaders (Headers h a))
=> HasServer (Verb method status ctypes (Headers h a)) context m where
type ServerT (Verb method status ctypes (Headers h a)) context 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 sublayout context m)
=> HasServer (Header sym a :> sublayout) context m where
type ServerT (Header sym a :> sublayout) context m =
Maybe a -> ServerT sublayout context m
route Proxy ctx subserver =
let mheader req = parseHeaderMaybe =<< getHeader str req
in route (Proxy :: Proxy sublayout) ctx (passToServer subserver mheader)
where str = fromString $ symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context m)
=> HasServer (QueryParam sym a :> sublayout) context m where
type ServerT (QueryParam sym a :> sublayout) context m =
Maybe a -> ServerT sublayout context m
route Proxy ctx subserver =
let querytext r = parseQueryText $ rqQueryString r
param r =
case lookup paramname (querytext r) of
Nothing -> Nothing
Just Nothing -> Nothing
Just (Just v) -> parseQueryParamMaybe v
in route (Proxy :: Proxy sublayout) ctx (passToServer subserver param)
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, FromHttpApiData a, HasServer sublayout context m)
=> HasServer (QueryParams sym a :> sublayout) context m where
type ServerT (QueryParams sym a :> sublayout) context m =
[a] -> ServerT sublayout context m
route Proxy ctx subserver =
let querytext r = parseQueryText $ rqQueryString r
parameters r = filter looksLikeParam (querytext r)
values r = mapMaybe (convert . snd) (parameters r)
in route (Proxy :: Proxy sublayout) ctx (passToServer subserver values)
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
looksLikeParam (name, _) = name == paramname || name == (paramname <> "[]")
convert Nothing = Nothing
convert (Just v) = parseQueryParamMaybe v
instance (KnownSymbol sym, HasServer sublayout context m)
=> HasServer (QueryFlag sym :> sublayout) context m where
type ServerT (QueryFlag sym :> sublayout) context m =
Bool -> ServerT sublayout context m
route Proxy ctx subserver =
let querytext r = parseQueryText $ rqQueryString r
param r = case lookup paramname (querytext r) of
Just Nothing -> True
Just (Just v) -> examine v
Nothing -> False
in route (Proxy :: Proxy sublayout) ctx (passToServer subserver param)
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
examine v | v == "true" || v == "1" || v == "" = True
| otherwise = False
instance HasServer Raw context m where
type ServerT Raw context m = m ()
route Proxy _ rawApplication = RawRouter $ \ env request respond -> do
r <- runDelayed rawApplication env request
case r of
Route app -> (snapToApplication' app) request (respond . Route)
Fail a -> respond $ Fail a
FailFatal e -> respond $ FailFatal e
instance ( AllCTUnrender list a, HasServer sublayout context m
) => HasServer (ReqBody list a :> sublayout) context m where
type ServerT (ReqBody list a :> sublayout) context m =
a -> ServerT sublayout context m
route Proxy ctx subserver =
route (Proxy :: Proxy sublayout) ctx (addBodyCheck (subserver ) bodyCheck')
where
bodyCheck' = do
req <- lift getRequest
let contentTypeH = fromMaybe "application/octet-stream" $ getHeader hContentType req
mrqbody <- handleCTypeH (Proxy :: Proxy list) (cs contentTypeH) <$>
lift (readRequestBody 2147483647)
case mrqbody of
Nothing -> delayedFailFatal err415
Just (Left e) -> delayedFailFatal err400 { errBody = cs e }
Just (Right v) -> return v
instance (KnownSymbol path, HasServer sublayout context m) => HasServer (path :> sublayout) context m where
type ServerT (path :> sublayout) context m = ServerT sublayout context m
route Proxy ctx subserver =
pathRouter
(cs (symbolVal proxyPath))
(route (Proxy :: Proxy sublayout) ctx subserver)
where proxyPath = Proxy :: Proxy path
instance HasServer api context m => HasServer (HttpVersion :> api) context m where
type ServerT (HttpVersion :> api) context m = HttpVersion -> ServerT api context m
route Proxy ctx subserver =
route (Proxy :: Proxy api) ctx (passToServer subserver rqVersion)
instance HasServer api context m => HasServer (IsSecure :> api) context m where
type ServerT (IsSecure :> api) context m = IsSecure -> ServerT api context m
route Proxy ctx subserver =
route (Proxy :: Proxy api) ctx (passToServer subserver (bool NotSecure Secure . rqIsSecure))
instance HasServer api context m => HasServer (RemoteHost :> api) context m where
type ServerT (RemoteHost :> api) context m = B.ByteString -> ServerT api context m
route Proxy ctx subserver =
route (Proxy :: Proxy api) ctx (passToServer subserver rqHostName)
data BasicAuthResult usr = Unauthorized | BadPassword | NoSuchUser | Authorized usr
deriving (Functor, Eq, Read, Show, Generic)
instance (HasServer api context m,
KnownSymbol realm,
HasContextEntry context (BasicAuthCheck m usr)
) => HasServer (BasicAuth realm usr :> api) context m where
type ServerT (BasicAuth realm usr :> api) context m = usr -> ServerT api context m
route Proxy ctx subserver =
route (Proxy :: Proxy api) ctx (subserver `addAuthCheck` authCheck)
where
realm = B.pack $ symbolVal (Proxy :: Proxy realm)
basicAuthContext = getContextEntry ctx
authCheck = withRequest $ \req -> runBasicAuth req realm basicAuthContext
ct_wildcard :: B.ByteString
ct_wildcard = "*" <> "/" <> "*"