{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Boots.Factory.Web(
buildWeb
, HasWeb(..)
, HasWebConfig(..)
, WebConfig(..)
, EndpointConfig(..)
, WebEnv(..)
, newWebEnv
, askEnv
, EnvMiddleware
, registerMiddleware
, tryServe
, trySwagger
, tryServeWithSwagger
, HasSwagger(..)
, HasServer(..)
, HasContextEntry(..)
, SetContextEntry(..)
, Context(..)
, logException
, whenException
, ToSchema
, Vault
) where
import Boots
import Boots.Endpoint.Swagger
import Boots.Metrics
import Control.Exception
( SomeException
, fromException
)
import qualified Data.HashMap.Strict as HM
import Data.Maybe
import Data.Swagger (Swagger)
import Data.Swagger.Schema (ToSchema)
import Data.Text (Text)
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Encoding
import Data.Word
import Network.Wai
import Network.Wai.Handler.Warp
import Salak
import Servant
import Servant.Server.Internal.ServerError (responseServerError)
import Servant.Swagger
data WebConfig = WebConfig
{ hostname :: !String
, port :: !Word16
} deriving (Eq, Show)
instance Default WebConfig where
{-# INLINE def #-}
def = WebConfig "localhost" 8888
instance FromProp m WebConfig where
{-# INLINE fromProp #-}
fromProp = WebConfig
<$> "host" .?: hostname
<*> "port" .?: port
class HasWebConfig env where
askWebConfig :: Lens' env WebConfig
instance HasWebConfig WebConfig where
askWebConfig = id
data EndpointConfig = EndpointConfig
{ enabled :: Bool
, endpoints :: HM.HashMap Text Bool
}
instance FromProp m EndpointConfig where
fromProp = EndpointConfig
<$> "enabled" .?= True
<*> "enabled" .?= HM.empty
data WebEnv env context = WebEnv
{ serveW :: forall api. HasServer api context
=> Proxy api -> Context context -> Server api -> Application
, serveA :: forall api. HasSwagger api
=> Proxy api -> Swagger
, middleware :: EnvMiddleware env
, envs :: AppEnv env
, context :: AppEnv env -> Context context
, config :: WebConfig
, endpoint :: EndpointConfig
, store :: Store
}
instance HasWebConfig (WebEnv env context) where
askWebConfig = lens config (\x y -> x { config = y})
instance HasMetrics (WebEnv env context) where
{-# INLINE askMetrics #-}
askMetrics = lens store (\x y -> x { store = y})
instance HasApp (WebEnv env context) env where
{-# INLINE askApp #-}
askApp = lens envs (\x y -> x { envs = y})
instance HasSalak (WebEnv env context) where
{-# INLINE askSalak #-}
askSalak = askApp @(WebEnv env context) @env . askSalak
instance HasLogger (WebEnv env context) where
{-# INLINE askLogger #-}
askLogger = askApp @(WebEnv env context) @env . askLogger
instance HasRandom (WebEnv env context) where
{-# INLINE askRandom #-}
askRandom = askApp @(WebEnv env context) @env . askRandom
instance HasHealth (WebEnv env context) where
{-# INLINE askHealth #-}
askHealth = askApp @(WebEnv env context) @env . askHealth
class
( HasContextEntry context (AppEnv env)
, SetContextEntry context (AppEnv env))
=> HasWeb context env | context -> env where
askWeb :: Lens' (Context context) (AppEnv env)
askWeb = lens getContextEntry (flip setContextEntry)
instance HasWeb (AppEnv env : as) env
class HasContextEntry context env => SetContextEntry context env where
setContextEntry :: env -> Context context -> Context context
instance {-# OVERLAPPABLE #-} SetContextEntry as env => SetContextEntry (a : as) env where
{-# INLINE setContextEntry #-}
setContextEntry env (a :. as) = a :. setContextEntry env as
instance SetContextEntry (env : as) env where
{-# INLINE setContextEntry #-}
setContextEntry env (_ :. as) = env :. as
instance HasWeb context env => HasApp (Context context) env where
askApp = askWeb @context @env
instance HasWeb context env => HasSalak (Context context) where
askSalak = askWeb @context @env . askSalak
instance HasWeb context env => HasLogger (Context context) where
askLogger = askWeb @context @env . askLogger
instance HasWeb context env => HasRandom (Context context) where
askRandom = askWeb @context @env . askRandom
{-# INLINE newWebEnv #-}
newWebEnv
:: HasContextEntry context (AppEnv env)
=> AppEnv env
-> (AppEnv env -> Context context)
-> WebConfig
-> EndpointConfig
-> Store
-> WebEnv env context
newWebEnv = WebEnv serveWithContext toSwagger id
{-# INLINE askEnv #-}
askEnv :: MonadMask n => Factory n (WebEnv env context) (AppEnv env)
askEnv = envs <$> getEnv
type EnvMiddleware env = (AppEnv env -> Application) -> AppEnv env -> Application
{-# INLINE registerMiddleware #-}
registerMiddleware
:: MonadMask n
=> EnvMiddleware env
-> Factory n (WebEnv env context) ()
registerMiddleware md = modifyEnv $ \web -> web { middleware = md . middleware web }
buildWeb
:: forall context env n
. ( MonadIO n
, MonadMask n
, HasWeb context env
)
=> Proxy context
-> Proxy env
-> Factory n (WebEnv env context) (IO ())
buildWeb _ _ = do
(WebEnv{..} :: WebEnv env context) <- getEnv
within envs $ do
let AppEnv{..} = envs
serveWarp WebConfig{..} = runSettings
$ defaultSettings
& setPort (fromIntegral port)
& setOnExceptionResponse whenException
& setOnException (\_ -> runAppT envs . logException)
let ok = enabled endpoint && HM.lookup "swagger" (endpoints endpoint) /= Just False
when ok
$ logInfo
$ "Swagger enabled: http://"
<> toLogStr (hostname config)
<> ":"
<> toLogStr (port config)
<> "/endpoints/swagger"
logInfo $ "Service started on port(s): " <> toLogStr (port config)
delay $ logInfo "Service ended"
return
$ serveWarp config
$ flip middleware envs
$ \env1 -> if ok
then serveW (Proxy @EndpointSwagger) (context env1)
(return $ baseInfo (hostname config) name version (port config) $ serveA $ Proxy @EmptyAPI)
else serveW (Proxy @EmptyAPI) (context env1) emptyServer
{-# INLINE logException #-}
logException :: HasLogger env => SomeException -> App env ()
logException = logError . toLogStr . formatException
{-# INLINE whenException #-}
whenException :: SomeException -> Network.Wai.Response
whenException e = responseServerError
$ fromMaybe err400 { errBody = fromString $ show e} (fromException e :: Maybe ServerError)
{-# INLINE formatException #-}
formatException :: SomeException -> Text
formatException e = case fromException e of
Just ServerError{..} -> fromString errReasonPhrase <> " " <> toStrict (decodeUtf8 errBody)
_ -> fromString $ show e
tryServeWithSwagger
:: forall env context api n
. ( HasContextEntry context (AppEnv env)
, HasServer api context
, HasSwagger api
, MonadMask n)
=> Bool
-> Proxy context
-> Proxy api
-> ServerT api (App (AppEnv env))
-> Factory n (WebEnv env context) ()
tryServeWithSwagger b pc proxy server = do
trySwagger b proxy
tryServe b pc proxy server
trySwagger
:: (MonadMask n, HasSwagger api)
=> Bool
-> Proxy api
-> Factory n (WebEnv env context) ()
trySwagger b api = when b $ modifyEnv $ \web -> web { serveA = serveA web . gop api }
tryServe
:: forall env context api n
. ( HasContextEntry context (AppEnv env)
, HasServer api context
, MonadMask n)
=> Bool
-> Proxy context
-> Proxy api
-> ServerT api (App (AppEnv env))
-> Factory n (WebEnv env context) ()
tryServe b pc proxy server = when b $
modifyEnv
$ \web -> web { serveW = \p c s -> serveW web (gop p proxy) c
$ s :<|> hoistServerWithContext proxy pc (go . runAppT (getContextEntry c :: AppEnv env)) server }
where
{-# INLINE go #-}
go :: IO a -> Servant.Handler a
go = liftIO
{-# INLINE gop #-}
gop :: forall a b. Proxy a -> Proxy b -> Proxy (a :<|> b)
gop _ _ = Proxy