| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Auth.Server
Contents
- data Auth auths val :: [*] -> * -> *
- data AuthResult val
- = BadPassword
- | NoSuchUser
- | Authenticated val
- | Indefinite
- data JWT :: *
- class FromJWT a where
- class ToJWT a where
- data IsMatch
- data JWTSettings = JWTSettings {
- key :: JWK
- audienceMatches :: StringOrURI -> IsMatch
- defaultJWTSettings :: JWK -> JWTSettings
- data Cookie :: *
- data CookieSettings = CookieSettings {}
- defaultCookieSettings :: CookieSettings
- makeCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie)
- makeCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString)
- data IsSecure
- class AreAuths as ctxs v
- data BasicAuth :: *
- class FromBasicAuthData a where
- fromBasicAuthData :: BasicAuthData -> BasicAuthCfg -> IO (AuthResult a)
- type family BasicAuthCfg
- data BasicAuthData :: * = BasicAuthData {}
- data IsPasswordCorrect
- class ThrowAll a where
- throwAll :: ServantErr -> a
- generateKey :: IO JWK
- makeJWT :: ToJWT a => a -> JWTSettings -> Maybe UTCTime -> IO (Either Error ByteString)
- 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 err401Additional configuration happens via Context.
Auth
Basic types
data Auth auths val :: [*] -> * -> *
Auth [auth1, auth2] val :> api represents an API protected *either* by
auth1 or auth2
Instances
| type ServerT * ((:>) * * (Auth auths v) api) m = AuthResult v -> ServerT * api m |
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
| Monad AuthResult Source | |
| Functor AuthResult Source | |
| Applicative AuthResult Source | |
| Foldable AuthResult Source | |
| Traversable AuthResult Source | |
| Alternative AuthResult Source | |
| MonadPlus AuthResult Source | |
| Eq val => Eq (AuthResult val) Source | |
| Ord val => Ord (AuthResult val) Source | |
| Read val => Read (AuthResult val) Source | |
| Show val => Show (AuthResult val) Source | |
| Generic (AuthResult val) Source | |
| Monoid (AuthResult val) Source | |
| type Rep (AuthResult val) Source |
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'
data JWT :: *
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 |
Settings
data JWTSettings Source
JWTSettings are used to generate cookies, and to verify JWTs.
Constructors
| JWTSettings | |
Fields
| |
Instances
defaultJWTSettings :: JWK -> JWTSettings Source
A JWTSettings where the audience always matches.
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'
data Cookie :: *
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 CSRF protection.
Instances
| FromJWT usr => IsAuth Cookie usr Source | |
| type AuthArgs Cookie = (:) * CookieSettings ((:) * JWTSettings ([] *)) Source |
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
| |
makeCookie :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe SetCookie) Source
makeCookieBS :: ToJWT v => CookieSettings -> JWTSettings -> v -> IO (Maybe ByteString) Source
Related types
BasicAuth
Combinator
Re-exported from 'servant-auth'
data BasicAuth :: *
Basic Auth.
Instances
| FromBasicAuthData usr => IsAuth BasicAuth usr Source | |
| type AuthArgs BasicAuth = (:) * BasicAuthCfg ([] *) Source |
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
Related types
data BasicAuthData :: *
A simple datatype to hold data required to decorate a request
Constructors
| BasicAuthData | |
Fields | |
data IsPasswordCorrect Source
Constructors
| PasswordCorrect | |
| PasswordIncorrect |
Utilies
Methods
throwAll :: ServantErr -> 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
generateKey :: IO JWK Source
Generate a key suitable for use with defaultConfig.
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.
Re-exports
data SetCookie :: *
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 the Default instance to create one and override values (see http://www.yesodweb.com/book/settings-types for details):
import Web.Cookie :set -XOverloadedStrings let cookie =def{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.