servant-auth-server-0.4.9.1: servant-server/servant-auth compatibility
Safe HaskellNone
LanguageHaskell2010

Servant.Auth.Server.Internal.AddSetCookie

Documentation

data Nat Source #

Constructors

Z 
S Nat 

type family AddSetCookiesApi (n :: Nat) a where ... Source #

type family AddSetCookieApiVerb a where ... Source #

Equations

AddSetCookieApiVerb (Headers ls a) = Headers (Header "Set-Cookie" SetCookie ': ls) a 
AddSetCookieApiVerb a = Headers '[Header "Set-Cookie" SetCookie] a 

type family MapAddSetCookieApiVerb (as :: [Type]) :: [Type] where ... Source #

type family AddSetCookieApi a Source #

Instances

Instances details
type AddSetCookieApi Raw Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (NamedRoutes api) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (a :<|> b) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (Headers hs a) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (a :> b) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (UVerb method ctyps as) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (UVerb method ctyps as) = UVerb method ctyps (MapAddSetCookieApiVerb as)
type AddSetCookieApi (Verb method stat ctyps a) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (Verb method stat ctyps a) = Verb method stat ctyps (AddSetCookieApiVerb a)
type AddSetCookieApi (Stream method stat framing ctyps a) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

type AddSetCookieApi (Stream method stat framing ctyps a) = Stream method stat framing ctyps (AddSetCookieApiVerb a)

data SetCookieList (n :: Nat) where Source #

Constructors

SetCookieNil :: SetCookieList 'Z 
SetCookieCons :: forall (n1 :: Nat). Maybe SetCookie -> SetCookieList n1 -> SetCookieList ('S n1) 

class AddSetCookies (n :: Nat) orig new where Source #

Methods

addSetCookies :: SetCookieList n -> orig -> new Source #

Instances

Instances details
orig1 ~ orig2 => AddSetCookies 'Z orig1 orig2 Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList 'Z -> orig1 -> orig2 Source #

AddSetCookies ('S n) Application Application Source #

for servant <0.11

Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

(AddSetCookies ('S n) (ServerT (ToServantApi api) m) cookiedApi, GServantProduct (Rep (api (AsServerT m))), Generic (api (AsServerT m)), ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m) => AddSetCookies ('S n) (api (AsServerT m)) cookiedApi Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList ('S n) -> api (AsServerT m) -> cookiedApi Source #

(AddHeader mods "Set-Cookie" SetCookie cookied new, AddSetCookies n (m old) (m cookied), Functor m) => AddSetCookies ('S n) (m old) (m new) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList ('S n) -> m old -> m new Source #

(AddSetCookies ('S n) a a, AddSetCookies ('S n) b b') => AddSetCookies ('S n) (a :<|> b) (a :<|> b') Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList ('S n) -> (a :<|> b) -> a :<|> b' Source #

(AddSetCookies ('S n) a a', AddSetCookies ('S n) b b') => AddSetCookies ('S n) (a :<|> b) (a' :<|> b') Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList ('S n) -> (a :<|> b) -> a' :<|> b' Source #

AddSetCookies ('S n) oldb newb => AddSetCookies ('S n) (a -> oldb) (a -> newb) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

Methods

addSetCookies :: SetCookieList ('S n) -> (a -> oldb) -> a -> newb Source #

AddSetCookies ('S n) (Tagged m Application) (Tagged m Application) Source #

for servant >=0.11

Instance details

Defined in Servant.Auth.Server.Internal.AddSetCookie

mkHeaders :: forall (x :: Nat). SetCookieList x -> [Header] Source #