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

Safe HaskellNone
LanguageHaskell2010

Servant.Ekg

Documentation

class HasEndpoint a where Source #

Instances
HasEndpoint Raw Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint EmptyAPI Source # 
Instance details

Defined in Servant.Ekg

ReflectMethod method => HasEndpoint (NoContentVerb method :: Type) Source # 
Instance details

Defined in Servant.Ekg

(HasEndpoint a, HasEndpoint b) => HasEndpoint (a :<|> b :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (WithNamedContext x y sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (HttpVersion :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (StreamBody' mods framing ct a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

Methods

getEndpoint :: Proxy (StreamBody' mods framing ct a :> sub) -> Request -> Maybe APIEndpoint Source #

enumerateEndpoints :: Proxy (StreamBody' mods framing ct a :> sub) -> [APIEndpoint] Source #

HasEndpoint sub => HasEndpoint (ReqBody' mods cts a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

Methods

getEndpoint :: Proxy (ReqBody' mods cts a :> sub) -> Request -> Maybe APIEndpoint Source #

enumerateEndpoints :: Proxy (ReqBody' mods cts a :> sub) -> [APIEndpoint] Source #

HasEndpoint sub => HasEndpoint (RemoteHost :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (QueryParam' mods h a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (QueryParams h a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (QueryFlag h :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (Header' mods h a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (IsSecure :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (Summary d :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (Description d :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

(KnownSymbol capture, HasEndpoint sub) => HasEndpoint (Capture' mods capture a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

Methods

getEndpoint :: Proxy (Capture' mods capture a :> sub) -> Request -> Maybe APIEndpoint Source #

enumerateEndpoints :: Proxy (Capture' mods capture a :> sub) -> [APIEndpoint] Source #

HasEndpoint sub => HasEndpoint (CaptureAll h a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (BasicAuth realm a :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

HasEndpoint sub => HasEndpoint (Vault :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

(KnownSymbol path, HasEndpoint sub) => HasEndpoint (path :> sub :: Type) Source # 
Instance details

Defined in Servant.Ekg

ReflectMethod method => HasEndpoint (Verb method status cts a :: Type) Source # 
Instance details

Defined in Servant.Ekg

Methods

getEndpoint :: Proxy (Verb method status cts a) -> Request -> Maybe APIEndpoint Source #

enumerateEndpoints :: Proxy (Verb method status cts a) -> [APIEndpoint] Source #

ReflectMethod method => HasEndpoint (Stream method status framing ct a :: Type) Source # 
Instance details

Defined in Servant.Ekg

Methods

getEndpoint :: Proxy (Stream method status framing ct a) -> Request -> Maybe APIEndpoint Source #

enumerateEndpoints :: Proxy (Stream method status framing ct a) -> [APIEndpoint] Source #

data APIEndpoint Source #

Constructors

APIEndpoint 

Fields

Instances
Eq APIEndpoint Source # 
Instance details

Defined in Servant.Ekg.Internal

Show APIEndpoint Source # 
Instance details

Defined in Servant.Ekg.Internal

Generic APIEndpoint Source # 
Instance details

Defined in Servant.Ekg.Internal

Associated Types

type Rep APIEndpoint :: Type -> Type #

Hashable APIEndpoint Source # 
Instance details

Defined in Servant.Ekg.Internal

type Rep APIEndpoint Source # 
Instance details

Defined in Servant.Ekg.Internal

type Rep APIEndpoint = D1 (MetaData "APIEndpoint" "Servant.Ekg.Internal" "servant-ekg-0.3.1-98YxKD7Zsig1t2vtXJMDF0" False) (C1 (MetaCons "APIEndpoint" PrefixI True) (S1 (MetaSel (Just "pathSegments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: S1 (MetaSel (Just "method") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Method)))