Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Util.Combinators.Logging
Contents
Description
Allows to enable logging of requests and responses.
Synopsis
- data LoggingApi config api
- data LoggingApiRec config (lcontext :: LoggingContext) api
- data LoggingMod (mod :: LoggingModKind)
- type LoggingLevel lvl = LoggingMod ('LMLoggingLevel lvl)
- type LoggingRequestsEnabled = LoggingMod ('LMRequestsLogged 'True)
- type LoggingRequestsDisabled = LoggingMod ('LMRequestsLogged 'False)
- type LoggingResponsesEnabled = LoggingMod ('LMResponsesLogged 'True)
- type LoggingResponsesDisabled = LoggingMod ('LMResponsesLogged 'False)
- type LoggingDisabled = LoggingMod 'LMLoggingDisabled
- newtype LogContext = LogContext {}
- class HasServer api ctx => HasLoggingServer config (lcontext :: LoggingContext) api ctx where
- routeWithLog :: Proxy (LoggingApiRec config lcontext api) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext api)) -> Router env
- newtype ServantLogConfig = ServantLogConfig {
- clcLog :: LogContext -> Text -> IO ()
- newtype ForResponseLog a = ForResponseLog {
- unForResponseLog :: a
- type BuildableForResponseIfNecessary lcontext resp = (If (LcResponsesEnabled lcontext) (Buildable (ForResponseLog resp)) (() :: Constraint), Demote (LcResponsesEnabled lcontext))
- buildListForResponse :: Buildable (ForResponseLog x) => (forall a. [a] -> [a]) -> ForResponseLog [x] -> Builder
- buildForResponse :: Buildable a => ForResponseLog a -> Builder
- class ApiHasArgClass api where
- type ApiArg api :: Type
- apiArgName :: Proxy api -> String
- class ApiHasArgClass subApi => ApiCanLogArg subApi where
- type ApiArgToLog subApi :: Type
- toLogParamInfo :: Buildable (ApiArgToLog subApi) => Proxy subApi -> ApiArg subApi -> Text
- addParamLogInfo :: Text -> ApiParamsLogInfo -> ApiParamsLogInfo
- setInPrefix :: ApiParamsLogInfo -> ApiParamsLogInfo
- serverWithLogging :: forall api a. ServantLogConfig -> Proxy api -> (forall (config :: Type). Reifies config ServantLogConfig => Proxy (LoggingApi config api) -> a) -> a
Automatic requests logging
data LoggingApi config api Source #
Enables logging for server which serves given api.
config
is a type at which you have to specify ServantLogConfig
via
reflection. This way was chosen because the least thing we need in
config is LoggerName
, and we want to have <>
on LoggerName
s thus
KnownSymbol
is not enough.
This logging will report
- Request parameters, including request bodies
- If execution failed with error, it will be displayed
- Details like request method and endpoint execution time
If user makes request which is not defined it won't be logged. However, I don't find it a great problem, it may impede only in development or on getting acknowledged with api.
Instances
(HasServer (LoggingApiRec config EmptyLoggingContext api) ctx, HasServer api ctx) => HasServer (LoggingApi config api :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ServerT (LoggingApi config api) m # Methods route :: Proxy (LoggingApi config api) -> Context ctx -> Delayed env (Server (LoggingApi config api)) -> Router env # hoistServerWithContext :: Proxy (LoggingApi config api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (LoggingApi config api) m -> ServerT (LoggingApi config api) n # | |
type ServerT (LoggingApi config api :: Type) m Source # | |
Defined in Servant.Util.Combinators.Logging |
data LoggingApiRec config (lcontext :: LoggingContext) api Source #
Helper to traverse servant api and apply logging.
Instances
HasLoggingServer config lcontext api ctx => HasServer (LoggingApiRec config lcontext api :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ServerT (LoggingApiRec config lcontext api) m # Methods route :: Proxy (LoggingApiRec config lcontext api) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext api)) -> Router env # hoistServerWithContext :: Proxy (LoggingApiRec config lcontext api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (LoggingApiRec config lcontext api) m -> ServerT (LoggingApiRec config lcontext api) n # | |
type ServerT (LoggingApiRec config lcontext api :: Type) m Source # | |
Defined in Servant.Util.Combinators.Logging |
data LoggingMod (mod :: LoggingModKind) Source #
Servant combinator that changes how the logs will be printed for the affected endpoints.
This is an internal thing, we export aliases.
Instances
type LoggingLevel lvl = LoggingMod ('LMLoggingLevel lvl) Source #
Combinator to set the logging level within the endpoints.
type LoggingRequestsEnabled = LoggingMod ('LMRequestsLogged 'True) Source #
Combinator to enable logging of requests back for a narrower set of entrypoints.
type LoggingRequestsDisabled = LoggingMod ('LMRequestsLogged 'False) Source #
Combinator to disable logging of requests.
type LoggingResponsesEnabled = LoggingMod ('LMResponsesLogged 'True) Source #
Combinator to enable logging of responses.
type LoggingResponsesDisabled = LoggingMod ('LMResponsesLogged 'False) Source #
Combinator to disable logging of responses.
type LoggingDisabled = LoggingMod 'LMLoggingDisabled Source #
Combinator to disable all the logging.
This works similarly to other similar combinators and can be partially
or fully reverted with LoggingRequestsDisabled
or LoggingResponsesDisabled
.
newtype LogContext Source #
Logging context that will be supplied to the user.
Constructors
LogContext | |
Fields
|
Instances
Eq LogContext Source # | |
Defined in Servant.Util.Combinators.Logging | |
Show LogContext Source # | |
Defined in Servant.Util.Combinators.Logging Methods showsPrec :: Int -> LogContext -> ShowS # show :: LogContext -> String # showList :: [LogContext] -> ShowS # |
class HasServer api ctx => HasLoggingServer config (lcontext :: LoggingContext) api ctx where Source #
Version of HasServer
which is assumed to perform logging.
It's helpful because 'ServerT (LoggingApi ...)' is already defined for us
in actual HasServer
instance once and forever.
Methods
routeWithLog :: Proxy (LoggingApiRec config lcontext api) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext api)) -> Router env Source #
Instances
HasLoggingServer (config :: k) lcontext Raw ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext Raw) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext Raw)) -> Router env Source # | |
(HasServer (NoContentVerb mt) ctx, Reifies config ServantLogConfig, Demote lcontext, ReflectMethod mt, BuildableForResponseIfNecessary lcontext NoContent) => HasLoggingServer (config :: k1) lcontext (NoContentVerb mt :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (NoContentVerb mt)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (NoContentVerb mt))) -> Router env Source # | |
(HasLoggingServer config lcontext api1 ctx, HasLoggingServer config lcontext api2 ctx) => HasLoggingServer (config :: k) lcontext (api1 :<|> api2 :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (api1 :<|> api2)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (api1 :<|> api2))) -> Router env Source # | |
(HasLoggingServer config (ApplyLoggingMod lcontext mod) res ctx, HasServer res ctx) => HasLoggingServer (config :: k) lcontext (LoggingMod mod :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (LoggingMod mod :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (LoggingMod mod :> res))) -> Router env Source # | |
HasLoggingServer config lcontext res ctx => HasLoggingServer (config :: k) lcontext (Description d :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (Description d :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (Description d :> res))) -> Router env Source # | |
HasLoggingServer config lcontext res ctx => HasLoggingServer (config :: k) lcontext (Summary s :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (Summary s :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (Summary s :> res))) -> Router env Source # | |
(HasLoggingServer config lcontext res ctx, KnownSymbol s) => HasLoggingServer (config :: k) lcontext (QueryFlag s :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (QueryFlag s :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (QueryFlag s :> res))) -> Router env Source # | |
(KnownSymbol path, HasLoggingServer config lcontext res ctx) => HasLoggingServer (config :: k) lcontext (path :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (path :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (path :> res))) -> Router env Source # | |
(HasServer (subApi :> res) ctx, HasServer (subApi :> LoggingApiRec config lcontext res) ctx, ApiHasArg subApi res, ApiHasArg subApi (LoggingApiRec config lcontext res), ApiCanLogArg subApi, Buildable (ApiArgToLog subApi), subApi ~ apiType a) => HasLoggingServer (config :: k) lcontext (apiType a :> res :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (apiType a :> res)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (apiType a :> res))) -> Router env Source # | |
(HasServer (Verb mt st ct a) ctx, Reifies config ServantLogConfig, Demote lcontext, ReflectMethod mt, BuildableForResponseIfNecessary lcontext a) => HasLoggingServer (config :: k1) lcontext (Verb mt st ct a :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (Verb mt st ct a)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (Verb mt st ct a))) -> Router env Source # | |
HasLoggingServer config context subApi ctx => HasLoggingServer (config :: Type) context (TagDescriptions ver mapping :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Tag Methods routeWithLog :: Proxy (LoggingApiRec config context (TagDescriptions ver mapping :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config context (TagDescriptions ver mapping :> subApi))) -> Router env Source # | |
HasLoggingServer config lcontext subApi ctx => HasLoggingServer (config :: Type) lcontext (Tag name :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Tag Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (Tag name :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (Tag name :> subApi))) -> Router env Source # | |
(HasLoggingServer config lcontext subApi ctx, HasContextEntry (ctx .++ DefaultErrorFormatters) ErrorFormatters, ReifySortingItems base, ReifyParamsNames provided) => HasLoggingServer (config :: Type) lcontext (SortingParams provided base :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Sorting.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (SortingParams provided base :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (SortingParams provided base :> subApi))) -> Router env Source # | |
(HasLoggingServer config lcontext subApi ctx, AreFilteringParams params, ReifyParamsNames params, BuildSomeFilter params) => HasLoggingServer (config :: Type) lcontext (FilteringParams params :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Filtering.Logging Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (FilteringParams params :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (FilteringParams params :> subApi))) -> Router env Source # | |
HasLoggingServer config lcontext subApi ctx => HasLoggingServer (config :: Type) lcontext (ErrorResponses errors :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.ErrorResponses Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (ErrorResponses errors :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (ErrorResponses errors :> subApi))) -> Router env Source # | |
(HasLoggingServer config lcontext subApi ctx, KnownPaginationPageSize settings, HasContextEntry (ctx .++ DefaultErrorFormatters) ErrorFormatters) => HasLoggingServer (config :: Type) lcontext (PaginationParams settings :> subApi :: Type) ctx Source # | |
Defined in Servant.Util.Combinators.Pagination Methods routeWithLog :: Proxy (LoggingApiRec config lcontext (PaginationParams settings :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (PaginationParams settings :> subApi))) -> Router env Source # |
newtype ServantLogConfig Source #
Logging configuration specified at server start.
Constructors
ServantLogConfig | |
Fields
|
newtype ForResponseLog a Source #
When it comes to logging responses, returned data may be very large. Log space is valuable (already in testnet we got truncated logs), so we have to care about printing only whose data which may be useful.
Constructors
ForResponseLog | |
Fields
|
Instances
Buildable (ForResponseLog Integer) Source # | |
Defined in Servant.Util.Combinators.Logging Methods build :: ForResponseLog Integer -> Builder # | |
Buildable (ForResponseLog ()) Source # | |
Defined in Servant.Util.Combinators.Logging Methods build :: ForResponseLog () -> Builder # | |
Buildable (ForResponseLog NoContent) Source # | |
Defined in Servant.Util.Combinators.Logging Methods build :: ForResponseLog NoContent -> Builder # | |
Buildable (ForResponseLog Swagger) Source # | |
Defined in Servant.Util.Combinators.Logging Methods build :: ForResponseLog Swagger -> Builder # | |
Buildable (ForResponseLog (SwaggerUiHtml dir api)) Source # | |
Defined in Servant.Util.Combinators.Logging Methods build :: ForResponseLog (SwaggerUiHtml dir api) -> Builder # |
type BuildableForResponseIfNecessary lcontext resp = (If (LcResponsesEnabled lcontext) (Buildable (ForResponseLog resp)) (() :: Constraint), Demote (LcResponsesEnabled lcontext)) Source #
Require Buildable
for the response type, but only if logging context
assumes that the response will indeed be built.
buildListForResponse :: Buildable (ForResponseLog x) => (forall a. [a] -> [a]) -> ForResponseLog [x] -> Builder Source #
buildForResponse :: Buildable a => ForResponseLog a -> Builder Source #
class ApiHasArgClass api where Source #
Proves info about argument specifier of servant API.
Minimal complete definition
Nothing
Associated Types
type ApiArg api :: Type Source #
For arguments-specifiers of API, get argument type.
E.g. Capture "cap" Int
-> Int
.
type ApiArg api = ApplicationRS api
Methods
apiArgName :: Proxy api -> String Source #
Name of argument.
E.g. name of argument specified by Capture "nyan"
is nyan.
default apiArgName :: forall n someApiType a. (KnownSymbol n, api ~ someApiType n a) => Proxy api -> String Source #
Instances
KnownSymbol s => ApiHasArgClass (QueryFlag s) Source # | |
ApiHasArgClass (ReqBody ct a) Source # | |
KnownSymbol s => ApiHasArgClass (Capture s a) Source # | |
KnownSymbol s => ApiHasArgClass (QueryParam' mods s a) Source # | |
Defined in Servant.Util.Common.Common Associated Types type ApiArg (QueryParam' mods s a) Source # Methods apiArgName :: Proxy (QueryParam' mods s a) -> String Source # |
class ApiHasArgClass subApi => ApiCanLogArg subApi where Source #
Describes a way to log a single parameter.
Minimal complete definition
Nothing
Methods
toLogParamInfo :: Buildable (ApiArgToLog subApi) => Proxy subApi -> ApiArg subApi -> Text Source #
Instances
KnownSymbol cs => ApiCanLogArg (QueryFlag cs) Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ApiArgToLog (QueryFlag cs) Source # | |
ApiCanLogArg (ReqBody ct a) Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ApiArgToLog (ReqBody ct a) Source # | |
KnownSymbol s => ApiCanLogArg (Capture s a) Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ApiArgToLog (Capture s a) Source # | |
(Buildable a, KnownSymbol cs, SBoolI (FoldRequired mods)) => ApiCanLogArg (QueryParam' mods cs a) Source # | |
Defined in Servant.Util.Combinators.Logging Associated Types type ApiArgToLog (QueryParam' mods cs a) Source # Methods toLogParamInfo :: Proxy (QueryParam' mods cs a) -> ApiArg (QueryParam' mods cs a) -> Text Source # |
addParamLogInfo :: Text -> ApiParamsLogInfo -> ApiParamsLogInfo Source #
setInPrefix :: ApiParamsLogInfo -> ApiParamsLogInfo Source #
serverWithLogging :: forall api a. ServantLogConfig -> Proxy api -> (forall (config :: Type). Reifies config ServantLogConfig => Proxy (LoggingApi config api) -> a) -> a Source #
Apply logging to the given server.