Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Auth.Server
Synopsis
- data Auth (auths :: [Type]) val
- data AuthResult val
- = BadPassword
- | NoSuchUser
- | Authenticated val
- | Indefinite
- newtype AuthCheck val = AuthCheck {
- runAuthCheck :: Request -> IO (AuthResult val)
- data JWT
- class FromJWT a where
- class ToJWT a where
- data IsMatch
- data JWTSettings = JWTSettings {
- signingKey :: JWK
- jwtAlg :: Maybe Alg
- validationKeys :: IO JWKSet
- audienceMatches :: StringOrURI -> IsMatch
- defaultJWTSettings :: JWK -> JWTSettings
- jwtAuthCheck :: FromJWT usr => JWTSettings -> AuthCheck usr
- data Cookie
- data CookieSettings = CookieSettings {
- cookieIsSecure :: !IsSecure
- cookieMaxAge :: !(Maybe DiffTime)
- cookieExpires :: !(Maybe UTCTime)
- cookiePath :: !(Maybe ByteString)
- cookieDomain :: !(Maybe ByteString)
- cookieSameSite :: !SameSite
- sessionCookieName :: !ByteString
- cookieXsrfSetting :: !(Maybe XsrfCookieSettings)
- data XsrfCookieSettings = XsrfCookieSettings {}
- defaultCookieSettings :: CookieSettings
- defaultXsrfCookieSettings :: XsrfCookieSettings
- makeSessionCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie)
- makeSessionCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString)
- makeXsrfCookie :: CookieSettings -> IO SetCookie
- makeCsrfCookie :: CookieSettings -> IO SetCookie
- makeCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie)
- makeCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString)
- acceptLogin :: forall (mods :: [Type]) response withOneCookie withTwoCookies session. (AddHeader mods "Set-Cookie" SetCookie response withOneCookie, AddHeader mods "Set-Cookie" SetCookie withOneCookie withTwoCookies, ToJWT session) => CookieSettings -> JWTSettings -> session -> IO (Maybe (response -> withTwoCookies))
- clearSession :: forall (mods :: [Type]) response withOneCookie withTwoCookies. (AddHeader mods "Set-Cookie" SetCookie response withOneCookie, AddHeader mods "Set-Cookie" SetCookie withOneCookie withTwoCookies) => CookieSettings -> response -> withTwoCookies
- data IsSecure
- data SameSite
- class AreAuths (as :: [Type]) (ctxs :: [Type]) v
- data BasicAuth
- class FromBasicAuthData a where
- fromBasicAuthData :: BasicAuthData -> BasicAuthCfg -> IO (AuthResult a)
- type family BasicAuthCfg
- data BasicAuthData = BasicAuthData {}
- data IsPasswordCorrect
- wwwAuthenticatedErr :: ByteString -> ServerError
- class ThrowAll a where
- throwAll :: ServerError -> a
- generateKey :: IO JWK
- generateSecret :: MonadRandom m => m ByteString
- fromSecret :: ByteString -> JWK
- writeKey :: FilePath -> IO ()
- readKey :: FilePath -> IO JWK
- makeJWT :: ToJWT a => a -> JWTSettings -> Maybe UTCTime -> IO (Either Error ByteString)
- verifyJWT :: FromJWT a => JWTSettings -> ByteString -> IO (Maybe a)
- class Default a where
- def :: a
- data SetCookie
Documentation
This package provides implementations for some common authentication methods. Authentication yields a trustworthy (because generated by the server) value of an some arbitrary type:
type MyApi = Protected type Protected = Auth '[JWT, Cookie] User :> Get '[JSON] UserAccountDetails server :: Server Protected server (Authenticated usr) = ... -- here we know the client really is -- who she claims to be server _ = throwAll err401
Additional configuration happens via Context
.
Example for Custom Handler
To use a custom Handler
it is necessary to use
hoistServerWithContext
instead of
hoistServer
and specify the Context
.
Below is an example of passing CookieSettings
and JWTSettings
in the
Context
to create a specialized function equivalent to
hoistServer
for an API that includes cookie
authentication.
hoistServerWithAuth :: HasServer api '[CookieSettings, JWTSettings] => Proxy api -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n hoistServerWithAuth api = hoistServerWithContext api (Proxy :: Proxy '[CookieSettings, JWTSettings])
Auth
Basic types
data Auth (auths :: [Type]) val #
Auth [auth1, auth2] val :> api
represents an API protected *either* by
auth1
or auth2
Instances
HasLink sub => HasLink (Auth tag value :> sub :: Type) | A |
(AddSetCookies n (ServerT api Handler) (ServerT (AddSetCookiesApi n api) Handler), AreAuths auths ctxs v, HasContextEntry ctxs CookieSettings, HasContextEntry ctxs JWTSettings, HasServer (AddSetCookiesApi n api) ctxs, HasServer api ctxs, ToJWT v, n ~ 'S ('S 'Z)) => HasServer (Auth auths v :> api :: Type) ctxs Source # | |
Defined in Servant.Auth.Server.Internal | |
type MkLink (Auth tag value :> sub :: Type) a | |
type ServerT (Auth auths v :> api :: Type) m Source # | |
Defined in Servant.Auth.Server.Internal |
data AuthResult val Source #
The result of an authentication attempt.
Constructors
BadPassword | |
NoSuchUser | |
Authenticated val | Authentication succeeded. |
Indefinite | If an authentication procedure cannot be carried out - if for example it
expects a password and username in a header that is not present -
|
Instances
newtype AuthCheck val Source #
An AuthCheck
is the function used to decide the authentication status
(the AuthResult
) of a request. Different AuthCheck
s may be combined as a
Monoid or Alternative; the semantics of this is that the *first*
non-Indefinite
result from left to right is used and the rest are ignored.
Constructors
AuthCheck | |
Fields
|
Instances
MonadFail AuthCheck Source # | |||||
Defined in Servant.Auth.Server.Internal.Types | |||||
MonadIO AuthCheck Source # | |||||
Defined in Servant.Auth.Server.Internal.Types | |||||
Alternative AuthCheck Source # | |||||
Applicative AuthCheck Source # | |||||
Defined in Servant.Auth.Server.Internal.Types | |||||
Functor AuthCheck Source # | |||||
Monad AuthCheck Source # | |||||
MonadPlus AuthCheck Source # | |||||
MonadTime AuthCheck Source # | |||||
Defined in Servant.Auth.Server.Internal.Types | |||||
MonadReader Request AuthCheck Source # | |||||
Monoid (AuthCheck val) Source # | |||||
Semigroup (AuthCheck val) Source # | |||||
Generic (AuthCheck val) Source # | |||||
Defined in Servant.Auth.Server.Internal.Types Associated Types
| |||||
type Rep (AuthCheck val) Source # | |||||
Defined in Servant.Auth.Server.Internal.Types type Rep (AuthCheck val) = D1 ('MetaData "AuthCheck" "Servant.Auth.Server.Internal.Types" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'True) (C1 ('MetaCons "AuthCheck" 'PrefixI 'True) (S1 ('MetaSel ('Just "runAuthCheck") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Request -> IO (AuthResult val))))) |
JWT
JSON Web Tokens (JWT) are a compact and secure way of transferring information between parties. In this library, they are signed by the server (or by some other party posessing the relevant key), and used to indicate the bearer's identity or authorization.
Arbitrary information can be encoded - just declare instances for the
FromJWT
and ToJWT
classes. Don't go overboard though - be aware that
usually you'll be trasmitting this information on each request (and
response!).
Note that, while the tokens are signed, they are not encrypted. Do not put any information you do not wish the client to know in them!
Combinator
Re-exported from 'servant-auth'
A JSON Web Token (JWT) in the Authorization header:
Authorization: Bearer <token>
Note that while the token is signed, it is not encrypted. Therefore do not keep in it any information you would not like the client to know.
JWTs are described in IETF's RFC 7519
Instances
FromJWT usr => IsAuth JWT usr Source # | |||||
Defined in Servant.Auth.Server.Internal.Class Associated Types
| |||||
type AuthArgs JWT Source # | |||||
Defined in Servant.Auth.Server.Internal.Class |
Classes
How to decode data from a JWT.
The default implementation assumes the data is stored in the unregistered
dat
claim, and uses the FromJSON
instance to decode value from there.
Minimal complete definition
Nothing
How to encode data from a JWT.
The default implementation stores data in the unregistered dat
claim, and
uses the type's ToJSON
instance to encode the data.
Minimal complete definition
Nothing
Related types
Constructors
Matches | |
DoesNotMatch |
Instances
Generic IsMatch Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
| |||||
Read IsMatch Source # | |||||
Show IsMatch Source # | |||||
Eq IsMatch Source # | |||||
Ord IsMatch Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes | |||||
type Rep IsMatch Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes |
Settings
data JWTSettings Source #
JWTSettings
are used to generate cookies, and to verify JWTs.
Constructors
JWTSettings | |
Fields
|
Instances
Generic JWTSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
| |||||
type Rep JWTSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes type Rep JWTSettings = D1 ('MetaData "JWTSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'False) (C1 ('MetaCons "JWTSettings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "signingKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JWK) :*: S1 ('MetaSel ('Just "jwtAlg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Alg))) :*: (S1 ('MetaSel ('Just "validationKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IO JWKSet)) :*: S1 ('MetaSel ('Just "audienceMatches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (StringOrURI -> IsMatch))))) |
defaultJWTSettings :: JWK -> JWTSettings Source #
A JWTSettings
where the audience always matches.
Create check
jwtAuthCheck :: FromJWT usr => JWTSettings -> AuthCheck usr Source #
A JWT AuthCheck
. You likely won't need to use this directly unless you
are protecting a Raw
endpoint.
Cookie
Cookies are also a method of identifying and authenticating a user. They are particular common when the client is a browser
Combinator
Re-exported from 'servant-auth'
A cookie. The content cookie itself is a JWT. Another cookie is also used, the contents of which are expected to be send back to the server in a header, for XSRF protection.
Instances
FromJWT usr => IsAuth Cookie usr Source # | |||||
Defined in Servant.Auth.Server.Internal.Class Associated Types
| |||||
type AuthArgs Cookie Source # | |||||
Defined in Servant.Auth.Server.Internal.Class |
Settings
data CookieSettings Source #
The policies to use when generating cookies.
If *both* cookieMaxAge
and cookieExpires
are Nothing
, browsers will
treat the cookie as a *session cookie*. These will be deleted when the
browser is closed.
Note that having the setting Secure
may cause testing failures if you are
not testing over HTTPS.
Constructors
CookieSettings | |
Fields
|
Instances
Generic CookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
Methods from :: CookieSettings -> Rep CookieSettings x # to :: Rep CookieSettings x -> CookieSettings # | |||||
Show CookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods showsPrec :: Int -> CookieSettings -> ShowS # show :: CookieSettings -> String # showList :: [CookieSettings] -> ShowS # | |||||
Default CookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods def :: CookieSettings # | |||||
Eq CookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods (==) :: CookieSettings -> CookieSettings -> Bool # (/=) :: CookieSettings -> CookieSettings -> Bool # | |||||
type Rep CookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes type Rep CookieSettings = D1 ('MetaData "CookieSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'False) (C1 ('MetaCons "CookieSettings" 'PrefixI 'True) (((S1 ('MetaSel ('Just "cookieIsSecure") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IsSecure) :*: S1 ('MetaSel ('Just "cookieMaxAge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DiffTime))) :*: (S1 ('MetaSel ('Just "cookieExpires") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "cookiePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)))) :*: ((S1 ('MetaSel ('Just "cookieDomain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "cookieSameSite") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SameSite)) :*: (S1 ('MetaSel ('Just "sessionCookieName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "cookieXsrfSetting") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe XsrfCookieSettings)))))) |
data XsrfCookieSettings Source #
The policies to use when generating and verifying XSRF cookies
Constructors
XsrfCookieSettings | |
Fields
|
Instances
Generic XsrfCookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
Methods from :: XsrfCookieSettings -> Rep XsrfCookieSettings x # to :: Rep XsrfCookieSettings x -> XsrfCookieSettings # | |||||
Show XsrfCookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods showsPrec :: Int -> XsrfCookieSettings -> ShowS # show :: XsrfCookieSettings -> String # showList :: [XsrfCookieSettings] -> ShowS # | |||||
Default XsrfCookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods | |||||
Eq XsrfCookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods (==) :: XsrfCookieSettings -> XsrfCookieSettings -> Bool # (/=) :: XsrfCookieSettings -> XsrfCookieSettings -> Bool # | |||||
type Rep XsrfCookieSettings Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes type Rep XsrfCookieSettings = D1 ('MetaData "XsrfCookieSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'False) (C1 ('MetaCons "XsrfCookieSettings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "xsrfCookieName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "xsrfCookiePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString))) :*: (S1 ('MetaSel ('Just "xsrfHeaderName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "xsrfExcludeGet") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) |
makeSessionCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie) Source #
Makes a cookie with session information.
makeSessionCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString) Source #
makeXsrfCookie :: CookieSettings -> IO SetCookie Source #
Makes a cookie to be used for XSRF.
makeCsrfCookie :: CookieSettings -> IO SetCookie Source #
Deprecated: Use makeXsrfCookie instead
Alias for makeXsrfCookie
.
makeCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie) Source #
Deprecated: Use makeSessionCookie instead
Alias for makeSessionCookie
.
makeCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString) Source #
Deprecated: Use makeSessionCookieBS instead
Alias for makeSessionCookieBS
.
acceptLogin :: forall (mods :: [Type]) response withOneCookie withTwoCookies session. (AddHeader mods "Set-Cookie" SetCookie response withOneCookie, AddHeader mods "Set-Cookie" SetCookie withOneCookie withTwoCookies, ToJWT session) => CookieSettings -> JWTSettings -> session -> IO (Maybe (response -> withTwoCookies)) Source #
For a JWT-serializable session, returns a function that decorates a provided response object with XSRF and session cookies. This should be used when a user successfully authenticates with credentials.
clearSession :: forall (mods :: [Type]) response withOneCookie withTwoCookies. (AddHeader mods "Set-Cookie" SetCookie response withOneCookie, AddHeader mods "Set-Cookie" SetCookie withOneCookie withTwoCookies) => CookieSettings -> response -> withTwoCookies Source #
Adds headers to a response that clears all session cookies | using max-age and expires cookie attributes.
Related types
Was this request made over an SSL connection?
Note that this value will not tell you if the client originally
made this request over SSL, but rather whether the current
connection is SSL. The distinction lies with reverse proxies.
In many cases, the client will connect to a load balancer over SSL,
but connect to the WAI handler without SSL. In such a case,
the handlers would get NotSecure
, but from a user perspective,
there is a secure connection.
Constructors
Secure | the connection to the server is secure (HTTPS) |
NotSecure | the connection to the server is not secure (HTTP) |
Instances
Generic IsSecure | |
Defined in Servant.API.IsSecure | |
Read IsSecure | |
Show IsSecure | |
Eq IsSecure | |
Ord IsSecure | |
Defined in Servant.API.IsSecure | |
HasLink sub => HasLink (IsSecure :> sub :: Type) | |
HasServer api context => HasServer (IsSecure :> api :: Type) context | |
Defined in Servant.Server.Internal | |
type Rep IsSecure | |
type MkLink (IsSecure :> sub :: Type) a | |
type ServerT (IsSecure :> api :: Type) m | |
Constructors
AnySite | |
SameSiteStrict | |
SameSiteLax |
Instances
Generic SameSite Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
| |||||
Read SameSite Source # | |||||
Show SameSite Source # | |||||
Eq SameSite Source # | |||||
Ord SameSite Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes | |||||
type Rep SameSite Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes type Rep SameSite = D1 ('MetaData "SameSite" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'False) (C1 ('MetaCons "AnySite" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SameSiteStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SameSiteLax" 'PrefixI 'False) (U1 :: Type -> Type))) |
class AreAuths (as :: [Type]) (ctxs :: [Type]) v Source #
Minimal complete definition
BasicAuth
Combinator
Re-exported from 'servant-auth'
Basic Auth.
Instances
FromBasicAuthData usr => IsAuth BasicAuth usr Source # | |||||
Defined in Servant.Auth.Server.Internal.Class Associated Types
| |||||
type AuthArgs BasicAuth Source # | |||||
Defined in Servant.Auth.Server.Internal.Class |
Classes
class FromBasicAuthData a where Source #
Methods
fromBasicAuthData :: BasicAuthData -> BasicAuthCfg -> IO (AuthResult a) Source #
Whether the username exists and the password is correct.
Note that, rather than passing a Pass
to the function, we pass a
function that checks an EncryptedPass
. This is to make sure you don't
accidentally do something untoward with the password, like store it.
Settings
type family BasicAuthCfg Source #
A type holding the configuration for Basic Authentication.
It is defined as a type family with no arguments, so that
it can be instantiated to whatever type you need to
authenticate your users (use type instance BasicAuthCfg = ...
).
Note that the instantiation is application-wide, i.e. there can be only one instance. As a consequence, it should not be instantiated in a library.
Basic Authentication expects an element of type BasicAuthCfg
to be in the Context
; that element is then passed automatically
to the instance of FromBasicAuthData
together with the
authentication data obtained from the client.
If you do not need a configuration for Basic Authentication,
you can use just BasicAuthCfg = ()
, and recall to also
add ()
to the Context
.
A basic but more interesting example is to take as BasicAuthCfg
a list of authorised username/password pairs:
deriving instance Eq BasicAuthData type instance BasicAuthCfg = [BasicAuthData] instance FromBasicAuthData User where fromBasicAuthData authData authCfg = if elem authData authCfg then ...
Related types
data BasicAuthData #
A simple datatype to hold data required to decorate a request
Constructors
BasicAuthData | |
Fields |
data IsPasswordCorrect Source #
Constructors
PasswordCorrect | |
PasswordIncorrect |
Instances
Generic IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Associated Types
Methods from :: IsPasswordCorrect -> Rep IsPasswordCorrect x # to :: Rep IsPasswordCorrect x -> IsPasswordCorrect # | |||||
Read IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods readsPrec :: Int -> ReadS IsPasswordCorrect # readList :: ReadS [IsPasswordCorrect] # | |||||
Show IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods showsPrec :: Int -> IsPasswordCorrect -> ShowS # show :: IsPasswordCorrect -> String # showList :: [IsPasswordCorrect] -> ShowS # | |||||
Eq IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods (==) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # (/=) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # | |||||
Ord IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods compare :: IsPasswordCorrect -> IsPasswordCorrect -> Ordering # (<) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # (<=) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # (>) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # (>=) :: IsPasswordCorrect -> IsPasswordCorrect -> Bool # max :: IsPasswordCorrect -> IsPasswordCorrect -> IsPasswordCorrect # min :: IsPasswordCorrect -> IsPasswordCorrect -> IsPasswordCorrect # | |||||
type Rep IsPasswordCorrect Source # | |||||
Defined in Servant.Auth.Server.Internal.ConfigTypes type Rep IsPasswordCorrect = D1 ('MetaData "IsPasswordCorrect" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.9.1-4gCm79nClZlK0DXZWI8UFm" 'False) (C1 ('MetaCons "PasswordCorrect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PasswordIncorrect" 'PrefixI 'False) (U1 :: Type -> Type)) |
Authentication request
wwwAuthenticatedErr :: ByteString -> ServerError Source #
A ServerError
that asks the client to authenticate via Basic
Authentication, should be invoked by an application whenever
appropriate. The argument is the realm.
Utilies
class ThrowAll a where Source #
Methods
throwAll :: ServerError -> a Source #
throwAll
is a convenience function to throw errors across an entire
sub-API
throwAll err400 :: Handler a :<|> Handler b :<|> Handler c == throwError err400 :<|> throwError err400 :<|> err400
Instances
ThrowAll Application Source # | for |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> Application Source # | |
(GenericServant api (AsServerT m), ThrowAll (ToServant api (AsServerT m))) => ThrowAll (api (AsServerT m)) Source # | |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> api (AsServerT m) Source # | |
MonadError ServerError m => ThrowAll (m a) Source # | |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> m a Source # | |
(ThrowAll a, ThrowAll b) => ThrowAll (a :<|> b) Source # | |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> a :<|> b Source # | |
ThrowAll b => ThrowAll (a -> b) Source # | |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> a -> b Source # | |
MonadError ServerError m => ThrowAll (Tagged m Application) Source # | for |
Defined in Servant.Auth.Server.Internal.ThrowAll Methods throwAll :: ServerError -> Tagged m Application Source # |
generateKey :: IO JWK Source #
Generate a key suitable for use with defaultConfig
.
generateSecret :: MonadRandom m => m ByteString Source #
Generate a bytestring suitable for use with fromSecret
.
fromSecret :: ByteString -> JWK Source #
Restores a key from a bytestring.
writeKey :: FilePath -> IO () Source #
Writes a secret to a file. Can for instance be used from the REPL
to persist a key to a file, which can then be included with the
application. Restore the key using readKey
.
makeJWT :: ToJWT a => a -> JWTSettings -> Maybe UTCTime -> IO (Either Error ByteString) Source #
Creates a JWT containing the specified data. The data is stored in the
dat
claim. The 'Maybe UTCTime' argument indicates the time at which the
token expires.
verifyJWT :: FromJWT a => JWTSettings -> ByteString -> IO (Maybe a) Source #
Re-exports
A class for types with a default value.
Minimal complete definition
Nothing
Methods
The default value for this type.
Instances
Default All | |
Defined in Data.Default.Internal | |
Default Any | |
Defined in Data.Default.Internal | |
Default CBool | |
Defined in Data.Default.Internal | |
Default CClock | |
Defined in Data.Default.Internal | |
Default CDouble | |
Defined in Data.Default.Internal | |
Default CFloat | |
Defined in Data.Default.Internal | |
Default CInt | |
Defined in Data.Default.Internal | |
Default CIntMax | |
Defined in Data.Default.Internal | |
Default CIntPtr | |
Defined in Data.Default.Internal | |
Default CLLong | |
Defined in Data.Default.Internal | |
Default CLong | |
Defined in Data.Default.Internal | |
Default CPtrdiff | |
Defined in Data.Default.Internal | |
Default CSUSeconds | |
Defined in Data.Default.Internal Methods def :: CSUSeconds # | |
Default CShort | |
Defined in Data.Default.Internal | |
Default CSigAtomic | |
Defined in Data.Default.Internal Methods def :: CSigAtomic # | |
Default CSize | |
Defined in Data.Default.Internal | |
Default CTime | |
Defined in Data.Default.Internal | |
Default CUInt | |
Defined in Data.Default.Internal | |
Default CUIntMax | |
Defined in Data.Default.Internal | |
Default CUIntPtr | |
Defined in Data.Default.Internal | |
Default CULLong | |
Defined in Data.Default.Internal | |
Default CULong | |
Defined in Data.Default.Internal | |
Default CUSeconds | |
Defined in Data.Default.Internal | |
Default CUShort | |
Defined in Data.Default.Internal | |
Default IntPtr | |
Defined in Data.Default.Internal | |
Default WordPtr | |
Defined in Data.Default.Internal | |
Default Int16 | |
Defined in Data.Default.Internal | |
Default Int32 | |
Defined in Data.Default.Internal | |
Default Int64 | |
Defined in Data.Default.Internal | |
Default Int8 | |
Defined in Data.Default.Internal | |
Default Word16 | |
Defined in Data.Default.Internal | |
Default Word32 | |
Defined in Data.Default.Internal | |
Default Word64 | |
Defined in Data.Default.Internal | |
Default Word8 | |
Defined in Data.Default.Internal | |
Default IntSet | |
Defined in Data.Default.Internal | |
Default SetCookie |
|
Defined in Web.Cookie | |
Default Ordering | |
Defined in Data.Default.Internal | |
Default CookieSettings Source # | |
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods def :: CookieSettings # | |
Default XsrfCookieSettings Source # | |
Defined in Servant.Auth.Server.Internal.ConfigTypes Methods | |
Default Integer | |
Defined in Data.Default.Internal | |
Default () | |
Defined in Data.Default.Internal | |
Default Bool | |
Defined in Data.Default.Internal | |
Default Double | |
Defined in Data.Default.Internal | |
Default Float | |
Defined in Data.Default.Internal | |
Default Int | |
Defined in Data.Default.Internal | |
Default Word | |
Defined in Data.Default.Internal | |
(Default a, RealFloat a) => Default (Complex a) | |
Defined in Data.Default.Internal | |
Default a => Default (Identity a) | |
Defined in Data.Default.Internal | |
Default (First a) | |
Defined in Data.Default.Internal | |
Default (Last a) | |
Defined in Data.Default.Internal | |
Default a => Default (Dual a) | |
Defined in Data.Default.Internal | |
Default (Endo a) | |
Defined in Data.Default.Internal | |
Num a => Default (Product a) | |
Defined in Data.Default.Internal | |
Num a => Default (Sum a) | |
Defined in Data.Default.Internal | |
Default (ConstPtr a) | |
Defined in Data.Default.Internal | |
Default (FunPtr a) | |
Defined in Data.Default.Internal | |
Default (Ptr a) | |
Defined in Data.Default.Internal | |
Integral a => Default (Ratio a) | |
Defined in Data.Default.Internal | |
Default (IntMap v) | |
Defined in Data.Default.Internal | |
Default (Seq a) | |
Defined in Data.Default.Internal | |
Default (Set v) | |
Defined in Data.Default.Internal | |
Default a => Default (Tree a) | |
Defined in Data.Default.Internal | |
Default (Maybe a) | |
Defined in Data.Default.Internal | |
Default a => Default (Solo a) | |
Defined in Data.Default.Internal | |
Default [a] | |
Defined in Data.Default.Internal | |
HasResolution a => Default (Fixed a) | |
Defined in Data.Default.Internal | |
Default (Proxy a) | |
Defined in Data.Default.Internal | |
Default (Map k v) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2) => Default (a1, a2) | |
Defined in Data.Default.Internal | |
Default a => Default (Const a b) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3) => Default (a1, a2, a3) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4) => Default (a1, a2, a3, a4) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5) => Default (a1, a2, a3, a4, a5) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6) => Default (a1, a2, a3, a4, a5, a6) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7) => Default (a1, a2, a3, a4, a5, a6, a7) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8) => Default (a1, a2, a3, a4, a5, a6, a7, a8) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29, Default a30) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30) | |
Defined in Data.Default.Internal | |
(Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10, Default a11, Default a12, Default a13, Default a14, Default a15, Default a16, Default a17, Default a18, Default a19, Default a20, Default a21, Default a22, Default a23, Default a24, Default a25, Default a26, Default a27, Default a28, Default a29, Default a30, Default a31) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, a21, a22, a23, a24, a25, a26, a27, a28, a29, a30, a31) | |
Defined in Data.Default.Internal |
Data type representing the key-value pair to use for a cookie, as well as configuration options for it.
Creating a SetCookie
SetCookie
does not export a constructor; instead, use defaultSetCookie
and override values (see http://www.yesodweb.com/book/settings-types for details):
import Web.Cookie :set -XOverloadedStrings let cookie =defaultSetCookie
{setCookieName
= "cookieName",setCookieValue
= "cookieValue" }
Cookie Configuration
Cookies have several configuration options; a brief summary of each option is given below. For more information, see RFC 6265 or Wikipedia.
Instances
Show SetCookie | |
Default SetCookie |
|
Defined in Web.Cookie | |
NFData SetCookie | |
Defined in Web.Cookie | |
Eq SetCookie | |
FromHttpApiData SetCookie | Note: this instance works correctly for alphanumeric name and value
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text SetCookie # parseHeader :: ByteString -> Either Text SetCookie # | |
ToHttpApiData SetCookie | Note: this instance works correctly for alphanumeric name and value
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: SetCookie -> Text # toEncodedUrlPiece :: SetCookie -> Builder # toHeader :: SetCookie -> ByteString # toQueryParam :: SetCookie -> Text # toEncodedQueryParam :: SetCookie -> Builder # |