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

Servant.Auth.Server

Synopsis

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

Instances details
HasLink sub => HasLink (Auth tag value :> sub :: Type)

A HasLink instance for Auth

Instance details

Defined in Servant.Auth

Associated Types

type MkLink (Auth tag value :> sub) a #

Methods

toLink :: (Link -> a) -> Proxy (Auth tag value :> sub) -> Link -> MkLink (Auth tag value :> sub) a #

(n ~ 'S ('S 'Z), HasServer (AddSetCookiesApi n api) ctxs, AreAuths auths ctxs v, HasServer api ctxs, AddSetCookies n (ServerT api Handler) (ServerT (AddSetCookiesApi n api) Handler), ToJWT v, HasContextEntry ctxs CookieSettings, HasContextEntry ctxs JWTSettings) => HasServer (Auth auths v :> api :: Type) ctxs Source # 
Instance details

Defined in Servant.Auth.Server.Internal

Associated Types

type ServerT (Auth auths v :> api) m #

Methods

route :: Proxy (Auth auths v :> api) -> Context ctxs -> Delayed env (Server (Auth auths v :> api)) -> Router env #

hoistServerWithContext :: Proxy (Auth auths v :> api) -> Proxy ctxs -> (forall x. m x -> n x) -> ServerT (Auth auths v :> api) m -> ServerT (Auth auths v :> api) n #

type MkLink (Auth tag value :> sub :: Type) a 
Instance details

Defined in Servant.Auth

type MkLink (Auth tag value :> sub :: Type) a = MkLink sub a
type ServerT (Auth auths v :> api :: Type) m Source # 
Instance details

Defined in Servant.Auth.Server.Internal

type ServerT (Auth auths v :> api :: Type) 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 - Indefinite is returned. This indicates that other authentication methods should be tried.

Instances

Instances details
Monad AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

(>>=) :: AuthResult a -> (a -> AuthResult b) -> AuthResult b #

(>>) :: AuthResult a -> AuthResult b -> AuthResult b #

return :: a -> AuthResult a #

Functor AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

fmap :: (a -> b) -> AuthResult a -> AuthResult b #

(<$) :: a -> AuthResult b -> AuthResult a #

Applicative AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

pure :: a -> AuthResult a #

(<*>) :: AuthResult (a -> b) -> AuthResult a -> AuthResult b #

liftA2 :: (a -> b -> c) -> AuthResult a -> AuthResult b -> AuthResult c #

(*>) :: AuthResult a -> AuthResult b -> AuthResult b #

(<*) :: AuthResult a -> AuthResult b -> AuthResult a #

Foldable AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

fold :: Monoid m => AuthResult m -> m #

foldMap :: Monoid m => (a -> m) -> AuthResult a -> m #

foldMap' :: Monoid m => (a -> m) -> AuthResult a -> m #

foldr :: (a -> b -> b) -> b -> AuthResult a -> b #

foldr' :: (a -> b -> b) -> b -> AuthResult a -> b #

foldl :: (b -> a -> b) -> b -> AuthResult a -> b #

foldl' :: (b -> a -> b) -> b -> AuthResult a -> b #

foldr1 :: (a -> a -> a) -> AuthResult a -> a #

foldl1 :: (a -> a -> a) -> AuthResult a -> a #

toList :: AuthResult a -> [a] #

null :: AuthResult a -> Bool #

length :: AuthResult a -> Int #

elem :: Eq a => a -> AuthResult a -> Bool #

maximum :: Ord a => AuthResult a -> a #

minimum :: Ord a => AuthResult a -> a #

sum :: Num a => AuthResult a -> a #

product :: Num a => AuthResult a -> a #

Traversable AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

traverse :: Applicative f => (a -> f b) -> AuthResult a -> f (AuthResult b) #

sequenceA :: Applicative f => AuthResult (f a) -> f (AuthResult a) #

mapM :: Monad m => (a -> m b) -> AuthResult a -> m (AuthResult b) #

sequence :: Monad m => AuthResult (m a) -> m (AuthResult a) #

Alternative AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

MonadPlus AuthResult Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Eq val => Eq (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

(==) :: AuthResult val -> AuthResult val -> Bool #

(/=) :: AuthResult val -> AuthResult val -> Bool #

Ord val => Ord (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

compare :: AuthResult val -> AuthResult val -> Ordering #

(<) :: AuthResult val -> AuthResult val -> Bool #

(<=) :: AuthResult val -> AuthResult val -> Bool #

(>) :: AuthResult val -> AuthResult val -> Bool #

(>=) :: AuthResult val -> AuthResult val -> Bool #

max :: AuthResult val -> AuthResult val -> AuthResult val #

min :: AuthResult val -> AuthResult val -> AuthResult val #

Read val => Read (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Show val => Show (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

showsPrec :: Int -> AuthResult val -> ShowS #

show :: AuthResult val -> String #

showList :: [AuthResult val] -> ShowS #

Generic (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Associated Types

type Rep (AuthResult val) :: Type -> Type #

Methods

from :: AuthResult val -> Rep (AuthResult val) x #

to :: Rep (AuthResult val) x -> AuthResult val #

Semigroup (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

(<>) :: AuthResult val -> AuthResult val -> AuthResult val #

sconcat :: NonEmpty (AuthResult val) -> AuthResult val #

stimes :: Integral b => b -> AuthResult val -> AuthResult val #

Monoid (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

mempty :: AuthResult val #

mappend :: AuthResult val -> AuthResult val -> AuthResult val #

mconcat :: [AuthResult val] -> AuthResult val #

type Rep (AuthResult val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

type Rep (AuthResult val) = D1 ('MetaData "AuthResult" "Servant.Auth.Server.Internal.Types" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" 'False) ((C1 ('MetaCons "BadPassword" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoSuchUser" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Authenticated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 val)) :+: C1 ('MetaCons "Indefinite" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype AuthCheck val Source #

An AuthCheck is the function used to decide the authentication status (the AuthResult) of a request. Different AuthChecks 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

Instances details
Monad AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

(>>=) :: AuthCheck a -> (a -> AuthCheck b) -> AuthCheck b #

(>>) :: AuthCheck a -> AuthCheck b -> AuthCheck b #

return :: a -> AuthCheck a #

Functor AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

fmap :: (a -> b) -> AuthCheck a -> AuthCheck b #

(<$) :: a -> AuthCheck b -> AuthCheck a #

MonadFail AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

fail :: String -> AuthCheck a #

Applicative AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

pure :: a -> AuthCheck a #

(<*>) :: AuthCheck (a -> b) -> AuthCheck a -> AuthCheck b #

liftA2 :: (a -> b -> c) -> AuthCheck a -> AuthCheck b -> AuthCheck c #

(*>) :: AuthCheck a -> AuthCheck b -> AuthCheck b #

(<*) :: AuthCheck a -> AuthCheck b -> AuthCheck a #

Alternative AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

empty :: AuthCheck a #

(<|>) :: AuthCheck a -> AuthCheck a -> AuthCheck a #

some :: AuthCheck a -> AuthCheck [a] #

many :: AuthCheck a -> AuthCheck [a] #

MonadPlus AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

mzero :: AuthCheck a #

mplus :: AuthCheck a -> AuthCheck a -> AuthCheck a #

MonadIO AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

liftIO :: IO a -> AuthCheck a #

MonadTime AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

MonadReader Request AuthCheck Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

ask :: AuthCheck Request #

local :: (Request -> Request) -> AuthCheck a -> AuthCheck a #

reader :: (Request -> a) -> AuthCheck a #

Generic (AuthCheck val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Associated Types

type Rep (AuthCheck val) :: Type -> Type #

Methods

from :: AuthCheck val -> Rep (AuthCheck val) x #

to :: Rep (AuthCheck val) x -> AuthCheck val #

Semigroup (AuthCheck val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

(<>) :: AuthCheck val -> AuthCheck val -> AuthCheck val #

sconcat :: NonEmpty (AuthCheck val) -> AuthCheck val #

stimes :: Integral b => b -> AuthCheck val -> AuthCheck val #

Monoid (AuthCheck val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

Methods

mempty :: AuthCheck val #

mappend :: AuthCheck val -> AuthCheck val -> AuthCheck val #

mconcat :: [AuthCheck val] -> AuthCheck val #

type Rep (AuthCheck val) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Types

type Rep (AuthCheck val) = D1 ('MetaData "AuthCheck" "Servant.Auth.Server.Internal.Types" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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'

data JWT #

A JSON Web Token (JWT) in the 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

Instances details
FromJWT usr => IsAuth JWT usr Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Associated Types

type AuthArgs JWT :: [Type] Source #

Methods

runAuth :: proxy JWT -> proxy usr -> Unapp (AuthArgs JWT) (AuthCheck usr) Source #

type AuthArgs JWT Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Classes

class FromJWT a where #

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

class ToJWT a where #

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

Methods

encodeJWT :: a -> ClaimsSet #

Related types

data IsMatch Source #

Constructors

Matches 
DoesNotMatch 

Instances

Instances details
Eq IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Methods

(==) :: IsMatch -> IsMatch -> Bool #

(/=) :: IsMatch -> IsMatch -> Bool #

Ord IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Read IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Show IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Generic IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep IsMatch :: Type -> Type #

Methods

from :: IsMatch -> Rep IsMatch x #

to :: Rep IsMatch x -> IsMatch #

type Rep IsMatch Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep IsMatch = D1 ('MetaData "IsMatch" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" 'False) (C1 ('MetaCons "Matches" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoesNotMatch" 'PrefixI 'False) (U1 :: Type -> Type))

Settings

data JWTSettings Source #

JWTSettings are used to generate cookies, and to verify JWTs.

Constructors

JWTSettings 

Fields

Instances

Instances details
Generic JWTSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep JWTSettings :: Type -> Type #

type Rep JWTSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep JWTSettings = D1 ('MetaData "JWTSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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 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'

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 XSRF protection.

Instances

Instances details
FromJWT usr => IsAuth Cookie usr Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Associated Types

type AuthArgs Cookie :: [Type] Source #

Methods

runAuth :: proxy Cookie -> proxy usr -> Unapp (AuthArgs Cookie) (AuthCheck usr) Source #

type AuthArgs Cookie Source # 
Instance details

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

Instances details
Eq CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Show CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Generic CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep CookieSettings :: Type -> Type #

Default CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Methods

def :: CookieSettings #

type Rep CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep CookieSettings = D1 ('MetaData "CookieSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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

Instances details
Eq XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Show XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Generic XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep XsrfCookieSettings :: Type -> Type #

Default XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep XsrfCookieSettings = D1 ('MetaData "XsrfCookieSettings" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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.

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 :: (ToJWT session, AddHeader "Set-Cookie" SetCookie response withOneCookie, AddHeader "Set-Cookie" SetCookie withOneCookie withTwoCookies) => 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 :: (AddHeader "Set-Cookie" SetCookie response withOneCookie, AddHeader "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

data IsSecure #

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

Instances details
Eq IsSecure 
Instance details

Defined in Servant.API.IsSecure

Ord IsSecure 
Instance details

Defined in Servant.API.IsSecure

Read IsSecure 
Instance details

Defined in Servant.API.IsSecure

Show IsSecure 
Instance details

Defined in Servant.API.IsSecure

Generic IsSecure 
Instance details

Defined in Servant.API.IsSecure

Associated Types

type Rep IsSecure :: Type -> Type #

Methods

from :: IsSecure -> Rep IsSecure x #

to :: Rep IsSecure x -> IsSecure #

HasLink sub => HasLink (IsSecure :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (IsSecure :> sub) a #

Methods

toLink :: (Link -> a) -> Proxy (IsSecure :> sub) -> Link -> MkLink (IsSecure :> sub) a #

HasServer api context => HasServer (IsSecure :> api :: Type) context 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (IsSecure :> api) m #

Methods

route :: Proxy (IsSecure :> api) -> Context context -> Delayed env (Server (IsSecure :> api)) -> Router env #

hoistServerWithContext :: Proxy (IsSecure :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (IsSecure :> api) m -> ServerT (IsSecure :> api) n #

type Rep IsSecure 
Instance details

Defined in Servant.API.IsSecure

type Rep IsSecure = D1 ('MetaData "IsSecure" "Servant.API.IsSecure" "servant-0.19-KR5MGMkCgzD3mkDu6Wi5Ug" 'False) (C1 ('MetaCons "Secure" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotSecure" 'PrefixI 'False) (U1 :: Type -> Type))
type MkLink (IsSecure :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (IsSecure :> sub :: Type) a = MkLink sub a
type ServerT (IsSecure :> api :: Type) m 
Instance details

Defined in Servant.Server.Internal

type ServerT (IsSecure :> api :: Type) m = IsSecure -> ServerT api m

data SameSite Source #

Instances

Instances details
Eq SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Ord SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Read SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Show SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Generic SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep SameSite :: Type -> Type #

Methods

from :: SameSite -> Rep SameSite x #

to :: Rep SameSite x -> SameSite #

type Rep SameSite Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep SameSite = D1 ('MetaData "SameSite" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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 :: [*]) (ctxs :: [*]) v Source #

Minimal complete definition

runAuths

Instances

Instances details
AreAuths ('[] :: [Type]) ctxs v Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Methods

runAuths :: proxy '[] -> Context ctxs -> AuthCheck v Source #

(AuthCheck v ~ App (AuthArgs a) (Unapp (AuthArgs a) (AuthCheck v)), IsAuth a v, AreAuths as ctxs v, AppCtx ctxs (AuthArgs a) (Unapp (AuthArgs a) (AuthCheck v))) => AreAuths (a ': as) ctxs v Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Methods

runAuths :: proxy (a ': as) -> Context ctxs -> AuthCheck v Source #

BasicAuth

Combinator

Re-exported from 'servant-auth'

data BasicAuth #

Basic Auth.

Instances

Instances details
FromBasicAuthData usr => IsAuth BasicAuth usr Source # 
Instance details

Defined in Servant.Auth.Server.Internal.Class

Associated Types

type AuthArgs BasicAuth :: [Type] Source #

Methods

runAuth :: proxy BasicAuth -> proxy usr -> Unapp (AuthArgs BasicAuth) (AuthCheck usr) Source #

type AuthArgs BasicAuth Source # 
Instance details

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

data IsPasswordCorrect Source #

Instances

Instances details
Eq IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Ord IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Read IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Show IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Generic IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep IsPasswordCorrect :: Type -> Type #

type Rep IsPasswordCorrect Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

type Rep IsPasswordCorrect = D1 ('MetaData "IsPasswordCorrect" "Servant.Auth.Server.Internal.ConfigTypes" "servant-auth-server-0.4.7.0-DURpbxwj2hEG9mkaDDq3VV" '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

Instances details
ThrowAll Application Source #

for servant <0.11

Instance details

Defined in Servant.Auth.Server.Internal.ThrowAll

MonadError ServerError m => ThrowAll (m a) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ThrowAll

Methods

throwAll :: ServerError -> m a Source #

ThrowAll b => ThrowAll (a -> b) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ThrowAll

Methods

throwAll :: ServerError -> a -> b Source #

(ThrowAll a, ThrowAll b) => ThrowAll (a :<|> b) Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ThrowAll

Methods

throwAll :: ServerError -> a :<|> b Source #

MonadError ServerError m => ThrowAll (Tagged m Application) Source #

for servant >=0.11

Instance details

Defined in Servant.Auth.Server.Internal.ThrowAll

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.

readKey :: FilePath -> IO JWK Source #

Reads a key from a file.

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

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances

Instances details
Default Double 
Instance details

Defined in Data.Default.Class

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

def :: Int #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

def :: Ordering #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default SetCookie
def = defaultSetCookie
Instance details

Defined in Web.Cookie

Methods

def :: SetCookie #

Default XsrfCookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Default CookieSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Methods

def :: CookieSettings #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Ratio a #

Default a => Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Complex a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Default r => Default (e -> r) 
Instance details

Defined in Data.Default.Class

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f, g) #

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 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

Instances details
Eq SetCookie 
Instance details

Defined in Web.Cookie

Show SetCookie 
Instance details

Defined in Web.Cookie

NFData SetCookie 
Instance details

Defined in Web.Cookie

Methods

rnf :: SetCookie -> () #

Default SetCookie
def = defaultSetCookie
Instance details

Defined in Web.Cookie

Methods

def :: SetCookie #

ToHttpApiData SetCookie

Note: this instance works correctly for alphanumeric name and value

>>> let Right c = parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
>>> toUrlPiece c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
>>> toHeader c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData SetCookie

Note: this instance works correctly for alphanumeric name and value

>>> parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
Right (SetCookie {setCookieName = "SESSID", setCookieValue = "r2t5uvjq435r4q7ib3vtdjq120", setCookiePath = Nothing, setCookieExpires = Nothing, setCookieMaxAge = Nothing, setCookieDomain = Nothing, setCookieHttpOnly = False, setCookieSecure = False, setCookieSameSite = Nothing})
Instance details

Defined in Web.Internal.HttpApiData