Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Auth.Server.Internal.AddSetCookie
Documentation
type family AddSetCookiesApi (n :: Nat) a where ... Source #
Equations
AddSetCookiesApi ('S 'Z) a = AddSetCookieApi a | |
AddSetCookiesApi ('S n) a = AddSetCookiesApi n (AddSetCookieApi a) |
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 #
Equations
MapAddSetCookieApiVerb ('[] :: [Type]) = '[] :: [Type] | |
MapAddSetCookieApiVerb (a ': as) = AddSetCookieApiVerb a ': MapAddSetCookieApiVerb as |
type family AddSetCookieApi a Source #
Instances
type AddSetCookieApi Raw Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (NamedRoutes api) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (a :<|> b) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (Headers hs a) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (a :> b) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (UVerb method ctyps as) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (Verb method stat ctyps a) Source # | |
Defined in Servant.Auth.Server.Internal.AddSetCookie | |
type AddSetCookieApi (Stream method stat framing ctyps a) Source # | |
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 #