servant-auth-server-0.4.1.0: servant-server/servant-auth compatibility

Safe HaskellNone
LanguageHaskell2010

Servant.Auth.Server.Internal.ConfigTypes

Synopsis

Documentation

data XsrfCookieSettings Source #

The policies to use when generating and verifying XSRF cookies

Constructors

XsrfCookieSettings 

Fields

Instances
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 :: * -> * #

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.1.0-1w1DRS54AVKLDL2AYz1Azv" 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))))

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
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 :: * -> * #

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

data JWTSettings Source #

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

Constructors

JWTSettings 

Fields

Instances
Generic JWTSettings Source # 
Instance details

Defined in Servant.Auth.Server.Internal.ConfigTypes

Associated Types

type Rep JWTSettings :: * -> * #

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.1.0-1w1DRS54AVKLDL2AYz1Azv" 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)))))

data SameSite Source #

Instances
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 :: * -> * #

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.1.0-1w1DRS54AVKLDL2AYz1Azv" False) (C1 (MetaCons "AnySite" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SameSiteStrict" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SameSiteLax" PrefixI False) (U1 :: * -> *)))

data IsPasswordCorrect Source #

Instances
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 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.1.0-1w1DRS54AVKLDL2AYz1Azv" False) (C1 (MetaCons "PasswordCorrect" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PasswordIncorrect" PrefixI False) (U1 :: * -> *))

data IsMatch Source #

Constructors

Matches 
DoesNotMatch 
Instances
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 :: * -> * #

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.1.0-1w1DRS54AVKLDL2AYz1Azv" False) (C1 (MetaCons "Matches" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DoesNotMatch" PrefixI False) (U1 :: * -> *))

defaultJWTSettings :: JWK -> JWTSettings Source #

A JWTSettings where the audience always matches.

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
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 :: * -> * #

Methods

from :: IsSecure -> Rep IsSecure x #

to :: Rep IsSecure x -> IsSecure #

HasLink sub => HasLink (IsSecure :> sub :: *) 
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 :: *) 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.14.1-3072kfhxJq5BHSzCgVSyLs" False) (C1 (MetaCons "Secure" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NotSecure" PrefixI False) (U1 :: * -> *))
type MkLink (IsSecure :> sub :: *) a 
Instance details

Defined in Servant.Links

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

Defined in Servant.Server.Internal

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