boots-web-0.2: Factory for quickly building a web application

Copyright2019 Daniel YU
LicenseMIT
Maintainerleptonyu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Boots.Web

Contents

Description

A quick out-of-box factory using to build web application with many useful builtin web components, based on boots-app and servant.

  1. Builtin metrics, use ekg-core as backend.
  2. Builtin tracing log, support B3-Tags.
  3. Builtin endpoints, info, healthcheck, logger, metrics, refresh configuration, swagger api.
  4. Builtin error management.

Hackage boots-consul provides consul support for building microservices.

Synopsis

Boot web

bootWeb Source #

Arguments

:: (HasServer api context, HasSwagger api, HasWeb context env) 
=> String

Application name.

-> Version

Application version.

-> (AppEnv -> env)

Function which generates env using AppEnv.

-> (env -> Context context)

Function which generates context using env.

-> (Proxy context -> Proxy env -> Factory IO (WebEnv env context) ())

Customized Factory.

-> Proxy api

Api proxy.

-> ServerT api (App env)

Servant api server.

-> IO () 

A out-of-box web application booter with many predefined components.

buildWeb Source #

Arguments

:: (MonadIO n, MonadMask n, HasWeb context env) 
=> Proxy context

context proxy.

-> Proxy env

env proxy.

-> Factory n (WebEnv env context) (IO ())

Factory which create an application from WebEnv.

Build a web application from WebEnv.

type HasWeb context env = (HasApp env, HasLogger env, HasHealth env, HasRandom env, HasSalak env, HasContextEntry context env) Source #

Unified constraints for web environment.

Configuration

class HasWebConfig env where Source #

Environment values with WebConfig.

Instances
HasWebConfig WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

HasWebConfig (WebEnv env context) Source #

Environment values with WebEnv.

Instance details

Defined in Boots.Factory.Web

Methods

askWebConfig :: Lens' (WebEnv env context) WebConfig Source #

data WebConfig Source #

Application Configuration.

Constructors

WebConfig 

Fields

Instances
Eq WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

Show WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

Default WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

Methods

def :: WebConfig #

HasWebConfig WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

FromProp m WebConfig Source # 
Instance details

Defined in Boots.Factory.Web

Methods

fromProp :: Prop m WebConfig #

data EndpointConfig Source #

Endpoint configuration.

Constructors

EndpointConfig 
Instances
FromProp m EndpointConfig Source # 
Instance details

Defined in Boots.Factory.Web

Environment

data WebEnv env context Source #

Web environment, which defined all components to build a web application.

Constructors

WebEnv 

Fields

