servant-combinators-0.0.2: Extra servant combinators for full WAI functionality.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.API.Cookies

Description

 
Synopsis

Documentation

type SessionMap = Map ByteString ByteString Source #

A SessionMap is a hash map of session data from a request.

type SetCookieHeader a = Headers '[Header "Set-Cookie" SetCookie] a Source #

A SetCookieHeader is a convenience type for adding a "Set-Cookie" header that expects a SetCookie record type.

I wanted to have the header name be NTH.hSetCookie for extra "use the known correct value" goodness, but that breaks the type magic Servant relies upon.

data ProvideCookies (mods :: [Type]) Source #

The ProvideCookies and WithCookies combinator work in tandem together -- the ProvideCookies combinator parses the cookies from the request and stores them in the WAI request Vault, the WithCookies combinator provides the cookies as a hash map to the handler.

Instances

Instances details
(HasServer api (HasCookiesMaybe ': ctx), HasContextEntry ctx (Key (Maybe SessionMap)), HasContextEntry ctx Key) => HasServer (ProvideCookies '[Optional] :> api :: Type) ctx Source # 
Instance details

Defined in Servant.API.Cookies

Associated Types

type ServerT (ProvideCookies '[Optional] :> api) m #

Methods

route :: Proxy (ProvideCookies '[Optional] :> api) -> Context ctx -> Delayed env (Server (ProvideCookies '[Optional] :> api)) -> Router env #

hoistServerWithContext :: Proxy (ProvideCookies '[Optional] :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (ProvideCookies '[Optional] :> api) m -> ServerT (ProvideCookies '[Optional] :> api) n #

(HasServer api (HasCookies ': ctx), HasContextEntry ctx (Key SessionMap), HasContextEntry ctx Key) => HasServer (ProvideCookies '[Required] :> api :: Type) ctx Source # 
Instance details

Defined in Servant.API.Cookies

Associated Types

type ServerT (ProvideCookies '[Required] :> api) m #

Methods

route :: Proxy (ProvideCookies '[Required] :> api) -> Context ctx -> Delayed env (Server (ProvideCookies '[Required] :> api)) -> Router env #

hoistServerWithContext :: Proxy (ProvideCookies '[Required] :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (ProvideCookies '[Required] :> api) m -> ServerT (ProvideCookies '[Required] :> api) n #

type ServerT (ProvideCookies '[Optional] :> api :: Type) m Source # 
Instance details

Defined in Servant.API.Cookies

type ServerT (ProvideCookies '[Optional] :> api :: Type) m = ServerT api m
type ServerT (ProvideCookies '[Required] :> api :: Type) m Source # 
Instance details

Defined in Servant.API.Cookies

type ServerT (ProvideCookies '[Required] :> api :: Type) m = ServerT api m

data WithCookies (mods :: [Type]) Source #

As mentioned above, the WithCookies combinator provides already-parsed cookies to the handler as a SessionMap.

The cookie values are assumed to be encrypted with a Web.ClientSession.Key. Likewise, updateCookies encrypts the cookies on the outbound side via this mechanism.

Example:

import Control.Monad.IO.Class (liftIO)
import Servant
import ServantExtras.Cookies

import qualified Data.Map.Strict as Map

type MyAPI = "my-cookie-enabled-endpoint"
           :> ProvideCookies '[Required]
           :> WithCookies '[Required]
           :> Get '[JSON] NoContent

myServer :: Server MyAPI
myServer = cookieEndpointHandler
 where
   cookieEndpointHandler :: SessionMap -> Handler NoContent
   cookieEndpointHandler sMap =
      let mCookieValue = lookup MerlinWasHere $ Map.toList sMap in
      case mCookieValue of
       Nothing -> do
         liftIO $ print "Merlin was *NOT* here!"
         throwError err400 { errBody = "Clearly you've missed something." }
       Just message -> do
         liftIO $ do
           print "Merlin WAS here, and he left us a message!"
           print message
         pure NoContent

Instances

Instances details
(HasServer api ctx, HasContextEntry ctx HasCookiesMaybe, HasContextEntry ctx (Key (Maybe SessionMap))) => HasServer (WithCookies '[Optional] :> api :: Type) ctx Source # 
Instance details

Defined in Servant.API.Cookies

Associated Types

type ServerT (WithCookies '[Optional] :> api) m #

Methods

route :: Proxy (WithCookies '[Optional] :> api) -> Context ctx -> Delayed env (Server (WithCookies '[Optional] :> api)) -> Router env #

hoistServerWithContext :: Proxy (WithCookies '[Optional] :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (WithCookies '[Optional] :> api) m -> ServerT (WithCookies '[Optional] :> api) n #

(HasServer api ctx, HasContextEntry ctx HasCookies, HasContextEntry ctx (Key SessionMap)) => HasServer (WithCookies '[Required] :> api :: Type) ctx Source # 
Instance details

Defined in Servant.API.Cookies

Associated Types

type ServerT (WithCookies '[Required] :> api) m #

Methods

route :: Proxy (WithCookies '[Required] :> api) -> Context ctx -> Delayed env (Server (WithCookies '[Required] :> api)) -> Router env #

hoistServerWithContext :: Proxy (WithCookies '[Required] :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (WithCookies '[Required] :> api) m -> ServerT (WithCookies '[Required] :> api) n #

type ServerT (WithCookies '[Optional] :> api :: Type) m Source # 
Instance details

Defined in Servant.API.Cookies

type ServerT (WithCookies '[Optional] :> api :: Type) m = Maybe SessionMap -> ServerT api m
type ServerT (WithCookies '[Required] :> api :: Type) m Source # 
Instance details

Defined in Servant.API.Cookies

type ServerT (WithCookies '[Required] :> api :: Type) m = SessionMap -> ServerT api m

data HasCookies Source #

HasCookies and HasCookiesMaybe are internal utitily types. You should only need to use ProvideCookies and WithCookies.

As an aside, they're separate types (rather than a single type with a (mods :: [Type]) ) phantom type because the term-level values show up in the instances, and I didn't see a clean way to separate them out by case, and only covering one value from the sum type made Haskell (rightly) complain.

Constructors

HasCookies 

data HasCookiesMaybe Source #

HasCookies and HasCookiesMaybe are internal utitily types. You should only need to use ProvideCookies and WithCookies.

Constructors

HasCookiesMaybe 

updateCookies :: Key -> SessionMap -> SetCookie -> ByteString -> a -> IO (SetCookieHeader a) Source #

This function takes a SessionMap and provides a "Set-Cookie" header to set the SessionData to a newly minted value of your choice.

clearSession :: SetCookie -> a -> IO (SetCookieHeader a) Source #

This function clears session data, for a fresh, minty-clean experience. The archetypal use case is when a user logs out from your server.