servant-ekg-0.2.0.0: Helpers for using ekg with servant

Safe HaskellNone
LanguageHaskell2010

Servant.Ekg

Synopsis

Documentation

countResponseCodes :: (Counter, Counter, Counter, Counter) -> Middleware Source #

Count responses with 2XX, 4XX, 5XX, and XXX response codes.

class HasEndpoint a where Source #

Minimal complete definition

getEndpoint

Methods

getEndpoint :: Proxy a -> Request -> Maybe ([Text], Method) Source #

Instances

HasEndpoint * Raw Source # 
(HasEndpoint * a, HasEndpoint * b) => HasEndpoint * ((:<|>) a b) Source # 

Methods

getEndpoint :: Proxy (a :<|> b) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * (WithNamedContext x y sub) Source # 

Methods

getEndpoint :: Proxy (WithNamedContext x y sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * HttpVersion sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) HttpVersion sub) a -> Request -> Maybe ([Text], Method) Source #

(KnownSymbol capture, HasEndpoint * sub) => HasEndpoint * ((:>) * * (Capture k capture a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (Capture k capture a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (CaptureAll k h a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (CaptureAll k h a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (Header h a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (Header h a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * IsSecure sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) IsSecure sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (QueryParam k h a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (QueryParam k h a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (QueryParams k h a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (QueryParams k h a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (QueryFlag h) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (QueryFlag h) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * RemoteHost sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) RemoteHost sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * (ReqBody k cts a) sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) (ReqBody k cts a) sub) a -> Request -> Maybe ([Text], Method) Source #

HasEndpoint * sub => HasEndpoint * ((:>) * * Vault sub) Source # 

Methods

getEndpoint :: Proxy ((* :> *) Vault sub) a -> Request -> Maybe ([Text], Method) Source #

(KnownSymbol path, HasEndpoint * sub) => HasEndpoint * ((:>) * Symbol path sub) Source # 

Methods

getEndpoint :: Proxy ((* :> Symbol) path sub) a -> Request -> Maybe ([Text], Method) Source #

ReflectMethod k1 method => HasEndpoint * (Verb k k1 method status cts a) Source # 

Methods

getEndpoint :: Proxy (Verb k k1 method status cts a) a -> Request -> Maybe ([Text], Method) Source #