Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Auth.Server.Internal.ConfigTypes
Synopsis
- data IsMatch
- data JWTSettings = JWTSettings {
- signingKey :: JWK
- jwtAlg :: Maybe Alg
- validationKeys :: IO JWKSet
- audienceMatches :: StringOrURI -> IsMatch
- defaultJWTSettings :: JWK -> JWTSettings
- 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
- data SameSite
- data IsPasswordCorrect
- jwtSettingsToJwtValidationSettings :: JWTSettings -> JWTValidationSettings
- data IsSecure
Documentation
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 |
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.
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)))) |
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))) |
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)) |
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 | |