servant-server-0.16: A family of combinators for defining webservices APIs and serving them

Safe HaskellSafe
LanguageHaskell2010

Servant.Server.Internal.Context

Contents

Synopsis

Documentation

data Context contextTypes where Source #

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 :: Context '[] 
(:.) :: x -> Context xs -> Context (x ': xs) infixr 5 
Instances
(Eq a, Eq (Context as)) => Eq (Context (a ': as)) Source # 
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])) Source # 
Instance details

Defined in Servant.Server.Internal.Context

Methods

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

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

(Show a, Show (Context as)) => Show (Context (a ': as)) Source # 
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])) Source # 
Instance details

Defined in Servant.Server.Internal.Context

Methods

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

show :: Context [] -> String #

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

class HasContextEntry (context :: [*]) (val :: *) where Source #

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 Source #

Instances
HasContextEntry (val ': xs) val Source # 
Instance details

Defined in Servant.Server.Internal.Context

Methods

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

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

Defined in Servant.Server.Internal.Context

Methods

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

support for named subcontexts

data NamedContext (name :: Symbol) (subContext :: [*]) Source #

Normally context entries are accessed by their types. In case you need to have multiple values of the same type in your Context and need to access them, we provide NamedContext. You can think of it as sub-namespaces for Contexts.

Constructors

NamedContext (Context subContext) 

descendIntoNamedContext :: forall context name subContext. HasContextEntry context (NamedContext name subContext) => Proxy (name :: Symbol) -> Context context -> Context subContext Source #

descendIntoNamedContext allows you to access NamedContexts. Usually you won't have to use it yourself but instead use a combinator like WithNamedContext.

This is how descendIntoNamedContext works:

>>> :set -XFlexibleContexts
>>> let subContext = True :. EmptyContext
>>> :type subContext
subContext :: Context '[Bool]
>>> let parentContext = False :. (NamedContext subContext :: NamedContext "subContext" '[Bool]) :. EmptyContext
>>> :type parentContext
parentContext :: Context '[Bool, NamedContext "subContext" '[Bool]]
>>> descendIntoNamedContext (Proxy :: Proxy "subContext") parentContext :: Context '[Bool]
True :. EmptyContext