Instances
HasApp env => HasApp (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askApp :: Lens' (WebEnv env context) AppEnv #

HasRandom env => HasRandom (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askRandom :: Lens' (WebEnv env context) RD #

HasLogger env => HasLogger (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askLogger :: Lens' (WebEnv env context) LogFunc #

HasSalak env => HasSalak (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askSalak :: Lens' (WebEnv env context) Salak #

HasHealth env => HasHealth (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askHealth :: Lens' (WebEnv env context) (IO Health) #

HasMetrics (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askMetrics :: Lens' (WebEnv env context) Store Source #

HasWebConfig (WebEnv env context) Source #

Environment values with WebEnv.

Instance details

Defined in Boots.Factory.Web

Methods

askWebConfig :: Lens' (WebEnv env context) WebConfig Source #

newWebEnv Source #

Arguments

:: (HasContextEntry context env, HasLogger env) 
=> env

Application environment.

-> (env -> Context context)

Function used to generate context from env.

-> WebConfig

Web configuration.

-> EndpointConfig

Endpoint configuration.

-> Store

Metrics store.

-> WebEnv env context 

Create a web environment.

askEnv :: MonadMask n => Factory n (WebEnv env context) env Source #

Get application environment env.

Modified Middleware

type EnvMiddleware env = (env -> Application) -> 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

tryServe Source #

Arguments

:: (HasContextEntry context env, HasServer api context, MonadMask n) 
=> Bool

If do this action.

-> Proxy context

Context proxy.

-> Proxy api

Api proxy.

-> ServerT api (App env)

Api server.

-> Factory n (WebEnv env context) () 

Try serve a web server.

trySwagger Source #

Arguments

:: (MonadMask n, HasSwagger api) 
=> Bool

If do this action.

-> Proxy api

Api proxy.

-> Factory n (WebEnv env context) () 

Try serve a swagger definition.

tryServeWithSwagger Source #

Arguments

:: (HasContextEntry context env, HasServer api context, HasSwagger api, MonadMask n) 
=> Bool

If do this action.

-> Proxy context

Context proxy.

-> Proxy api

Api proxy.

-> ServerT api (App 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 ToParamSchema and/or ToSchema instances.

ToParamSchema is used for Capture, QueryParam and Header. ToSchema is used for ReqBody and response data types.

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)

Methods

toSwagger :: Proxy api -> Swagger #

Generate a Swagger specification for a servant API.

Instances
HasSwagger Raw 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy Raw -> Swagger #

HasSwagger EmptyAPI 
Instance details

Defined in Servant.Swagger.Internal

(HasSwagger a, HasSwagger b) => HasSwagger (a :<|> b :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (a :<|> b) -> Swagger #

HasSwagger sub => HasSwagger (WithNamedContext x c sub :: Type)

WithNamedContext combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (WithNamedContext x c sub) -> Swagger #

HasSwagger sub => HasSwagger (HttpVersion :> sub :: Type)

HttpVersion combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (HttpVersion :> sub) -> Swagger #

(ToSchema a, Accept ct, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (StreamBody' mods fr ct a :> sub :: Type)

This instance is an approximation.

Since: servant-swagger-1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (StreamBody' mods fr ct a :> sub) -> Swagger #

(ToSchema a, AllAccept cs, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (ReqBody' mods cs a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (ReqBody' mods cs a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (RemoteHost :> sub :: Type)

RemoteHost combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (RemoteHost :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasSwagger (QueryParam' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParam' mods sym a :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub) => HasSwagger (QueryParams sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParams sym a :> sub) -> Swagger #

(KnownSymbol sym, HasSwagger sub) => HasSwagger (QueryFlag sym :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryFlag sym :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasSwagger (Header' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Header' mods sym a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (IsSecure :> sub :: Type)

IsSecure combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (IsSecure :> sub) -> Swagger #

(KnownSymbol desc, HasSwagger api) => HasSwagger (Summary desc :> api :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Summary desc :> api) -> Swagger #

(KnownSymbol desc, HasSwagger api) => HasSwagger (Description desc :> api :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Description desc :> api) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (Capture' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Capture' mods sym a :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub) => HasSwagger (CaptureAll sym a :> sub :: Type)

Swagger Spec doesn't have a notion of CaptureAll, this instance is the best effort.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (CaptureAll sym a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (Vault :> sub :: Type)

Vault combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Vault :> sub) -> Swagger #

(KnownSymbol sym, HasSwagger sub) => HasSwagger (sym :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (sym :> sub) -> Swagger #

(ToSchema a, AllAccept cs, AllToResponseHeader hs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs (Headers hs a) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs a)) -> Swagger #

(AllAccept cs, AllToResponseHeader hs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs (Headers hs NoContent) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs NoContent)) -> Swagger #

(ToSchema a, AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs a :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs a) -> Swagger #

(AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs NoContent :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs NoContent) -> Swagger #

(ToSchema a, Accept ct, KnownNat status, SwaggerMethod method) => HasSwagger (Stream method status fr ct a :: Type)

Since: servant-swagger-1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Stream method status fr ct a) -> Swagger #

class HasServer (api :: k) (context :: [Type]) where #

Associated Types

type ServerT (api :: k) (m :: Type -> Type) :: Type #

Methods

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"
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT Raw m :: Type #

Methods

route :: Proxy Raw -> Context context -> Delayed env (Server Raw) -> Router env #

hoistServerWithContext :: Proxy Raw -> Proxy context -> (forall x. m x -> n x) -> ServerT Raw m -> ServerT Raw n #

HasServer EmptyAPI context

The server for an EmptyAPI is emptyAPIServer.

type MyApi = "nothing" :> EmptyApi

server :: Server MyApi
server = emptyAPIServer
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT EmptyAPI m :: Type #

Methods

route :: Proxy EmptyAPI -> Context context -> Delayed env (Server EmptyAPI) -> Router env #

hoistServerWithContext :: Proxy EmptyAPI -> Proxy context -> (forall x. m x -> n x) -> ServerT EmptyAPI m -> ServerT EmptyAPI n #

(TypeError (HasServerArrowTypeError a b) :: Constraint) => HasServer (a -> b :: Type) context

This instance prevents from accidentally using '->' instead of :>

>>> serve (Proxy :: Proxy (Capture "foo" Int -> Get '[JSON] Int)) (error "...")
...
...No instance HasServer (a -> b).
...Maybe you have used '->' instead of ':>' between
...Capture' '[] "foo" Int
...and
...Verb 'GET 200 '[JSON] Int
...
>>> undefined :: Server (Capture "foo" Int -> Get '[JSON] Int)
...
...No instance HasServer (a -> b).
...Maybe you have used '->' instead of ':>' between
...Capture' '[] "foo" Int
...and
...Verb 'GET 200 '[JSON] Int
...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (a -> b) m :: Type #

Methods

route :: Proxy (a -> b) -> Context context -> Delayed env (Server (a -> b)) -> Router env #

hoistServerWithContext :: Proxy (a -> b) -> Proxy context -> (forall x. m x -> n x) -> ServerT (a -> b) m -> ServerT (a -> b) n #

(HasServer a context, HasServer b context) => HasServer (a :<|> b :: Type) context

A server for a :<|> b first tries to match the request against the route represented by a and if it fails tries b. You must provide a request handler for each route.

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 = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (a :<|> b) m :: Type #

Methods

route :: Proxy (a :<|> b) -> Context context -> Delayed env (Server (a :<|> b)) -> Router env #

hoistServerWithContext :: Proxy (a :<|> b) -> Proxy context -> (forall x. m x -> n x) -> ServerT (a :<|> b) m -> ServerT (a :<|> b) n #

(HasContextEntry context (NamedContext name subContext), HasServer subApi subContext) => HasServer (WithNamedContext name subContext subApi :: Type) context 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (WithNamedContext name subContext subApi) m :: Type #

Methods

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 :>.

>>> serve (Proxy :: Proxy (Capture "foo" :> Get '[JSON] Int)) (error "...")
...
...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'.
...Maybe you haven't applied enough arguments to
...Capture' '[] "foo"
...
>>> undefined :: Server (Capture "foo" :> Get '[JSON] Int)
...
...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'.
...Maybe you haven't applied enough arguments to
...Capture' '[] "foo"
...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (arr :> api) m :: Type #

Methods

route :: Proxy (arr :> api) -> Context context -> Delayed env (Server (arr :> api)) -> Router env #

hoistServerWithContext :: Proxy (arr :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (arr :> api) m -> ServerT (arr :> api) n #

HasServer api context => HasServer (HttpVersion :> api :: Type) context 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (HttpVersion :> api) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (StreamBody' mods framing ctype a :> api) m :: Type #

Methods

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 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. The Content-Type header is inspected, and the list provided is used to attempt deserialization. If the request does not have a Content-Type header, it is treated as application/octet-stream (as specified in RFC7231. 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 FromJSON instance.

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...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (ReqBody' mods list a :> api) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (RemoteHost :> api) m :: Type #

Methods

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 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.

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...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParam' mods sym a :> api) m :: Type #

Methods

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 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.

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...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParams sym a :> api) m :: Type #

Methods

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 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:

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...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryFlag sym :> api) m :: Type #

Methods

route :: Proxy (QueryFlag sym :> api) -> Context context -> Delayed env (Server (QueryFlag sym :> api)) -> Router env #

hoistServerWithContext :: Proxy (QueryFlag sym :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryFlag sym :> api) m -> ServerT (QueryFlag sym :> api) n #

(KnownSymbol sym, FromHttpApiData a, HasServer api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (Header' mods sym a :> api :: Type) context

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.

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
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Header' mods sym a :> api) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (IsSecure :> api) m :: Type #

Methods

route :: Proxy (IsSecure :> api) -> Context context -> Delayed env (Server (IsSecure :> api)) -> Router env #

hoistServerWithContext :: Proxy (IsSecure :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (IsSecure :> api) m -> ServerT (IsSecure :> api) n #

HasServer api ctx => HasServer (Summary desc :> api :: Type) ctx

Ignore Summary in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Summary desc :> api) m :: Type #

Methods

route :: Proxy (Summary desc :> api) -> Context ctx -> Delayed env (Server (Summary desc :> api)) -> Router env #

hoistServerWithContext :: Proxy (Summary desc :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (Summary desc :> api) m -> ServerT (Summary desc :> api) n #

HasServer api ctx => HasServer (Description desc :> api :: Type) ctx

Ignore Description in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Description desc :> api) m :: Type #

Methods

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 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.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book

server :: Server MyApi
server = getBook
  where getBook :: Text -> Handler Book
        getBook isbn = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Capture' mods capture a :> api) m :: Type #

Methods

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 CaptureAll in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of a list of the type specified by the CaptureAll. This lets servant worry about getting values from the URL and turning them into values of the type you specify.

You can control how they'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile

server :: Server MyApi
server = getSourceFile
  where getSourceFile :: [Text] -> Handler Book
        getSourceFile pathSegments = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (CaptureAll capture a :> api) m :: Type #

Methods

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

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (BasicAuth realm usr :> api) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Vault :> api) m :: Type #

Methods

route :: Proxy (Vault :> api) -> Context context -> Delayed env (Server (Vault :> api)) -> Router env #

hoistServerWithContext :: Proxy (Vault :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Vault :> api) m -> ServerT (Vault :> api) n #

(KnownSymbol path, HasServer api context) => HasServer (path :> api :: Type) context

Make sure the incoming request starts with "/path", strip it and pass the rest of the request path to api.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (path :> api) m :: Type #

Methods

route :: Proxy (path :> api) -> Context context -> Delayed env (Server (path :> api)) -> Router env #

hoistServerWithContext :: Proxy (path :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (path :> api) m -> ServerT (path :> api) n #

(AllCTRender ctypes a, ReflectMethod method, KnownNat status) => HasServer (Verb method status ctypes a :: Type) context 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes a) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes (Headers h a)) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype a) m :: Type #

Methods

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 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype (Headers h a)) m :: Type #

Methods

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 Contexts. 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])
...

Methods

getContextEntry :: Context context -> val #

Instances
HasContextEntry xs val => HasContextEntry (notIt ': xs) val 
Instance details

Defined in Servant.Server.Internal.Context

Methods

getContextEntry :: Context (notIt ': xs) -> val #

HasContextEntry (val ': xs) val 
Instance details

Defined in Servant.Server.Internal.Context

Methods

getContextEntry :: Context (val ': xs) -> val #

class HasContextEntry context env => SetContextEntry context env where Source #

Class type used to modify context entries.

Methods

setContextEntry :: env -> Context context -> Context context Source #

Instances
SetContextEntry (env ': as) env Source # 
Instance details

Defined in Boots.Factory.Web

Methods

setContextEntry :: env -> Context (env ': as) -> Context (env ': as) Source #

SetContextEntry as env => SetContextEntry (a ': as) env Source # 
Instance details

Defined in Boots.Factory.Web

Methods

setContextEntry :: env -> Context (a ': as) -> Context (a ': as) Source #

data Context (contextTypes :: [Type]) where #

Contexts 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, ()]

Constructors

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)) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

(==) :: Context (a ': as) -> Context (a ': as) -> Bool #

(/=) :: Context (a ': as) -> Context (a ': as) -> Bool #

Eq (Context ([] :: [Type])) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

(==) :: Context [] -> Context [] -> Bool #

(/=) :: Context [] -> Context [] -> Bool #

(Show a, Show (Context as)) => Show (Context (a ': as)) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

showsPrec :: Int -> Context (a ': as) -> ShowS #

show :: Context (a ': as) -> String #

showList :: [Context (a ': as)] -> ShowS #

Show (Context ([] :: [Type])) 
Instance details

Defined in Servant.Server.Internal.Context

Methods

showsPrec :: Int -> Context [] -> ShowS #

show :: Context [] -> String #

showList :: [Context []] -> ShowS #

(SetContextEntry context env, HasRandom env) => HasRandom (Context context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askRandom :: Lens' (Context context) RD #

(SetContextEntry context env, HasLogger env) => HasLogger (Context context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askLogger :: Lens' (Context context) LogFunc #

(SetContextEntry context env, HasSalak env) => HasSalak (Context context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askSalak :: Lens' (Context context) Salak #

askContext :: SetContextEntry context env => Lens' (Context context) env Source #

Lens for modify env in context.

logException :: HasLogger env => SomeException -> App env () Source #

Log exception.

whenException :: SomeException -> Response Source #

Convert an exception into Response.

class ToSchema a #

Convert a type into Schema.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}   -- allows to write Text literals
{-# LANGUAGE OverloadedLists #-}     -- allows to write Map and HashMap 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 ToSchema instance you can use a default generic implementation of declareNamedSchema.

To do that, simply add deriving Generic clause to your datatype and declare a ToSchema instance for your datatype without giving definition for 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
ToSchema Bool 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Char 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Double 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Float 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int8 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int16 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int32 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int64 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Integer 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Natural 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word8 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word16 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word32 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word64 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema () 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema String 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Version 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchemaByteStringError ByteString :: Constraint) => ToSchema ByteString 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchemaByteStringError ByteString :: Constraint) => ToSchema ByteString 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Scientific 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Text 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema UTCTime
>>> toSchema (Proxy :: Proxy UTCTime) ^. format
Just "yyyy-mm-ddThh:MM:ssZ"
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Object 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Text 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema All 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Any 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema HealthStatus Source # 
Instance details

Defined in Boots.Endpoint.Health

ToSchema Health Source # 
Instance details

Defined in Boots.Endpoint.Health

ToSchema IntSet 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema ZonedTime

Format "date" corresponds to yyyy-mm-ddThh:MM:ss(Z|+hh:MM) format.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema LocalTime
>>> toSchema (Proxy :: Proxy LocalTime) ^. format
Just "yyyy-mm-ddThh:MM:ss"
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema NominalDiffTime 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Day

Format "date" corresponds to yyyy-mm-dd format.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema UUID

For ToJSON instance, see uuid-aeson package.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema [a] 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Maybe a) 
Instance details

Defined in Data.Swagger.Internal.Schema

HasResolution a => ToSchema (Fixed a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Identity a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (First a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Last a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Dual a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Sum a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Product a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (NonEmpty a)

Since: swagger2-2.2.1

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (IntMap a)

NOTE: This schema does not account for the uniqueness of keys.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Set a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (HashSet a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b) => ToSchema (Either a b) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b) => ToSchema (a, b) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (HashMap k v) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (Map k v) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c) => ToSchema (a, b, c) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c, ToSchema d) => ToSchema (a, b, c, d) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e) => ToSchema (a, b, c, d, e) 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f) => ToSchema (a, b, c, d, e, f) 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: Proxy (a, b, c, d, e, f) -> Declare (Definitions Schema) NamedSchema #

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f, ToSchema g) => ToSchema (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: Proxy (a, b, c, d, e, f, g) -> Declare (Definitions Schema) NamedSchema #

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.

Methods

askMetrics :: Lens' env Store Source #

Instances
HasMetrics (WebEnv env context) Source # 
Instance details

Defined in Boots.Factory.Web

Methods

askMetrics :: Lens' (WebEnv env context) Store Source #

data Store #

A mutable metric store.

newStore :: IO Store #

Create a new, empty metric store.

Middleware

Endpoint

Tracing

Other