| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Servant.Server.Internal.Context
Contents
Synopsis
- data Context contextTypes where- EmptyContext :: Context '[]
- (:.) :: x -> Context xs -> Context (x ': xs)
 
- type family (l1 :: [*]) .++ (l2 :: [*]) where ...
- (.++) :: Context l1 -> Context l2 -> Context (l1 .++ l2)
- class HasContextEntry (context :: [*]) (val :: *) where- getContextEntry :: Context context -> val
 
- data NamedContext (name :: Symbol) (subContext :: [*]) = NamedContext (Context subContext)
- descendIntoNamedContext :: forall context name subContext. HasContextEntry context (NamedContext name subContext) => Proxy (name :: Symbol) -> Context context -> Context subContext
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 heterogeneous
 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 :. () :. EmptyContextTrue :. () :. EmptyContext :: Context '[Bool, ()]
Constructors
| EmptyContext :: Context '[] | |
| (:.) :: x -> Context xs -> Context (x ': xs) infixr 5 | 
type family (l1 :: [*]) .++ (l2 :: [*]) where ... Source #
Append two type-level lists.
Hint: import it as
import Servant.Server (type (.++))
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) :: BoolTrue
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 xs val => HasContextEntry (notIt ': xs) val Source # | |
| Defined in Servant.Server.Internal.Context Methods getContextEntry :: Context (notIt ': xs) -> val Source # | |
| HasContextEntry (val ': xs) val Source # | |
| Defined in Servant.Server.Internal.Context Methods getContextEntry :: Context (val ': 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 subContextsubContext :: Context '[Bool]>>>let parentContext = False :. (NamedContext subContext :: NamedContext "subContext" '[Bool]) :. EmptyContext>>>:type parentContextparentContext :: Context '[Bool, NamedContext "subContext" '[Bool]]>>>descendIntoNamedContext (Proxy :: Proxy "subContext") parentContext :: Context '[Bool]True :. EmptyContext