Copyright | 2019 Daniel YU |
---|---|
License | MIT |
Maintainer | leptonyu@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
A quick out-of-box factory using to build web application with many useful builtin web components, based on boots-app and servant.
- Builtin metrics, use ekg-core as backend.
- Builtin tracing log, support B3-Tags.
- Builtin endpoints, info, healthcheck, logger, metrics, refresh configuration, swagger api.
- Builtin error management.
Hackage boots-consul provides consul support for building microservices.
Synopsis
- bootWeb :: forall api env context. (HasServer api context, HasSwagger api, HasWeb context env) => String -> Version -> Factory IO (AppEnv ()) env -> Factory IO (AppEnv env) (AppEnv env -> Context context) -> Factory IO (WebEnv env context) () -> Proxy api -> ServerT api (App (AppEnv env)) -> IO ()
- bootWebEnv :: String -> Version -> Factory IO (AppEnv ()) env -> Factory IO (WebEnv env '[AppEnv env]) () -> IO ()
- runContext :: HasContextEntry context env => Context context -> AppT env m () -> m ()
- buildWeb :: forall context env n. (MonadIO n, MonadMask n, HasWeb context env) => Proxy context -> Proxy env -> Factory n (WebEnv env context) (IO ())
- class (HasContextEntry context (AppEnv env), SetContextEntry context (AppEnv env)) => HasWeb context env | context -> env where
- class HasWebConfig env where
- askWebConfig :: Lens' env WebConfig
- data WebConfig = WebConfig {}
- data EndpointConfig = EndpointConfig {}
- 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
- newWebEnv :: HasContextEntry context (AppEnv env) => AppEnv env -> (AppEnv env -> Context context) -> WebConfig -> EndpointConfig -> Store -> WebEnv env context
- askEnv :: MonadMask n => Factory n (WebEnv env context) (AppEnv env)
- type EnvMiddleware env = (AppEnv env -> Application) -> AppEnv env -> Application
- registerMiddleware :: MonadMask n => EnvMiddleware env -> Factory n (WebEnv env context) ()
- 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) ()
- trySwagger :: (MonadMask n, HasSwagger api) => Bool -> Proxy api -> Factory n (WebEnv env context) ()
- 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) ()
- class HasSwagger (api :: k) where
- class HasServer (api :: k) (context :: [Type]) where
- class HasContextEntry (context :: [Type]) val where
- getContextEntry :: Context context -> val
- class HasContextEntry context env => SetContextEntry context env where
- setContextEntry :: env -> Context context -> Context context
- data Context (contextTypes :: [Type]) where
- logException :: HasLogger env => SomeException -> App env ()
- whenException :: SomeException -> Response
- class ToSchema a
- type Vault = Vault RealWorld
- class HasMetrics env where
- askMetrics :: Lens' env Store
- data Store
- newStore :: IO Store
- module Boots.Factory.Endpoint
- module Boots.Factory.Trace
- module Boots.Factory.Error
- module Boots.Factory.Random
Boot web
:: (HasServer api context, HasSwagger api, HasWeb context env) | |
=> String | Application name. |
-> Version | Application version. |
-> Factory IO (AppEnv ()) env | Function which generates |
-> Factory IO (AppEnv env) (AppEnv env -> Context context) | Function which generates |
-> Factory IO (WebEnv env context) () | Customized |
-> Proxy api | Api proxy. |
-> ServerT api (App (AppEnv env)) | Servant api server. |
-> IO () |
A out-of-box web application booter with many predefined components.
bootWebEnv :: String -> Version -> Factory IO (AppEnv ()) env -> Factory IO (WebEnv env '[AppEnv env]) () -> IO () Source #
A out-of-box web application booter with many predefined components. A more generic version use bootWeb
runContext :: HasContextEntry context env => Context context -> AppT env m () -> m () Source #
Run context.
:: (MonadIO n, MonadMask n, HasWeb context env) | |
=> Proxy context |
|
-> Proxy env |
|
-> Factory n (WebEnv env context) (IO ()) | Factory which create an application from |
Build a web application from WebEnv
.
class (HasContextEntry context (AppEnv env), SetContextEntry context (AppEnv env)) => HasWeb context env | context -> env where Source #
Nothing
Configuration
class HasWebConfig env where Source #
Environment values with WebConfig
.
askWebConfig :: Lens' env WebConfig Source #
Instances
HasWebConfig WebConfig Source # | |
Defined in Boots.Factory.Web | |
HasWebConfig (WebEnv env context) Source # | Environment values with |
Defined in Boots.Factory.Web |
Application Configuration.
data EndpointConfig Source #
Endpoint configuration.
Instances
FromProp m EndpointConfig Source # | |
Defined in Boots.Factory.Web fromProp :: Prop m EndpointConfig # |
Environment
data WebEnv env context Source #
Web environment, which defined all components to build a web application.
WebEnv | |
|
Instances
HasRandom (WebEnv env context) Source # | |
HasLogger (WebEnv env context) Source # | |
HasSalak (WebEnv env context) Source # | |
HasHealth (WebEnv env context) Source # | |
HasMetrics (WebEnv env context) Source # | |
Defined in Boots.Factory.Web | |
HasWebConfig (WebEnv env context) Source # | Environment values with |
Defined in Boots.Factory.Web | |
HasApp (WebEnv env context) env Source # | |
:: HasContextEntry context (AppEnv env) | |
=> AppEnv env | Application environment. |
-> (AppEnv env -> Context context) | Function used to generate |
-> WebConfig | Web configuration. |
-> EndpointConfig | Endpoint configuration. |
-> Store | Metrics store. |
-> WebEnv env context |
Create a web environment.
askEnv :: MonadMask n => Factory n (WebEnv env context) (AppEnv env) Source #
Get application environment env
.
Modified Middleware
type EnvMiddleware env = (AppEnv env -> Application) -> AppEnv env -> Application Source #
Modified wai Middleware
, which support modify env
.
registerMiddleware :: MonadMask n => EnvMiddleware env -> Factory n (WebEnv env context) () Source #
Register a modified middleware.
Api serve
:: (HasContextEntry context (AppEnv env), HasServer api context, MonadMask n) | |
=> Bool | If do this action. |
-> Proxy context | Context proxy. |
-> Proxy api | Api proxy. |
-> ServerT api (App (AppEnv env)) | Api server. |
-> Factory n (WebEnv env context) () |
Try serve a web server.
:: (MonadMask n, HasSwagger api) | |
=> Bool | If do this action. |
-> Proxy api | Api proxy. |
-> Factory n (WebEnv env context) () |
Try serve a swagger definition.
:: (HasContextEntry context (AppEnv env), HasServer api context, HasSwagger api, MonadMask n) | |
=> Bool | If do this action. |
-> Proxy context | Context proxy. |
-> Proxy api | Api proxy. |
-> ServerT api (App (AppEnv env)) | Api server. |
-> Factory n (WebEnv env context) () |
Serve web server with swagger.
Utilities
class HasSwagger (api :: k) where #
Generate a Swagger specification for a servant API.
To generate Swagger specification, your data types need
and/or ToParamSchema
instances.ToSchema
is used for ToParamSchema
, Capture
and QueryParam
.
Header
is used for ToSchema
and response data types.ReqBody
You can easily derive those instances via Generic
.
For more information, refer to swagger2 documentation.
Example:
newtype Username = Username String deriving (Generic, ToText) instance ToParamSchema Username data User = User { username :: Username , fullname :: String } deriving (Generic) instance ToJSON User instance ToSchema User type MyAPI = QueryParam "username" Username :> Get '[JSON] User mySwagger :: Swagger mySwagger = toSwagger (Proxy :: Proxy MyAPI)
Instances
class HasServer (api :: k) (context :: [Type]) where #
route :: Proxy api -> Context context -> Delayed env (Server api) -> Router env #
hoistServerWithContext :: Proxy api -> Proxy context -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n #
Instances
HasServer Raw context | 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" |
HasServer EmptyAPI context | The server for an type MyApi = "nothing" :> EmptyApi server :: Server MyApi server = emptyAPIServer |
(TypeError (HasServerArrowTypeError a b) :: Constraint) => HasServer (a -> b :: Type) context | This instance prevents from accidentally using '->' instead of
|
(HasServer a context, HasServer b context) => HasServer (a :<|> b :: Type) context | A server for type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books server :: Server MyApi server = listAllBooks :<|> postBook where listAllBooks = ... postBook book = ... |
Defined in Servant.Server.Internal | |
(HasContextEntry context (NamedContext name subContext), HasServer subApi subContext) => HasServer (WithNamedContext name subContext subApi :: Type) context | |
Defined in Servant.Server.Internal type ServerT (WithNamedContext name subContext subApi) m :: Type # route :: Proxy (WithNamedContext name subContext subApi) -> Context context -> Delayed env (Server (WithNamedContext name subContext subApi)) -> Router env # hoistServerWithContext :: Proxy (WithNamedContext name subContext subApi) -> Proxy context -> (forall x. m x -> n x) -> ServerT (WithNamedContext name subContext subApi) m -> ServerT (WithNamedContext name subContext subApi) n # | |
(TypeError (HasServerArrowKindError arr) :: Constraint) => HasServer (arr :> api :: Type) context | This instance catches mistakes when there are non-saturated
type applications on LHS of
|
Defined in Servant.Server.Internal | |
HasServer api context => HasServer (HttpVersion :> api :: Type) context | |
Defined in Servant.Server.Internal type ServerT (HttpVersion :> api) m :: Type # route :: Proxy (HttpVersion :> api) -> Context context -> Delayed env (Server (HttpVersion :> api)) -> Router env # hoistServerWithContext :: Proxy (HttpVersion :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (HttpVersion :> api) m -> ServerT (HttpVersion :> api) n # | |
(FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk, HasServer api context) => HasServer (StreamBody' mods framing ctype a :> api :: Type) context | |
Defined in Servant.Server.Internal type ServerT (StreamBody' mods framing ctype a :> api) m :: Type # route :: Proxy (StreamBody' mods framing ctype a :> api) -> Context context -> Delayed env (Server (StreamBody' mods framing ctype a :> api)) -> Router env # hoistServerWithContext :: Proxy (StreamBody' mods framing ctype a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (StreamBody' mods framing ctype a :> api) m -> ServerT (StreamBody' mods framing ctype a :> api) n # | |
(AllCTUnrender list a, HasServer api context, SBoolI (FoldLenient mods)) => HasServer (ReqBody' mods list a :> api :: Type) context | If you use All it asks is for a Example: type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book server :: Server MyApi server = postBook where postBook :: Book -> Handler Book postBook book = ...insert into your db... |
Defined in Servant.Server.Internal route :: Proxy (ReqBody' mods list a :> api) -> Context context -> Delayed env (Server (ReqBody' mods list a :> api)) -> Router env # hoistServerWithContext :: Proxy (ReqBody' mods list a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (ReqBody' mods list a :> api) m -> ServerT (ReqBody' mods list a :> api) n # | |
HasServer api context => HasServer (RemoteHost :> api :: Type) context | |
Defined in Servant.Server.Internal type ServerT (RemoteHost :> api) m :: Type # route :: Proxy (RemoteHost :> api) -> Context context -> Delayed env (Server (RemoteHost :> api)) -> Router env # hoistServerWithContext :: Proxy (RemoteHost :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (RemoteHost :> api) m -> ServerT (RemoteHost :> api) n # | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (QueryParam' mods sym a :> api :: Type) context | If you use 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 You can control how it'll be converted from Example: type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book] server :: Server MyApi server = getBooksBy where getBooksBy :: Maybe Text -> Handler [Book] getBooksBy Nothing = ...return all books... getBooksBy (Just author) = ...return books by the given author... |
Defined in Servant.Server.Internal type ServerT (QueryParam' mods sym a :> api) m :: Type # route :: Proxy (QueryParam' mods sym a :> api) -> Context context -> Delayed env (Server (QueryParam' mods sym a :> api)) -> Router env # hoistServerWithContext :: Proxy (QueryParam' mods sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryParam' mods sym a :> api) m -> ServerT (QueryParam' mods sym a :> api) n # | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context) => HasServer (QueryParams sym a :> api :: Type) context | If you use This lets servant worry about looking up 0 or more values in the query string
associated to You can control how the individual values are converted from Example: type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book] server :: Server MyApi server = getBooksBy where getBooksBy :: [Text] -> Handler [Book] getBooksBy authors = ...return all books by these authors... |
Defined in Servant.Server.Internal type ServerT (QueryParams sym a :> api) m :: Type # route :: Proxy (QueryParams sym a :> api) -> Context context -> Delayed env (Server (QueryParams sym a :> api)) -> Router env # hoistServerWithContext :: Proxy (QueryParams sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryParams sym a :> api) m -> ServerT (QueryParams sym a :> api) n # | |
(KnownSymbol sym, HasServer api context) => HasServer (QueryFlag sym :> api :: Type) context | If you use Example: type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book] server :: Server MyApi server = getBooks where getBooks :: Bool -> Handler [Book] getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument... |
Defined in Servant.Server.Internal | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (Header' mods sym a :> api :: Type) context | If you use All it asks is for a Example: newtype Referer = Referer Text deriving (Eq, Show, FromHttpApiData) -- GET /view-my-referer type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer server :: Server MyApi server = viewReferer where viewReferer :: Referer -> Handler referer viewReferer referer = return referer |
Defined in Servant.Server.Internal route :: Proxy (Header' mods sym a :> api) -> Context context -> Delayed env (Server (Header' mods sym a :> api)) -> Router env # hoistServerWithContext :: Proxy (Header' mods sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Header' mods sym a :> api) m -> ServerT (Header' mods sym a :> api) n # | |
HasServer api context => HasServer (IsSecure :> api :: Type) context | |
Defined in Servant.Server.Internal | |
HasServer api ctx => HasServer (Summary desc :> api :: Type) ctx | Ignore |
Defined in Servant.Server.Internal | |
HasServer api ctx => HasServer (Description desc :> api :: Type) ctx | Ignore |
Defined in Servant.Server.Internal type ServerT (Description desc :> api) m :: Type # route :: Proxy (Description desc :> api) -> Context ctx -> Delayed env (Server (Description desc :> api)) -> Router env # hoistServerWithContext :: Proxy (Description desc :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (Description desc :> api) m -> ServerT (Description desc :> api) n # | |
(KnownSymbol capture, FromHttpApiData a, HasServer api context) => HasServer (Capture' mods capture a :> api :: Type) context | If you use You can control how it'll be converted from Example: type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book server :: Server MyApi server = getBook where getBook :: Text -> Handler Book getBook isbn = ... |
Defined in Servant.Server.Internal route :: Proxy (Capture' mods capture a :> api) -> Context context -> Delayed env (Server (Capture' mods capture a :> api)) -> Router env # hoistServerWithContext :: Proxy (Capture' mods capture a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Capture' mods capture a :> api) m -> ServerT (Capture' mods capture a :> api) n # | |
(KnownSymbol capture, FromHttpApiData a, HasServer api context) => HasServer (CaptureAll capture a :> api :: Type) context | If you use You can control how they'll be converted from Example: type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile server :: Server MyApi server = getSourceFile where getSourceFile :: [Text] -> Handler Book getSourceFile pathSegments = ... |
Defined in Servant.Server.Internal type ServerT (CaptureAll capture a :> api) m :: Type # route :: Proxy (CaptureAll capture a :> api) -> Context context -> Delayed env (Server (CaptureAll capture a :> api)) -> Router env # hoistServerWithContext :: Proxy (CaptureAll capture a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (CaptureAll capture a :> api) m -> ServerT (CaptureAll capture a :> api) n # | |
(KnownSymbol realm, HasServer api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer (BasicAuth realm usr :> api :: Type) context | Basic Authentication |
Defined in Servant.Server.Internal route :: Proxy (BasicAuth realm usr :> api) -> Context context -> Delayed env (Server (BasicAuth realm usr :> api)) -> Router env # hoistServerWithContext :: Proxy (BasicAuth realm usr :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (BasicAuth realm usr :> api) m -> ServerT (BasicAuth realm usr :> api) n # | |
HasServer api context => HasServer (Vault :> api :: Type) context | |
Defined in Servant.Server.Internal | |
(KnownSymbol path, HasServer api context) => HasServer (path :> api :: Type) context | Make sure the incoming request starts with |
Defined in Servant.Server.Internal | |
(AllCTRender ctypes a, ReflectMethod method, KnownNat status) => HasServer (Verb method status ctypes a :: Type) context | |
Defined in Servant.Server.Internal route :: Proxy (Verb method status ctypes a) -> Context context -> Delayed env (Server (Verb method status ctypes a)) -> Router env # hoistServerWithContext :: Proxy (Verb method status ctypes a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes a) m -> ServerT (Verb method status ctypes a) n # | |
(AllCTRender ctypes a, ReflectMethod method, KnownNat status, GetHeaders (Headers h a)) => HasServer (Verb method status ctypes (Headers h a) :: Type) context | |
Defined in Servant.Server.Internal route :: Proxy (Verb method status ctypes (Headers h a)) -> Context context -> Delayed env (Server (Verb method status ctypes (Headers h a))) -> Router env # hoistServerWithContext :: Proxy (Verb method status ctypes (Headers h a)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes (Headers h a)) m -> ServerT (Verb method status ctypes (Headers h a)) n # | |
(MimeRender ctype chunk, ReflectMethod method, KnownNat status, FramingRender framing, ToSourceIO chunk a) => HasServer (Stream method status framing ctype a :: Type) context | |
Defined in Servant.Server.Internal route :: Proxy (Stream method status framing ctype a) -> Context context -> Delayed env (Server (Stream method status framing ctype a)) -> Router env # hoistServerWithContext :: Proxy (Stream method status framing ctype a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype a) m -> ServerT (Stream method status framing ctype a) n # | |
(MimeRender ctype chunk, ReflectMethod method, KnownNat status, FramingRender framing, ToSourceIO chunk a, GetHeaders (Headers h a)) => HasServer (Stream method status framing ctype (Headers h a) :: Type) context | |
Defined in Servant.Server.Internal route :: Proxy (Stream method status framing ctype (Headers h a)) -> Context context -> Delayed env (Server (Stream method status framing ctype (Headers h a))) -> Router env # hoistServerWithContext :: Proxy (Stream method status framing ctype (Headers h a)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype (Headers h a)) m -> ServerT (Stream method status framing ctype (Headers h a)) n # |
class HasContextEntry (context :: [Type]) val where #
This class is used to access context entries in Context
s. getContextEntry
returns the first value where the type matches:
>>>
getContextEntry (True :. False :. EmptyContext) :: Bool
True
If the Context
does not contain an entry of the requested type, you'll get
an error:
>>>
getContextEntry (True :. False :. EmptyContext) :: String
... ...No instance for (HasContextEntry '[] [Char]) ...
getContextEntry :: Context context -> val #
Instances
HasContextEntry xs val => HasContextEntry (notIt ': xs) val | |
Defined in Servant.Server.Internal.Context getContextEntry :: Context (notIt ': xs) -> val # | |
HasContextEntry (val ': xs) val | |
Defined in Servant.Server.Internal.Context getContextEntry :: Context (val ': xs) -> val # |
class HasContextEntry context env => SetContextEntry context env where Source #
Class type used to modify context
entries.
setContextEntry :: env -> Context context -> Context context Source #
Instances
SetContextEntry (env ': as) env Source # | |
Defined in Boots.Factory.Web setContextEntry :: env -> Context (env ': as) -> Context (env ': as) Source # | |
SetContextEntry as env => SetContextEntry (a ': as) env Source # | |
Defined in Boots.Factory.Web setContextEntry :: env -> Context (a ': as) -> Context (a ': as) Source # |
data Context (contextTypes :: [Type]) where #
Context
s are used to pass values to combinators. (They are not meant
to be used to pass parameters to your handlers, i.e. they should not replace
any custom ReaderT
-monad-stack that you're using
with hoistServer
.) If you don't use combinators that
require any context entries, you can just use serve
as always.
If you are using combinators that require a non-empty Context
you have to
use serveWithContext
and pass it a Context
that contains all
the values your combinators need. A Context
is essentially a heterogenous
list and accessing the elements is being done by type (see getContextEntry
).
The parameter of the type Context
is a type-level list reflecting the types
of the contained context entries. To create a Context
with entries, use the
operator (
::.
)
>>>
:type True :. () :. EmptyContext
True :. () :. EmptyContext :: Context '[Bool, ()]
EmptyContext :: forall (contextTypes :: [Type]). Context ([] :: [Type]) | |
(:.) :: forall (contextTypes :: [Type]) x (xs :: [Type]). x -> Context xs -> Context (x ': xs) infixr 5 |
Instances
(Eq a, Eq (Context as)) => Eq (Context (a ': as)) | |
Eq (Context ([] :: [Type])) | |
(Show a, Show (Context as)) => Show (Context (a ': as)) | |
Show (Context ([] :: [Type])) | |
HasWeb context env => HasRandom (Context context) Source # | |
HasWeb context env => HasLogger (Context context) Source # | |
HasWeb context env => HasSalak (Context context) Source # | |
HasWeb context env => HasApp (Context context) env Source # | |
logException :: HasLogger env => SomeException -> App env () Source #
Log exception.
whenException :: SomeException -> Response Source #
Convert an exception into Response
.
Convert a type into
.Schema
An example type and instance:
{-# LANGUAGE OverloadedStrings #-} -- allows to writeText
literals {-# LANGUAGE OverloadedLists #-} -- allows to writeMap
andHashMap
as lists import Control.Lens import Data.Proxy import Data.Swagger data Coord = Coord { x :: Double, y :: Double } instance ToSchema Coord where declareNamedSchema _ = do doubleSchema <- declareSchemaRef (Proxy :: Proxy Double) return $ NamedSchema (Just "Coord") $ mempty & type_ ?~ SwaggerObject & properties .~ [ ("x", doubleSchema) , ("y", doubleSchema) ] & required .~ [ "x", "y" ]
Instead of manually writing your
instance you can
use a default generic implementation of ToSchema
.declareNamedSchema
To do that, simply add deriving
clause to your datatype
and declare a Generic
instance for your datatype without
giving definition for ToSchema
.declareNamedSchema
For instance, the previous example can be simplified into this:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic) data Coord = Coord { x :: Double, y :: Double } deriving Generic instance ToSchema Coord
Instances
type Vault = Vault RealWorld #
A persistent store for values of arbitrary types.
This variant is the simplest and creates keys in the IO
monad.
See the module Data.Vault.ST if you want to use it with the ST
monad instead.
Metrics
class HasMetrics env where Source #
Environment values with Store
.
askMetrics :: Lens' env Store Source #
Instances
HasMetrics (WebEnv env context) Source # | |
Defined in Boots.Factory.Web |
Middleware
Endpoint
module Boots.Factory.Endpoint
Tracing
module Boots.Factory.Trace
Other
module Boots.Factory.Error
module Boots.Factory.Random